Playing aroud with Haskell State - haskell

So I am trying to implement a Haskell game using the State and as a part of the game, I wanted to implement ways to save a current player's name and retrieve it when called. I have helper functions popStack and pushStack which pops and pushes values into stack respectively.
The current code:
import Control.Monad.State
data Gamestate = Gamestate {
gamestack :: [String],
gamememory :: String
}
type NewGameState = State GameState
popStack :: NewGameState String
popStack = state $ \st -> case gamestack st of
[] -> (0.0,st)
x:xs -> (x,st { gamestack = xs })
pushStack :: String -> NewGameState ()
push d = modify $ \st -> st { gamestack = d : gamestack st }
I have come up with the following code for saveName and getName.
saveName :: NewGameState ()
saveName = do
memory <-head
pushStack $ x
getName :: NewGameState ()
getName = do
memory <- head gamestack
popStack $ memory
The code snippets above return type errors. I don't understand State Monads much. So how do I copy the current players name at the top of the gamestack into gamememory using saveName and push the gamememory at the top of gamestack when I use getName?
Sorry if its a bit confusing. I am an ESL speaker. Thanks in advance.

I'm going to answer your question by showing you the idiomatic way to do what you are trying to do. As I go along I'm going to point out what I fixed in your code.
First problem: You have inconsistent capitalization of Gamestate. Capitalization matters in Haskell, so I renamed everything to GameState.
So after making that fixes, the first thing I did was define lenses to your two data type's fields. This makes it much easier do stateful things that modify a subset of your state. You will see this when I get to the implementations of the remaining functions:
import Control.Monad.State
import Control.Lens
data GameState = GameState
{ _gamestack :: [String]
, _gamememory :: String
}
gamestack :: Lens' GameState [String]
gamestack k (GameState s m) = fmap (\s' -> GameState s' m) (k s)
gamememory :: Lens' GameState String
gamememory k (GameState s m) = fmap (\m' -> GameState s m') (k m)
type NewGameState = State GameState
Note that you don't have to manually define lenses like this. Instead of defining gamememory and gamestack, you could also have done this instead:
{-# LANGUAGE TemplateHaskell #-} -- Note the extension
import Control.Lens
data GameState = GameState
{ _gamestack :: [String]
, _gamememory :: String
}
makeLenses ''GameState
Whichever way you choose, once we have these lenses, we can write push and pop in such a way that they don't care what state they are acting on, as long as it is a list:
pop :: State [a] (Maybe a)
pop = do
s <- get
case s of
[] -> return Nothing
x:xs -> do
put xs
return (Just x)
push :: a -> State [a] ()
push d = modify (d:)
Notice that I changed pop to return a Maybe if the list is empty. This is more idiomatic Haskell than defaulting to 0 or using head.
Using push and pop, it becomes very easy to transfer values between your game's memory and its stack:
saveName :: NewGameState ()
saveName = do
memory <- use gamememory
zoom gamestack (push memory)
getName :: NewGameState ()
getName = do
m <- zoom gamestack pop
case m of
Nothing -> return ()
Just x -> gamememory .= x
Notice how I use zoom to localize push and pop to operate on either the gamememory or the gamestack fields. zoom takes a lens to a sub-field and then runs the stateful action as if the entire state were just that sub-field. This is cool because now push and pop are much more reusable and we don't have to bake in a specific choice of state data type into them.
This also uses .=, which sets a given field. It's basically the same as:
lens .= x = zoom lens (put x)
To learn more about lenses, (.=), and zoom, you might want to read this post that I wrote.
Edit: By request, here is the lens-free version:
import Control.Monad.State
data GameState = GameState
{ gamestack :: [String]
, gamememory :: String
}
type NewGameState = State GameState
saveName :: NewGameState ()
saveName = do
GameState stack memory <- get
put (GameState (memory:stack) memory)
getName :: NewGameState ()
getName = do
GameState stack memory <- get
case stack of
[] -> put (GameState stack memory)
x:xs -> put (GameState xs x )

If something is on the right side of a <- than it has to be in that monad. So what you want here is something like
saveName :: NewGameState ()
saveName = do
memory <- fmap gamememory get
pushStack memory
getName = popStack
for saveName we fmap gamememory over the current state and store the result in memory than push that on the stack. We can actually write this as get >>= pushStack . gamememory if you want to be fancy.
popStack doesn't take any arguments so I'm not sure what you wanted there. My best guess is that it should just grab the last name we pushed on which just is a call to popStack.

NewGameState is a poor name - it isn't a new game state at all, it's a monad that carries around a state. I just called it Game.
pushStack vs push - You gave a signature named pushStack then a function named push. Pick one.
In popStack you have [] -> (0.0, st) Let's face it, 0.0 is not a string, so why are you trying to return it? Did you just not know what to do when popping an empty stack? How about you use "" instead?
saveName and getName Well you haven't even said what you want these to do. It seems you accepted other answerer's interpretations so going with that, we can just use record update syntax.
In the end, here is some code that at least compiles:
import Control.Monad.State
data GameState = GameState {
gamestack :: [String],
gamememory :: String
}
type Game = State GameState
popStack :: Game (Maybe String)
popStack = state $ \st -> case gamestack st of
[] -> (Nothing,st)
x:xs -> (Just x,st { gamestack = xs })
pushStack :: String -> Game ()
pushStack d = modify $ \st -> st { gamestack = d : gamestack st }
saveName :: Game ()
saveName = do
memory <- gamememory `fmap` get
pushStack memory
getName :: Game ()
getName = do
newMem <- popStack
case newMem of
Nothing -> return ()
Just n -> modify (\x -> x { gamememory = n } )

Related

How to change Tab-completed content at runtime in Haskeline?

I want to write a text interface, which provides some default commands. This program supports tab completion of those commands.
This program also records user inputs and stores it in StateData. And now I want this program to support tab completion of those user inputs. For example:
*Main > main
> read a<tab> -- press tab and no suggestions (read is a default command)
> read abcde
...
> read a<tab> -- press tab
abcde -- suggestions
Is it possible to do that without using unsafe mechanism like IORef? Is there a way to pass updated st from loop (in repl) to replSettings startState (in repl)?
I am new to Haskeline and thanks for your time.
repl :: StateData -> IO()
repl startState = runInputT (replSettings startState) $ loop startState
where
loop :: StateData -> InputT IO ()
loop st = do
inputL <- getInputLine "> "
case inputL of
Nothing -> return ()
Just "quit" -> outputStrLn "--Exited--" >> return ()
Just ipt -> do (opt, st') <- process ipt `runStateT` st
...
loop st'
replSettings :: StateData -> Settings IO
replSettings st =
Settings
{ complete = replCompletion st,
historyFile = Just "history.txt",
autoAddHistory = True
}
replCompletion :: StateData -> CompletionFunc IO
replCompletion st = completeWordWithPrev Nothing [' '] st (\x y -> return $ completionGenerator x y)
completionGenerator :: String -> String -> StateData -> [Completion]
completionGenerator "" c st =
commandSuggestion c (updatesSuggestions st) -- I wish to update it at run time
completionGenerator p c st = ...
IORef isn’t unsafe; you’re already in IO, so it’s a perfectly reasonable way to add mutable state here.
But if you want to avoid IO, you can simply use StateT StateData IO as the underlying monad for InputT, and thus the completion function in Settings. It seems you’re already trying to use StateT anyway. Here’s a complete example that just adds every entry to a list and autocompletes them naïvely:
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State (StateT, evalStateT, get, modify)
import Data.List (isPrefixOf)
import System.Console.Haskeline
type StateData = [String]
main :: IO ()
main = repl []
repl :: StateData -> IO ()
repl startState
= flip evalStateT startState
$ runInputT replSettings loop
where
loop :: InputT (StateT StateData IO) ()
loop = do
inputL <- getInputLine "> "
case inputL of
Nothing -> pure ()
Just "quit" -> outputStrLn "--Exited--"
Just ipt -> do
-- Just add each entry to the state directly.
lift $ modify (ipt :)
loop
replSettings :: Settings (StateT StateData IO)
replSettings = Settings
{ complete = replCompletion
, historyFile = Just "history.txt"
, autoAddHistory = True
}
replCompletion :: CompletionFunc (StateT StateData IO)
replCompletion = completeWordWithPrev Nothing " " completionGenerator
completionGenerator :: String -> String -> StateT StateData IO [Completion]
completionGenerator prefix suffix = do
st <- get
-- Trivial completion that just ignores the suffix.
pure $ fmap (\ s -> Completion s s True)
$ filter (prefix `isPrefixOf`) st
The completion generator could also be written using MonadState (from mtl) to insulate it from being able to access IO, and other code could likewise use this pure state while being agnostic to IO. But otherwise, since you’re already in IO in this code, StateT StateData IO / get / modify are no different than ReaderT (IORef StateData) IO / readIORef / modifyIORef.
In fact, if you put an IORef in StateData, supposing it’s a more complex record type in your code, the latter is a good way to make some parts of it mutable and others immutable.
data StateData = StateData
{ mutableThing :: !(IORef Thing)
, immutableStuff :: !Stuff
…
}

How to build a Monad with non-IO "exterior", but IO "interior"?

I'm trying to write a Monad which renders some HTML, while tracking (and caching) a few specific function calls. Here's what I tried:
data TemplateM a = TemplateM
{ templateCache :: ![(Text, Text)]
, templateResult :: !(IO a)
}
Here's how I plan to use this:
renderCached :: Text -> TemplateM Text
renderCached k =
-- lookup templateCache from the monadic context, if it lacks the key,
-- then fetch the key from an external data source (which is where the
-- "IO interior" comes from, and store it in templateCache (monadic context)
Notably, I do not want arbitrary IO actions to be executed in TemplateM via lift, liftIO, and suchlike. The only IO that should happen in TemplateM is to fetch something from the cache via the renderCached function.
I was able to define the Functor and Applicative instances for this, but got completely stuck with the Monad instance. Here's how far I got:
instance Functor TemplateM where
{-# INLINE fmap #-}
fmap fn tmpl = tmpl{templateResult=fmap fn (templateResult tmpl)}
instance Applicative TemplateM where
{-# INLINE pure #-}
pure x = TemplateM
{ templateCache = []
, templateResult = pure x
}
{-# INLINE (<*>) #-}
fn <*> f =
let fnCache = templateCache fn
fnFunction = templateResult fn
fCache = templateCache f
fResult = templateResult f
in TemplateM { templateCache = fnCache <> fCache
, templateResult = fnFunction <*> fResult
}
Is there any way to write the Monad instance for this without exposing the IO internals to the outside world?
I've worked out a solution sitting on top of ReaderT, but I really want to get my original idea to work:
newtype TemplateM a = TemplateM { unTemplateM :: ReaderT (IORef [(Text, Text)]) IO a } deriving (Functor, Applicative, Monad)
renderCached :: Text -> TemplateM Text
renderCached k = TemplateM $ do
-- this is just dummy code. The actual cache lookup has not
-- been implemented, but the types align
v <- pure $ "rendered template for " <> k
cacheRef <- ask
atomicModifyIORef' cacheRef (\x -> ((k, v):x, ()))
pure v
runTemplateM :: [(Text, Text)]
-> TemplateM a
-> IO ([(Text, Text)], a)
runTemplateM initialCache x = do
initialCacheRef <- newIORef initialCache
(flip runReaderT) initialCacheRef $ do
res <- unTemplateM x
ref <- ask
finalCache <- readIORef ref
pure (finalCache, res)
As others have suggested, the elementary solution here is to use StateT. Since you don't need to store your IORef in a data structure or share it between threads, you can eliminate it altogether. (Of course, if that changes and you do end up wanting to share state across multiple concurrent threads, you'll have to revisit this choice.)
import Control.Monad.State.Strict
import Data.Text (Text)
import Data.Tuple (swap)
newtype TemplateM a = TemplateM {unTemplateM :: StateT [(Text, Text)] IO a}
deriving (Functor, Applicative, Monad)
renderCached :: Text -> TemplateM Text
renderCached k = TemplateM $ do
v <- pure $ "rendered template for " <> k
modify ((k, v) :)
pure v
runTemplateM :: [(Text, Text)]
-> TemplateM a
-> IO ([(Text, Text)], a)
runTemplateM initialCache x = fmap swap $ flip runStateT initialCache (unTemplateM x)
It goes without saying that a cache like this should almost certainly be stored as a structure that is not a list. One promising option is to use text-trie, a data structure Wren Romano designed specially for this purpose. You might also consider a HashMap or even a Map.

Haskell Using monads as a sort of a global variable

I'm building a snake game and I'm using gloss graphics for the game.
I'm using G.play for initiation of the game:
main :: IO ()
main = do
rand <- R.randomIO
let world = startWorld rand
G.play
(displayMode world)
backgroundColor
stepRate
world
drawWorld
handleEvent
handleStep
Now the snake is basically a list of pairs of coordinates and the score is the length of the snake. However, I've added a feature of a special apple that gives you 2 points instead of 1, and only adds 1 length to the snake. But because the score is based on the snake's length I wanted to create a global variable that will count the number of times that the snake had eaten the special apple and will add that to the score. I searched the web and couldn't figure out how to actually use Monad.State to help me with this global variable.
You would use StateT if you would like to have access to both IO and State at the same time. State uses the exact same interface minus the extra parameter in the type constructor.
import Control.Monad.Trans.State
import Control.Monad.IO.Class
The game type is a State transformer applied to IO. This wraps State around the IO type allowing us to lift IO functions into the IO monad when required. Here s is our start state and a is our return state.
type Game s a = StateT s IO a
Game state is captured as a record type with the fields you want to update over time. This is where you store the snake, length, and other items in the global game state.
data GameState = GameState
{ _score :: Int
, _length :: Int
} deriving (Show)
To modify state we use the modify function from StateT which gets the state, applies a function over it, then sets the resulting state (modify fn = do s <- get; put (fn s))
set :: (GameState -> GameState) -> Game GameState ()
set field = modify field
score :: (Int -> Int) -> GameState -> GameState
score fn (GameState s l) = GameState (fn s) l
len :: (Int -> Int) -> GameState -> GameState
len fn (GameState s l) = GameState s (fn l)
To use IO we must lift the function to the IO monad using liftIO
display :: Show a => a -> Game GameState ()
display = liftIO . print
An example of this in use follows.
game :: Game GameState ()
game = do s <- gets _score
l <- gets _length
display "initial values"
display s
display l
set $ score (+2)
set $ len (+1)
s <- gets _score
l <- gets _length
display "modified values"
display s
display l
Where runStateT game (GameState 0 0) would print
"initial values"
0
0
"modified values"
2
1
((),GameState (_score = 2, _length = 1})
Which should fit your existing model with minor changes.

Generating random strings from a string-pool using QuickCheck

Consider the problem of generating strings out our a set of possible strings, in such a way that once a string is chosen, it cannot be repeated again. For this task I would like to use QuickCheck's Gen functions.
If I look at the type of the function I'm trying to write, it looks pretty much like a state monad. Since I'm using another monad, namely Gen , inside the state monad. I wrote my first attempt using StateT.
arbitraryStringS :: StateT GenState Gen String
arbitraryStringS =
mapStateT stringGenS get
where:
newtype GenState = St {getStrings :: [String]}
deriving (Show)
removeString :: String -> GenState -> GenState
removeString str (St xs) = St $ delete str xs
stringGenS :: Gen (a, GenState) -> Gen (String, GenState)
stringGenS genStSt =
genStSt >>= \(_, st) ->
elements (getStrings st) >>= \str ->
return (str, removeString str st)
Something that troubles me about this implementation is the fact that I'm not using the first element of stringGenS. Secondly, my end goal is to define a random generator for JSON values, that make use of a resource pool (which contains not only strings). Using StateT led me to implement "stateful" variants of QuickCheck's elements, listOf, etc.
I was wondering whether there's a better way of achieving this, or such a complexity is inherent to defining stateful variants of existing monads.
The combination of StateT and Gen could look like this:
import Control.Monad.State
import Data.List (delete)
import Test.QuickCheck
-- A more efficient solution would be to use Data.Set.
-- Even better, Data.Trie and ByteStrings:
-- https://hackage.haskell.org/package/bytestring-trie-0.2.4.1/docs/Data-Trie.html
newtype GenState = St { getStrings :: [String] }
deriving (Show)
removeString :: String -> GenState -> GenState
removeString str (St xs) = St $ delete str xs
stringGenS :: StateT GenState Gen String
stringGenS = do
s <- get
str <- lift $ elements (getStrings s)
modify $ removeString str
return str
The problem is that as you need the state, you can't run multiple such computations in Gen while sharing the state. The only reasonable thing to do would be to generate multiple random unique strings together (using the same state) as
evalStateT (replicateM 10 stringGenS)
which is of type GenState -> Gen [String].

How to pass a field constructor parameter to a function?

1) I need to pass a field constructor parameter to a function. I made some tests but i was unable to do so. Is it possible? Otherwise, is it possible with lens package?
2) Is it possible in a MonadState to modify a field using modify? (I made a few attempts, but without success. For example: modify (second = "x") does not work.
import Control.Monad.State
data Test = Test {first :: Int, second :: String} deriving Show
dataTest = Test {first = 1, second = ""}
test1 = runStateT modif1 dataTest -- OK
test2 = runStateT (modif2 "!") dataTest -- OK
test3 = runStateT (modif3 second) dataTest -- WRONG
-- modif1 :: StateT Test IO ()
modif1 = do
st <- get
r <- lift getLine
put $ st {second = "x" ++ r}
-- modif2 :: String -> StateT Test IO ()
modif2 s = do
stat <- get
r <- lift getLine
put $ stat {second = "x" ++ r ++ s}
-- modif3 :: ???? -> StateT Test IO ()
modif3 fc = do
stat <- get
r <- lift getLine
put $ stat {fc = "x" ++ r}
-- When i try to load the module, this is the result:
-- ghc > Failed:
-- ProvaRecord.hs:33:16:`fc' is not a (visible) constructor field name
As you said, you're probably looking for lenses. A lens is a value that allows to read, set or modify a given field. Usually with Control.Lens, you define fields with underscores and you use makeLenses to create full-featured lenses.
There are many combinators that allow lenses to be used together within MonadState. In your case we can use %=, which in this case would be specialized to type
(MonadState s m) => Lens' s b -> (b -> b) -> m ()
which modifies a state value using a given lens and a function that operates on the inside value.
Your example could be rewritten using lenses as follows:
{-# LANGUAGE TemplateHaskell, RankNTypes #-}
import Control.Lens
import Control.Monad.State
data Test = Test { _first :: Int
, _second :: String
}
deriving Show
-- Generate `first` and `second` lenses.
$(makeLenses ''Test)
-- | An example of a universal function that modifies any lens.
-- It reads a string and appends it to the existing value.
modif :: Lens' a String -> StateT a IO ()
modif l = do
r <- lift getLine
l %= (++ r)
dataTest :: Test
dataTest = Test { _first = 1, _second = "" }
test :: IO Test
test = execStateT (modif second) dataTest

Resources