STM with fclabels - haskell

I built a small game engine to manage a board of squares (currently used for playing a Conway's game of life). All the data is accessed throught lenses from fclabels and State. The engine couples user input and graphic rendering (usual game loop).
The computations between frames can sometimes be slow and long to execute. So I would like to use concurrency to manage the squares, using STM's TVar.
My data is currently represented like this:
data World = World {
… -- window configuration, not important
, _squares :: TVar [Square]
}
mkLabels [''World] -- creates labels, similar to mkLenses
My functions run in the Game Monad, which is defined as follow:
type Game a = StateT World IO a
Using the monadic versions of labels. I use Getters & Setters inside my monad.
I would like to know if there is a way to somehow write new labels that behave like these:
gets :: MonadState f m => Lens (->) f o -> m o
…
puts :: MonadState f m => Lens (->) f o -> o -> m ()
But that takes care of STM (gets would involve readTVar, puts would involve writeTvar, etc.).

If I understand you correctly, you want to define a lens tlens s.t.:
gets tlens
is the same as:
do tvar <- gets squares
sqs <- liftIO $ atomically $ readTVar tvar
return sqs
and where puts tlens sqs is the same as:
do tvar <- gets squares
liftIO $ atomically $ writeTVar tvar sqs
I think this can be answered by looking at the type of gets:
gets :: MonadState f m => Lens (->) f o -> m o
The lens parameter is pure and not monadic. To get at the contents of the TVar you'll need to run code in the IO-monad.
Moreover, the definition of gets in Data.Label.Monadic is (link) is:
gets lens = State.gets (Total.get lens)
where State is Control.Monad.State and Total is Data.Label.Total.
But State.gets takes a pure function, so again you're not going to be able to create a lens which will work with gets.

Related

Best practices with monad transformers : to hide or not to hide 'liftIO'

I will preface this by saying that I am a novice Haskell programmer (tinkered with it sporadically over the years) but I have a fair few years on the counter when it comes to OOO and imperative programming. I am currently learning how to use monads & combining them via the use of monad transformers (assuming I've got the correct term).
While I am able to assemble/chain things together, I am finding it hard to build an intuition for what the best way and style is & how best to assemble/write those interactions.
Specifically, I am curious to know what the best practice (or at least your practice) is for using lift/liftIO and any flavour in between & if there is way (and benefit) to hide them as I am finding them rather 'noisy'.
Below is an example snippet which I have put together to illustrate what I mean :
consumeRenderStageGL' :: RenderStage -> StateT RenderStageContext IO ()
consumeRenderStageGL' r = do
pushDebugGroupGL (name r)
liftIO $ consumePrologueGL ( prologue r )
liftIO $ consumeEpilogueGL ( epilogue r )
consumeStreamGL ( stream r )
liftIO $ popDebugGroupGL
Some of the functions it calls make use of the state monad :
pushDebugGroupGL :: String -> StateT RenderStageContext IO ()
pushDebugGroupGL tag = do
currentDebugMessageID <- gets debugMessageID
liftIO $ GL.pushDebugGroup GL.DebugSourceApplication (GL.DebugMessageID currentDebugMessageID) tag
modify (\fc -> fc { debugMessageID = (currentDebugMessageID + 1) })
consumeStreamGL :: Stream -> StateT RenderStageContext IO ()
consumeStreamGL s = do
mapM_ consumeTokenGL s
logGLErrors
While most don't and just live in IO (meaning they have to be lifted):
consumePrologueGL :: Prologue -> IO ()
consumePrologueGL p = do
colourClearFlag <- setupAndReturnClearFlag GL.ColorBuffer ( clearColour p ) (\(Colour4 r g b a) -> GL.clearColor $= (GL.Color4 r g b a))
depthClearFlag <- setupAndReturnClearFlag GL.DepthBuffer ( clearDepth p ) (\d -> GL.clearDepthf $= d)
stencilClearFlag <- setupAndReturnClearFlag GL.StencilBuffer ( clearStencil p ) (\s -> GL.clearStencil $= fromIntegral s)
GL.clear $ catMaybes [colourClearFlag, depthClearFlag, stencilClearFlag]
logGLErrors
where
setupAndReturnClearFlag flag mValue function = case mValue of
Nothing -> return Nothing
Just value -> (function value) >> return (Just flag)
My question is : is there any way to hide the liftIO in consumeRenderStageGL' and more importantly would this be a good or a bad idea?
One way I can think of hiding/getting rid of the liftIO is to bring both my consumePrologueGL & consumeEpilogueGL into my state monad but this seems wrong in the sense that those function do not need (and should not) interact with it ; all this just to reduce code noise.
The other option I can think of is to simply create the lifted version of the functions and call them in consumeRenderStageGL' - this would reduce the code noise but be identical in execution/evaluation.
The third option, which is how my logGLErrors works is that I have used a type class which has an instance defined for both IO & my state monads.
I look forward to reading what your opinions, advices and practices are.
Thanks in advance!
There are a few solutions. A common one is to make your basic actions MonadIO m => m … instead of IO …:
consumePrologueGL :: (MonadIO m) => Prologue -> m ()
consumePrologueGL p = liftIO $ do
…
Then you can use them in StateT RenderStageContext IO () without wrapping, due to MonadIO m => MonadIO (StateT s m), and of course MonadIO IO where liftIO is the identity function.
You can also abstract over the StateT part using MonadState from mtl, so if you add another transformer above/below it, you won’t have the same issue of lifting from/to StateT.
pushDebugGroupGL
:: (MonadIO m, MonadState RenderStageContext m)
=> String -> m ()
Generally, a concrete stack of transformers types is fine, it just helps to wrap all your basic operations for convenience so that all the lifts are in one place.
mtl helps remove the lift noise from your code altogether, and working in a polymorphic type m means you have to declare which effects a function actually uses, and can substitute different implementations of all the effects (except for MonadIO) for testing. Using monad transformers as an effect system like this is great if you have few types of effects; if you want something finer-grained or more flexible, you’ll start hitting the pain points that make people reach for algebraic effects instead.
It’s also worth assessing whether you need StateT over IO. Typically if you’re in IO, you don’t need the pure state offered by StateT, so instead of StateT MutableState IO you might as well use ReaderT (IORef MutableState) IO.
It’s also possible to make that (or a newtype wrapper for it) an instance of MonadState MutableState, so your code using get/put/modify wouldn’t even need to change:
{-# Language GeneralizedNewtypeDeriving #-}
import Data.Coerce (coerce)
newtype MutT s m a = MutT
{ getMutT :: ReaderT (IORef s) m a }
deriving
( Alternative
, Applicative
, Functor
, Monad
, MonadIO
, MonadTrans
)
evalMutT :: MutT s m a -> IORef s -> m a
evalMutT = coerce
instance (MonadIO m) => MonadState s (MutT s m) where
state f = MutT $ do
r <- ask
liftIO $ do
-- NB: possibly lazier than you want.
(a, s) <- f <$> readIORef r
a <$ writeIORef r s
This combo of ReaderT & IO is a pretty common design pattern.

How to limit code changes when introducing state?

I am a senior C/C++/Java/Assembler programmer and I have been always fascinated by the pure functional programming paradigm. From time to time, I try to implement something useful with it, e.g., a small tool, but often I quickly reach a point where I realize that I (and my tool, too) would be much faster in a non-pure language. It's probably because I have much more experience with imperative programming languages with thousands of idoms, patterns and typical solution approaches in my head.
Here is one of those situations. I have encountered it several times and I hope you guys can help me.
Let's assume I write a tool to simulate communication networks. One important task is the generation of network packets. The generation is quite complex, consisting of dozens of functions and configuration parameters, but at the end there is one master function and because I find it useful I always write down the signature:
generatePackets :: Configuration -> [Packet]
However, after a while I notice that it would be great if the packet generation would have some kind of random behavior deep down in one of the many sub-functions of the generation process. Since I need a random number generator for that (and I also need it at some other places in the code), this means to manually change dozens of signatures to something like
f :: Configuration -> RNGState [Packet]
with
type RNGState = State StdGen
I understand the "mathematical" necessity (no states) behind this. My question is on a higher (?) level: How would an experienced Haskell programmer have approached this situation? What kind of design pattern or work flow would have avoided the extra work later?
I have never worked with an experienced Haskell programmer. Maybe you will tell me that you never write signatures because you have to change them too often afterwards, or that you give all your functions a state monad, "just in case" :)
One approach that I've been fairly successful with is using a monad transformer stack. This lets you both add new effects when needed and also track the effects required by particular functions.
Here's a really simple example.
import Control.Monad.State
import Control.Monad.Reader
data Config = Config { v1 :: Int, v2 :: Int }
-- the type of the entire program describes all the effects that it can do
type Program = StateT Int (ReaderT Config IO) ()
runProgram program config startState =
runReaderT (runStateT program startState) config
-- doesn't use configuration values. doesn't do IO
step1 :: MonadState Int m => m ()
step1 = get >>= \x -> put (x+1)
-- can use configuration and change state, but can't do IO
step2 :: (MonadReader Config m, MonadState Int m) => m ()
step2 = do
x <- asks v1
y <- get
put (x+y)
-- can use configuration and do IO, but won't touch our internal state
step3 :: (MonadReader Config m, MonadIO m) => m ()
step3 = do
x <- asks v2
liftIO $ putStrLn ("the value of v2 is " ++ show x)
program :: Program
program = step1 >> step2 >> step3
main :: IO ()
main = do
let config = Config { v1 = 42, v2 = 123 }
startState = 17
result <- runProgram program config startState
return ()
Now if we want to add another effect:
step4 :: MonadWriter String m => m()
step4 = tell "done!"
program :: Program
program = step1 >> step2 >> step3 >> step4
Just adjust Program and runProgram
type Program = StateT Int (ReaderT Config (WriterT String IO)) ()
runProgram program config startState =
runWriterT $ runReaderT (runStateT program startState) config
To summarize, this approach lets us decompose a program in a way that tracks effects but also allows adding new effects as needed without a huge amount of refactoring.
edit:
It's come to my attention that I didn't answer the question about what to do for code that's already written. In many cases, it's not too difficult to change pure code into this style:
computation :: Double -> Double -> Double
computation x y = x + y
becomes
computation :: Monad m => Double -> Double -> m Double
computation x y = return (x + y)
This function will now work for any monad, but doesn't have access to any extra effects. Specifically, if we add another monad transformer to Program, then computation will still work.

Building a monad on top of hedis, a haskell redis lib

I want to write a simple DSL on top of hedis, a redis lib. The goal is to write functions like:
iWantThis :: ByteString -> MyRedis ()
iWantThis bs = do
load bs -- :: MyRedis () It fetches a BS from Redis and puts it as
-- the state in a state monad
bs <- get -- :: MyRedis (Maybe ByteString) Gets the current state
put $ doSomethingPure bs -- :: MyMonad () Updates the state
commit -- :: MyRedis () Write to redis
The basic idea is to fetch data from redis, put it in a state monad, do some stuff with the state and then put the updated state back into redis.
Obviously, it should be atomic so load and put should happen in the same Redis transaction. Hedis permits that by wrapping calls to Redis in a RedisTx (Queued a). For example, we have get :: ByteString -> RedisTx (Queued a).
Queued is a monad and you then run multiExec on your Queued a to execute everything in the Queued a in the same transaction. So I tried to define my MyRedis as such:
import qualified Database.Redis as R
newtype MyRedis a = MyRedis { runMyRedis :: StateT MyState R.RedisTx a } -- deriving MonadState, MyState...
The run function calls multiExec so I'm sure that as long as I stay in MyRedis everything happens in the same transaction.
run :: MyRedis (R.Queued a) -> MyState -> IO (R.TxResult a)
run m s = R.runRedis (undefined :: R.Connection) (R.multiExec r)
where r = evalStateT (runMyRedis m) s
Furthermore, I can define commit as:
commit :: ByteString -> MyRedis (R.Queued R.Status)
commit bs = do
MyState new <- get
(MyRedis . lift) (R.set bs new)
And a computation would look like:
computation :: MyRedis (R.Queued R.Status)
computation = do
load gid
MyState bs <- get
put $ MyState (reverse bs)
commit gid
where gid = "123"
But I can't figure out how to write "load"
load :: ByteString -> MyRedis ()
load gid = undefined
Actually, I think that it is not possible to write load, because get is of type ByteString -> RedisTx (Queued (Maybe ByteString)) and I have no way to peek into the Queued monad without executing it.
Questions:
Is it correct that because of the type of Hedis's get, it doesn't make sense to define a load function with the semantics above?
Is it possible to change the MyRedis type definition to make it work?
Hedis doesn't define a RedisT monad transformer. If such a transformer existed, would it be of any help?
Hedis defines (but does not export to lib users) a MonadRedis typeclass; would making my monad an instance of that typeclass help?
Is it the right approach? I want to:
Abstract over Redis (I may switch someday to another DB)
Restrict the Redis functions available to my users (basically only lifting to MyRedis get and set)
Guarantee that when I run my monad everything happens in the same (redis) transaction
Put my redis abstraction at the same level as other functions in my monad
You can play with the code at http://pastebin.com/MRqMCr9Q. Sorry for the pastebin, lpaste.net is down at the moment.
What you want is not possible. In particular, you can't provide a monadic interface while a running a computation in one Redis transaction. Nothing to do with the library you're using - it's just not something Redis can do.
Redis transactions are rather different from the ACID transactions you may be used to from the world of relational databases. Redis transactions have batching semantics, which means that later commands cannot in any way depend on the result of earlier commands.
Look: here's something similar to your example, run at the Redis command line.
> set "foo" "bar"
OK
> multi
OK
> get "foo"
QUEUED -- I can't now set "baz" to the result of this command because there is no result!
> exec
1) "bar" -- I only get the result after running the whole tran
Anyway, that's the purpose of that library's slightly odd Queued type: the idea is to prevent you from accessing any of the results of a batched command until the end of the batch. (It seems that the author wanted to abstract over batched and non-batched commands but there are simpler ways to do that. See below for how I'd simplify the transactional interface.)
So there's no "choosing what to do next" when Redis transactions are involved, but the whole point of (>>=) :: m a -> (a -> m b) -> m b is that later effects can depend on earlier results. You have to choose between monads and transactions.
If you decide you want transactions, there's an alternative to Monad called Applicative which handlily supports purely-static effects. This is exactly what we need. Here's some (entirely untested) code illustrating how I'd cook an Applicative version of your idea.
newtype RedisBatch a = RedisBatch (R.RedisTx (R.Queued a))
-- being a transactional batch of commands to send to redis
instance Functor RedisBatch where
fmap = liftA
instance Applicative RedisBatch where
pure x = RedisBatch (pure (pure x))
(RedisBatch rf) <*> (RedisBatch rx) = RedisBatch $ (<*>) <$> rf <*> rx
-- no monad instance
get :: ByteString -> RedisBatch (Maybe ByteString)
get key = RedisBatch $ get key
set :: ByteString -> ByteString -> RedisBatch (R.Status)
set key val = RedisBatch $ set key val
runBatch :: R.Connection -> RedisBatch a -> IO (R.TxResult a)
runBatch conn (RedisBatch x) = R.runRedis conn (R.multiExec x)
If I wanted to abstract over transactional-or-not behaviour, as the library author has attempted to do, I'd write a second type RedisCmd exposing a monadic interface, and a class containing my primitive operations, with instances for my two RedisBatch and RedisCmd types.
class Redis f where
get :: ByteString -> f (Maybe ByteString)
set :: ByteString -> ByteString -> f (R.Status)
Now, computations with a type of (Applicative f, Redis f) => ... could work for either behaviour (transactional or not), but those which require a monad (Monad m, Redis m) => ... would only be able to run in non-transactional mode.
When all's said and done, I'm not convinced it's worth it. People seem to like building abstractions over libraries like this, invariably providing less functionality than the library did and writing more code for bugs to lurk in. Whenever someone says "I may want to switch databases" I sigh: the only sufficiently abstract abstraction for that purpose is one which provides no functionality. Worry about switching databases when the time comes that you need to (that is, never).
On the other hand, if your goal is not to abstract the database but just to clean up the interface, the best thing may be to fork the library.

Repeatedly applying function to game board in Haskell

I've created a chess game with Haskell and everything seems to be working. However, I'm trying to define the main function of the program so that each time a move is made (which takes two positions and a board as arguments) the resulting board is kept somewhere, so that it can then be used as an argument for the next move. The code looks something like this.
makeMove :: Position -> Position -> Board -> Board
makeMove pos1 pos2 board = ...
I'm aware of the do notation and have a basic understanding of IO in Haskell, but I'm still unsure on how to proceed.
I'm assuming you want your game to be relatively dynamic and to respond to input, hence the IO question.
I'll give a bit of background theory on imperative style commands and IO interpreted as functions, then look at this in Haskell and finally talk about your case from this point of view.
Some background on imperative commands
If this is stuff you know, apologies, but it might help anyway, or it might help others.
In Haskell, we obviously have no direct mutation of variables. But we can consider a (closely) related idea of 'functions on states' - commands which would, in an imperative paradigm, be seen as mutating variables, can be seen as a 'state transformer': a function which, given one state (of the program, world, whatever) outputs another one.
An example:
Suppose we have a state consisting of a single integer variable a. Use the notation x := y meaning 'assign the value of expression y to the variable x'. (In many modern imperative languages this is written x = y, but to disambiguate with the equality relation = we can use a slightly different symbol.) Then the command (call it C)
a := 0
can be seen as something which modifies the variable a. But if we have an abstract idea of a type of 'states', we can see the 'meaning' of C as a function from states to states. This is sometimes written 〚C〛.
So 〚C〛: states -> states, and for any state s, 〚C〛s = <the state where a = 0>. There are much more complicated state transformers that act on much more complicated kinds of state, but the principle is not more complicated than this!
An important way to make new state transformers from old ones is notated by the familiar semicolon. So if we have state transformers C1 and C2, we can write a new state transformer which 'does C1 and then C2' as C1;C2. This is familiar from many imperative programming languages. In fact, the meaning as a state transformer of this 'concatenation' of commands is
〚C1;C2〛: states -> states
〚C1;C2〛s = 〚C2〛(〚C1〛s)
i.e. the composition of the commands. So in a sense, in Haskell-like notation
(;) : (states -> states) -> (states -> states) -> states -> states
c1 ; c2 = c2 . c1
i.e. (;) is an operator on state-transformers which composes them.
Haskell's approach
Now, Haskell has some neat ways of bringing these concepts directly into the language. Instead of having a distinct type for commands (state modifiers without a type, per se) and expressions (which, depending on the imperative context, may also be allowed to modify the state as well as resulting in a value), Haskell somewhat combines these into one. IO () entities represent pure state modifying actions which don't have a meaning as an expression, and IO a entities (where a is not ()) represent (potential) state modifying actions whose meaning as an expression (like a 'return type') is of type a.
Now, since IO () is like a command, we want something like (;), and indeed, in Haskell, we have the (>>) and (>>=) ('bind operators') which act just like it. We have (>>) :: IO a -> IO b -> IO b and (>>=) :: IO a -> (a -> IO b) -> IO b. For a command (IO ()) or command-expression (IO a), the (>>) operator simply ignores the return if there is one, and gives you the operation of doing the two commands in sequence. The (>>=) on the other hand is for if we care about the result of the expression. The second argument is a function which, when applied to the result of the command-expression, gives another command/command-expression which is the 'next step'.
Now, since Haskell has no 'mutable variables', an IORef a-type variable represents a mutable reference variable, to an a-type variable. If ioA is an IORef a-type entity, we can do readIORef ioA which returns an IO a, the expression which is the result of reading the variable. If x :: a we can do writeIORef ioA x which returns an IO (), the command which is the result of writing the value x to the variable. To create a new IORef a, with value x we use newIORef x which gives an IO (IORef a) where the IORef a initially contains the value x.
Haskell also has do notation which you alluded to, which is a nice syntactic sugar for the above. Simply,
do a; b = a >> b
do v <- e; c = e >>= \v -> c
Your case
If we have some IO entity getAMove :: IO (Position, Position) (which might be a simple parser on some user input, or whatever suits your case), we can define
moveIO :: IORef Board -> IO ()
moveIO board =
readIORef board >>= \currentState -> -- read current state of the board
getAMove >>= \(pos1, pos2) -> -- obtain move instructions
writeIORef board (makeMove pos1 pos2 currentState) -- update the board per makeMove
This can also be written using do notation:
moveIO board = do
currentState <- readIORef board; -- read current state of the board
(pos1, pos2) <- getAMove; -- obtain move instructions
writeIORef board (makeMove pos1 pos2 currentState) -- update the board per makeMove
Then, whenever you need a command which updates an IORef Board based on a call to getAMove you can use this moveIO.
Now, if you make appropriate functions with the following signatures, a simple main IO loop can be devised:
-- represents a test of the board as to whether the game should continue
checkForContinue :: Board -> Bool
checkForContinue state = ...
-- represents some kind of display action of the board.
-- could be a simple line by line print.
displayBoardState :: Board -> IO ()
displayBoardState state = ...
-- represents the starting state of the board.
startState :: Board
-- a simple main loop
mainLoop :: IORef Board -> IO ()
mainLoop board = do
currentState <- readIORef board;
displayState currentState;
if checkForContinue currentState then
do moveIO board; mainLoop board
else return ()
main :: IO ()
main = do
board <- newIORef startState;
mainLoop board
You could use recursion to model state as follows:
main :: IO ()
main = do
let initialBoard = ...
gameLoop initialBoard
gameLoop :: Board -> IO ()
gameLoop board | gameOver board = putStrLn "Game over."
| otherwise = do
print board
move <- askUserToMove
let newBoard = applyMove move board
gameLoop newBoard
Here board is "changed" by computing a new one and recursively calling the game loop.

What is the name of this Monad Stack function?

I've got a bunch of stateful functions inside a State monad. At one point in the program there needs to be some IO actions so I've wrapped IO inside a StateT getting a pair of types like this:
mostfunctions :: State Sometype a
toplevel :: StateT Sometype IO a
To keep things simple I don't want pass the IO context into the main set of functions and I would like to avoid wrapping them in the monad stack type. But in order to call them from the toplevel function I need something akin to a lift, but I'm not trying to lift a value from the inner monad. Rather I want to convert the state in the StateT monad into something equivalent in the State monad. To do this I've got the following:
wrapST :: (State Sometype a) -> StateT Sometype IO a
wrapST f = do s <- get
let (r,s2) = runState f s
put s2
return r
This then get used to interleave things like the following:
toplevel = do liftIO $ Some IO functions
wrapST $ Some state mutations
liftIO $ More IO functions
....
It seems like a fairly obvious block of code so I'm wondering does this function have a standard name, and it is already implemented somewhere in the standard libraries? I've tried to keep the description simple but obviously this extends to pulling one transformer out of a stack, converting the wrapped value to the cousin of the transformer type, skipping the monads below in the stack, and then pushing the results back in at the end.
It may be a good idea to refactor your code to use the type StateT SomeType m a instead of State SomeType a, because the first one is compatible to an arbitrary monad stack. If you'd change it like this, you don't need a function wrapST anymore, since you can call the stateful functions directly.
Okay. Suppose you have a function subOne :: Monad m => State Int Int:
subOne = do a <- get
put $ a - 1
return a
Now, change the types of all functions like this one from State SomeType a to StateT SomeType m a, leaving m as is. This way, your functions can work on any monadic stack. For those functions, that require IO, you can specify, that the monad at the bottom must be IO:
printState :: MonadIO m => StateT Int m ()
printState = do a <- get
liftIO $ print a
Now, it should be possible to use both functions together:
-- You could use me without IO as well!
subOne :: Monad m => StateT Int m ()
subOne = do a <- get
put $ a - 1
printState :: MonadIO m => StateT Int m ()
printState = do a <- get
liftIO $ print a
toZero :: StateT Int IO ()
toZero = do subOne -- A really pure function
printState -- function may perform IO
a <- get
when (a > 0) toZero
PS: I use GHC 7, some of the libs changed midway, so it might be a bit different on GHC 6.
A more direct answer to your question: the function hoist does exactly what you're describing in a slightly more generic way. Example usage:
import Control.Monad.State
import Data.Functor.Identity
import Control.Monad.Morph
foo :: State Int Integer
foo = put 1 >> return 1
bar :: StateT Int IO Integer
bar = hoist (return . runIdentity) foo
hoist is part of the MFunctor class, which is defined like this:
class MFunctor t where
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b
There are instances for most monad tranformers, but not ContT.

Resources