Moving piece across a board in Haskell - haskell

I'm working on a chess game in Haskell and I'm struggling with moving my pieces.
I understand that in functional programming, everything should be immutable, but I think I really need to have an updated list of pieces. I looked at monad.state but I'm having a hard time understanding it.
This is my list of pieces :
piecesList::[Piece]
piecesList = [Piece _type _color _coords, ..., ... Piece _type _color _coords]
And my approach for moving a piece from (old_x,old_y) to (new_x,new_y):
find the piece with (old_x,old_y) as coordinates in my list:
piece = getPiece (index_of (old_x old_y))
with
getPiece::Int->Piece
getPiece a = piecesList!!a
and
index_of :: (Int,Int)->Int
index_of (old_x, old_y) = fromJust $ findIndex piece piecesList
where
piece (Piece _ _ pos) = pos == (old_x, old_y)
update the coordinates of this particular piece:
moved = move (piece (new_x,new_y))
with
move::Piece->(Int,Int)->Piece
move piece (new_x,new_y) = piece { _position = (new_x,new_y) }
update the list of pieces with:
piecesList = updateBoard (index_of a b ) moved
with
updateBoard :: Int -> Piece -> Maybe [Piece]
updateBoard index newPiece = return board
where
(x,_:ys) = splitAt index piecesList
board = x ++ newPiece : ys
But still, it looks like my list of pieces is not updated.
Am I close to it? If so, what am I missing? Or is my approach completely wrong?
Thanks!
Edit
I'm using the following types:
data Piece = Piece {
_type :: PieceType,
_color :: PieceColor,
_position :: Position
} deriving Eq
data PieceColor = Black | White deriving Eq
data PieceType = Rook | Knight | Bishop | King | Queen | Pawn deriving Eq
type Position = (Int, Int)

it looks like my list of pieces is not updated.
Of course not: like everything in Haskell, the list of pieces is immutable, so it will never change under any circumstances.
With
piecesList = updateBoard (index_of a b ) moved
you merely define a new list of pieces, which also happens to be called pieces. GHCi and IHaskell allow this kind of shadowing (Haskell itself does not!), but it simply means that anything you define afterwards which refers to piecesList will use the new version. But getPiece and index_of already have already been defined before this “update”, and are completely oblivious to any new definitions you choose to come up with later on.
The most directly way to accomplish a task like this is to explicitly pass a modified version of the game state around. In fact updateBoard already goes that direction by giving an entire [Piece] list as the result. But you also need to use that updated state in the next step, rather than again the start state piecesList. Basically, if you just pass pieces as an argument to getPiece, index_of and updateBoard, you'll get the task done.
updateBoard :: Int -> Piece -> [Piece] -> [Piece] -- You don't seem to need `Maybe`
Note that this signature is parsed as
updateBoard :: Int -> Piece -> ([Piece] -> [Piece])
Now, it's a bit awkward, having to explicitly give the same old value to all kinds of helper functions. You already mention the state monad, which is indeed the standard thing to use here. Essentially, the state monad does the exact same thing: passing a value around as an argument to sub-functions. The only difference is that, if not told otherwise, it automatically uses always the same value.
You change the signature to
import Control.Monad.State
updateBoard :: Int -> Piece -> State [Piece] ()
Here, State [Piece] () is just a newtype wrapper for [Piece] -> ([Piece], ()). The () says that you don't give any interesting result information apart from the updated state. You could give other information too, and indeed need to in getPieces and indexOf:
getPiece :: Int -> State [Piece] Piece
indexOf :: (Int,Int) -> State [Piece] Int
Now as to how everything is actually written: do notation helps. Simply put the result in a return at the end, and obtain the old state with get. For example,
getPiece :: Int -> State [Piece] Piece
getPiece a = do
piecesList <- get
return $ piecesList!!a
The new state can simply be “put into the monad”:
updateBoard :: Int -> Piece -> State [Piece] ()
updateBoard index newPiece = do
piecesList <- get
let (x,_:ys) = splitAt index piecesList
put $ x ++ newPiece : ys

Related

Implementing a simple greedy ai for reversi/othello

Quick disclaimer that this is for a homework task so rather than me placing any code I wanted to get conceptual help from you guys, maybe examples to help me understand. Essentially we have to implement an ai for reversi/othello and while minmax is the final goal, I wanted to start with a greedy algorithm.
Ok so the relevant definitions/functions:
GameState - this variable holds the boundaries of the board, who's turn it is, and the board (with a list of Maybe Player where Nothing means the tile is empty and Maybe Player1 or Player2 which means a piece is present for a player.
legalMoves - returns a list of all possible legal moves when given a GameState. Here a move is defined as a position (x,y)
applyMove - finally we have applyMove which takes a GameState and a move and returns a new Maybe GameState based on the new board after that move was played.
The final goal here is to create a function that when given a GameState, returns the best move
What I've done:
Firstly, I've created an evaluation function which returns the eval of any GameState
(eval :: GameState -> Int). So a heuristic.
From here I've had trouble. What I've tried to do is map the applyMove func to legalMoves to return a list of all possible future GameStates given a GameState. Then I mapped my eval func to the list of GameStates to get a list of Int's then I finally took the maximum of this list to get the best evaluation.
The problem is I'm not sure how to go back to the actual move from legalMoves that gave me that evaluation.
Your current pipeline looks like this:
GameState -> (GameState, [Move]) -> [GameState] -> [Int] -> Int
Make it look like this instead:
GameState -> (GameState, [Move]) -> [(Move, GameState)] -> [(Move, Int)] -> (Move, Int)
In other words: track the association between moves and function return values through the whole pipeline. Then it is easy to extract the Move at the end.
May I suggest a 10-liners with a MiniMax strategy: https://github.com/haskell-game/tiny-games-hs/blob/main/prelude/mini-othello/mini-othello.hs
The key is to use the trial play function:
-- | Trial play
(%) :: GameState -> Coordinate -> (GameState, Int)
(%) inGameState -> cor -> (outGameState, nFlips)
To create different game strategy function e:
-- | Strategy function!
e :: GameState -> GameState
This generates a sequence of [(nFlips, (x,y)), ...]
((,)=<<snd.(a%))&k r
-- | Naive strategy
e a=q a.snd.head.f((>0).fst).m((,)=<<snd.(a%)$k r
-------------------------------------------------
-- | Greedy strategy
e a=q a.snd.f(\c#(w,_)e#(d,_)->d>w?e$c)(0,(0,0)).m((,)=<<snd.(a%))$k r
-----------------------------------------------------------------------
-- | MiniMax strategy
i=fst;j=snd;
g h a=f(\c e->i e>i c?e$c)(-65*h,(0,0))$
(\((b,p),d)->(h*(h*p==0?j a`c`i b$i$g(div h(-2))b),d))&
(((,)=<<(a%))&k r);
e a=q a.j$g 4a
Because is a code golfing exercise, many symbols are involved here:
? a b c -- if' operator
& = map

How should I organize normal and "state" versions of functions in the state monad?

I decided to try the State Monad to try and clean up some of the projects that I've started. I ran into a naming/compartmentalization problem.
If I have the following objects:
data Obj = Player { oPos :: Point }
data World = World { wKeys :: [Key], wPlayer :: Obj }
I might have a convenience function like:
setPlayer :: Obj -> World -> World
setPlayer o w = w{wPlayer = o}
and a matching state operation like:
setPlayerW :: Obj -> WorldState ()
setPlayerW o = get >>= put . setPlayer o
which uses the other convenience function; for convenience.
What is the typical naming convention for something like this? I post-pended the state version with a W, but that's kind of ugly.
And are the "state-versions" typical segregated from the "object-versions" in a separate file?
Am I going about this wrong completely? Is there a better set-up then having 2 different versions of any operations I might need?
Personally, I wouldn't have a separate function for the state version myself. Instead, use the modify function instead:
do let o = player
modify (setPlayer o)
something else
In a sense, the naming convention you're looking for would just be the same as using modify except folded into the names of each function. When I find myself naming functions like this, I generally try to find some way to organize them in the language instead of using their names. Sometimes, like here, an existing function is all you need; other times, it involves creating a function of your own to achieve the same end or extracting things into a module.
The core idea is that it's better to reify patterns in your code using first-class language constructs instead of encoding them indirectly into the names. (Of course, if this ends up really awkward, you shouldn't do it, but it's fine here.)
This looks like a good time to introduce the lens library. This is a bit of a daunting library at first, and I still struggle with some of its more complex features (the rabbit hole is pretty deep for this one), but it can really simplify a lot of your State code. To use it, it's recommended to change your data types a bit first so you can utilize template haskell:
import Control.Monad
import Control.Monad.State
import Control.Lens
-- Made assumption on what Point would look like
data Point = Point { _x :: Int, _y :: Int } deriving (Eq, Show)
data Obj = Player { _oPos :: Point } deriving (Eq, Show)
data World = World { _wKeys :: [Key], _wPlayer :: Obj } deriving (Eq, Show)
makeLenses ''Point
makeLenses ''Obj
makeLenses ''World
-- Also assumed this type
type WorldState = StateT World IO
Then you can write code that looks very much imperative using the generated lenses
setPlayerW :: Obj -> WorldState ()
setPlayerW o = wPlayer .= o
Or if you want the non-monadic version
setPlayer :: Obj -> World -> World
setPlayer o = wPlayer .~ o
So this uses the .= operator to set the wPlayer field of the World state to the new value. More impressively, you could use it to write code like
moveUp, moveDown, moveLeft, moveRight :: WorldState ()
moveUp = wPlayer.oPos.y += 1
moveDown = wPlayer.oPos.y -= 1
moveLeft = wPlayer.oPos.x -= 1
moveRight = wPlayer.oPos.x += 1
Which makes it look a lot like an object oriented language using normal function composition. A quick test:
game :: WorldState ()
game = do
replicateM_ 3 moveUp
replicateM_ 5 moveLeft
replicateM_ 10 moveRight
replicateM_ 6 moveDown
> execStateT game $ World [] $ Player $ Point 0 0
World {_wKeys = [], _wPlayer = Player {_oPos = Point {_x = 5, _y = -3}}}
There are a lot of really interesting and useful operators in the lens library, and there's a lot of support built-in for using it with StateT stacks.
Another nice feature is the zoom function, which takes a lens and "zooms in" on it, letting you operate as if your state has the value of whatever you zoomed onto. An example would be
game = zoom (wPlayer.oPos) $ do
y += 3
x -= 5
x += 10
y -= 6
And this would produce the same result as before. This is generally more efficient (fewer layers to unwrap at each step) and can be much cleaner.

(A simple way) to make calling a function with a certain value is a compile-time error?

I think it's not possible (or requires certain language extensions) to make a function like
f :: Maybe Int
f (Just n) = n
f Nothing = ... -- a compile-time error
There's also no way you can make a function like:
g :: MyClass a => Int -> a
g n | n < 10 = TypeClassInstance
| otherwise = OtherTypeClassInstance
So, I'm working on this tic-tac-toe API from the famous NICTA FP course that is required to do things like:
takeBack: takes either a finished board or a board in-play that has had at least one move and returns a board in-play. It is a compile-time type error to call this function on an empty board.
I think it's possible to do some really fancy type-level programming. But even if it is then I don't think someone who has just taken a 2-day introduction to functional programming could know it. Or did I miss something?
Update
Based the example given by #user2407038 and clarification from #Cirdec, I write this and it does make a compile-time error when you try to takeBack on an empty board which is great.
However -- moving the goal posts a little -- this trick seems limited. There's another requirement that you can't move on a game that's already over.
move: takes a tic-tac-toe board and position and moves to that position (if not occupied) returning a new board. This function can only be called on a board that is empty or in-play. Calling move on a game board that is finished is a compile-time type error.
It doesn't seem like a simple trick of having the type count the moves can be used in the case of complicated logic to determine whether the game is over.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
data N = S N | Z
data Stat
= Empty
| InPlay
| Won
deriving Show
data Board (n :: N)
= Board Stat [Int]
deriving Show
newBoard :: Board Z
newBoard = Board Empty []
move :: Int -> Board a -> Board (S a)
move x (Board Empty []) = Board InPlay [x]
move x (Board InPlay xs) = Board Won (x:xs)
takeBack :: Board (S a) -> Board a
takeBack (Board InPlay [x]) = Board Empty []
takeBack (Board InPlay (x:xs)) = Board InPlay xs
takeBack (Board Won (x:xs)) = Board InPlay xs
main :: IO ()
main = do
let
brd = newBoard -- Empty
m1 = move 1 brd -- InPlay
m2 = move 2 m1 -- Won
m3 = move 3 m2 -- Can't make this a compile-time error with this trick
tb2 = takeBack m2 -- Won
tb1 = takeBack tb2 -- InPlay
tb0 = takeBack tb1 -- Empty -> Compile-time error Yay!
return ()
You can do something like your first example with a GADT (generalized algebraic datatype);
data SMaybe (a :: Maybe *) where
SJust :: a -> SMaybe (Just a)
SNothing :: SMaybe Nothing
f :: SMaybe (Just a) -> a
f (SJust a) = a
-- f SNothing = undefined -- Including this case is a compile time error
Although I doubt this has much use. The simplest solution to the board thing is probably have a phantom type parameter on your Board datatype:
type Empty = False
type NonEmpty = True
data Board (b :: Bool) = Board ...
newBoard :: Board Empty
newBoard = Board ...
setAt :: (Int, Int) -> Bool -> Board a -> Board NonEmpty
setAt p b (Board ...) = ...
takeBack :: Board NonEmpty -> Board NonEmpty
takeBack (Board ...) = ...
You can increase the amount of information stored on the type level if you like. For example, you can have the number of filled "cells":
data N = S N | Z -- The naturals
data Board (n :: N) = Board ...
newBoard :: Board Z
newBoard = Board ...
setAt :: (Int, Int) -> Bool -> Board a -> Board (S a)
setAt = ...
takeBack :: Board (S n) -> Board (S n)
takeBack = ...
The examples above use DataKinds for convenience, but it isn't needed.
One easy way to accomplish something like this without invoking any type-level programming is a smart constructor. To make a smart constructor, you don't export the real constructor for a data type and instead provide a function that only creates values of the type that meet your other rules.
We can tackle the example problem by making smart constructors that represent a proof that a board is Playable, Finished, or NonEmpty.
type Position = (Int, Int)
type Player = Bool
data Board = Board -- ...
deriving (Eq, Show, Read, Ord)
newtype Playable = Playable {getPlayable :: Board}
deriving (Eq, Ord, Show)
newtype Finished = Finished {getFinished :: Board}
deriving (Eq, Ord, Show)
newtype NonEmpty = NonEmpty {getNonEmpty :: Board}
deriving (Eq, Ord, Show)
We are careful not to provide instances that could create any of these types; for example, we didn't derive Read instances for them. The only exported functions that will create these will first check the necessary conditions.
playable :: Board -> Maybe Playable
playable = undefined
finished :: Board -> Maybe Finished
finished = undefined
nonEmpty :: Board -> Maybe NonEmpty
nonEmpty = undefined
When we export the types from the module, we won't export their constructors
module TicTacToe (
Playable (getPlayable),
Finished (getFinished),
NonEmpty (getNonEmpty),
playable,
finished,
nonEmpty,
Position,
Player,
Board (..),
move,
whoWon,
takeBack,
playerAt
) where
The remaining functions can require that the client code has already gotten a type-level proof of the necessary property before invoking the function.
move :: Position -> Playable -> Board
move = undefined
whoWon :: Finished -> Player
whoWon = undefined
takeBack :: NonEmpty -> Board
takeBack = undefined
For this example problem, the smart constructors accomplished absolutely nothing. Any library user is going to define helper functions so that they only have to concern themselves with Maybe and not with any of these other special Board types.
move' :: Position -> Board -> Maybe Board
move' p = fmap (move p) . playable
whoWon' :: Board -> Maybe Player
whoWon' = fmap whoWon . finished
takeBack' :: Board -> Maybe Board
takeBack' = fmap takeBack . nonEmpty
This suggests that using Maybe in the interface is sufficient, and the requirements for compile-time errors in the exercise are superfluous. This also falls in line with the following requested function, which doesn't require a type-level proof that someone has moved in that position before being used.
playerAt :: Position -> Board -> Maybe Player
playerAt = undefined
Using type-level proofs of properties is more advantageous when there are many transformations for which those properties are invariant or can be easily deduced.

Haskell data serialization of some data implementing a common type class

Let's start with the following
data A = A String deriving Show
data B = B String deriving Show
class X a where
spooge :: a -> Q
[ Some implementations of X for A and B ]
Now let's say we have custom implementations of show and read, named show' and read' respectively which utilize Show as a serialization mechanism. I want show' and read' to have types
show' :: X a => a -> String
read' :: X a => String -> a
So I can do things like
f :: String -> [Q]
f d = map (\x -> spooge $ read' x) d
Where data could have been
[show' (A "foo"), show' (B "bar")]
In summary, I wanna serialize stuff of various types which share a common typeclass so I can call their separate implementations on the deserialized stuff automatically.
Now, I realize you could write some template haskell which would generate a wrapper type, like
data XWrap = AWrap A | BWrap B deriving (Show)
and serialize the wrapped type which would guarantee that the type info would be stored with it, and that we'd be able to get ourselves back at least an XWrap... but is there a better way using haskell ninja-ery?
EDIT
Okay I need to be more application specific. This is an API. Users will define their As, and Bs and fs as they see fit. I don't ever want them hacking through the rest of the code updating their XWraps, or switches or anything. The most i'm willing to compromise is one list somewhere of all the A, B, etc. in some format. Why?
Here's the application. A is "Download a file from an FTP server." B is "convert from flac to mp3". A contains username, password, port, etc. information. B contains file path information. There could be MANY As and Bs. Hundreds. As many as people are willing to compile into the program. Two was just an example. A and B are Xs, and Xs shall be called "Tickets." Q is IO (). Spooge is runTicket. I want to read the tickets off into their relevant data types and then write generic code that will runTicket on the stuff read' from the stuff on disk. At some point I have to jam type information into the serialized data.
I'd first like to stress for all our happy listeners out there that XWrap is a very good way, and a lot of the time you can write one yourself faster than writing it using Template Haskell.
You say you can get back "at least an XWrap", as if that meant you couldn't recover the types A and B from XWrap or you couldn't use your typeclass on them. Not true! You can even define
separateAB :: [XWrap] -> ([A],[B])
If you didn't want them mixed together, you should serialise them seperately!
This is nicer than haskell ninja-ery; maybe you don't need to handle arbitrary instances, maybe just the ones you made.
Do you really need your original types back? If you feel like using existential types because you just want to spooge your deserialised data, why not either serialise the Q itself, or have some intermediate data type PoisedToSpooge that you serialise, which can deserialise to give you all the data you need for a really good spooging. Why not make it an instance of X too?
You could add a method to your X class that converts to PoisedToSpooge.
You could call it something fun like toPoisedToSpooge, which trips nicely off the tongue, don't you think? :)
Anyway this would remove your typesystem complexity at the same time as resolving the annoying ambiguous type in
f d = map (\x -> spooge $ read' x) d -- oops, the type of read' x depends on the String
You can replace read' with
stringToPoisedToSpoogeToDeserialise :: String -> PoisedToSpooge -- use to deserialise
and define
f d = map (\x -> spooge $ stringToPoisedToSpoogeToDeserialise x) -- no ambiguous type
which we could of course write more succincly as
f = map (spooge.stringToPoisedToSpoogeToDeserialise)
although I recognise the irony here in suggesting making your code more succinct. :)
If what you really want is a heterogeneous list then use existential types. If you want serialization then use Cereal + ByteString. If you want dynamic typing, which is what I think your actual goal is, then use Data.Dynamic. If none of this is what you want, or you want me to expand please press the pound key.
Based on your edit, I don't see any reason a list of thunks won't work. In what way does IO () fail to represent both the operations of "Download a file from an FTP server" and "convert from flac to MP3"?
I'll assume you want to do more things with deserialised Tickets
than run them, because if not you may as well ask the user to supply a bunch of String -> IO()
or similar, nothing clever needed at all.
If so, hooray! It's not often I feel it's appropriate to recommend advanced language features like this.
class Ticketable a where
show' :: a -> String
read' :: String -> Maybe a
runTicket :: a -> IO ()
-- other useful things to do with tickets
This all hinges on the type of read'. read' :: Ticket a => String -> a isn't very useful,
because the only thing it can do with invalid data is crash.
If we change the type to read' :: Ticket a => String -> Maybe a this can allow us to read from disk and
try all the possibilities or fail altogether.
(Alternatively you could use a parser: parse :: Ticket a => String -> Maybe (a,String).)
Let's use a GADT to give us ExistentialQuantification without the syntax and with nicer error messages:
{-# LANGUAGE GADTs #-}
data Ticket where
MkTicket :: Ticketable a => a -> Ticket
showT :: Ticket -> String
showT (MkTicket a) = show' a
runT :: Ticket -> IO()
runT (MkTicket a) = runTicket a
Notice how the MkTicket contstuctor supplies the context Ticketable a for free! GADTs are great.
It would be nice to make Ticket and instance of Ticketable, but that won't work, because there would be
an ambiguous type a hidden in it. Let's take functions that read Ticketable types and make them read
Tickets.
ticketize :: Ticketable a => (String -> Maybe a) -> (String -> Maybe Ticket)
ticketize = ((.).fmap) MkTicket -- a little pointfree fun
You could use some unusual sentinel string such as
"\n-+-+-+-+-+-Ticket-+-+-+-Border-+-+-+-+-+-+-+-\n" to separate your serialised data or better, use separate files
altogether. For this example, I'll just use "\n" as the separator.
readTickets :: [String -> Maybe Ticket] -> String -> [Maybe Ticket]
readTickets readers xs = map (foldr orelse (const Nothing) readers) (lines xs)
orelse :: (a -> Maybe b) -> (a -> Maybe b) -> (a -> Maybe b)
(f `orelse` g) x = case f x of
Nothing -> g x
just_y -> just_y
Now let's get rid of the Justs and ignore the Nothings:
runAll :: [String -> Maybe Ticket] -> String -> IO ()
runAll ps xs = mapM_ runT . catMaybes $ readTickets ps xs
Let's make a trivial ticket that just prints the contents of some directory
newtype Dir = Dir {unDir :: FilePath} deriving Show
readDir xs = let (front,back) = splitAt 4 xs in
if front == "dir:" then Just $ Dir back else Nothing
instance Ticketable Dir where
show' (Dir p) = "dir:"++show p
read' = readDir
runTicket (Dir p) = doesDirectoryExist p >>= flip when
(getDirectoryContents >=> mapM_ putStrLn $ p)
and an even more trivial ticket
data HelloWorld = HelloWorld deriving Show
readHW "HelloWorld" = Just HelloWorld
readHW _ = Nothing
instance Ticketable HelloWorld where
show' HelloWorld = "HelloWorld"
read' = readHW
runTicket HelloWorld = putStrLn "Hello World!"
and then put it all together:
myreaders = [ticketize readDir,ticketize readHW]
main = runAll myreaders $ unlines ["HelloWorld",".","HelloWorld","..",",HelloWorld"]
Just use Either. Your users don't even have to wrap it themselves. You have your deserializer wrap it in the Either for you. I don't know exactly what your serialization protocol is, but I assume that you have some way to detect which kind of request, and the following example assumes the first byte distinguishes the two requests:
deserializeRequest :: IO (Either A B)
deserializeRequest = do
byte <- get1stByte
case byte of
0 -> do
...
return $ Left $ A <A's fields>
1 -> do
...
return $ Right $ B <B's fields>
Then you don't even need to type-class spooge. Just make it a function of Either A B:
spooge :: Either A B -> Q

State Monad, sequences of random numbers and monadic code

I'm trying to grasp the State Monad and with this purpose I wanted to write a monadic code that would generate a sequence of random numbers using a Linear Congruential Generator (probably not good, but my intention is just to learn the State Monad, not build a good RNG library).
The generator is just this (I want to generate a sequence of Bools for simplicity):
type Seed = Int
random :: Seed -> (Bool, Seed)
random seed = let (a, c, m) = (1664525, 1013904223, 2^32) -- some params for the LCG
seed' = (a*seed + c) `mod` m
in (even seed', seed') -- return True/False if seed' is even/odd
Don't worry about the numbers, this is just an update rule for the seed that (according to Numerical Recipes) should generate a pseudo-random sequence of Ints. Now, if I want to generate random numbers sequentially I'd do:
rand3Bools :: Seed -> ([Bool], Seed)
rand3Bools seed0 = let (b1, seed1) = random seed0
(b2, seed2) = random seed1
(b3, seed3) = random seed2
in ([b1,b2,b3], seed3)
Ok, so I could avoid this boilerplate by using a State Monad:
import Control.Monad.State
data Random {seed :: Seed, value :: Bool}
nextVal = do
Random seed val <- get
let seed' = updateSeed seed
val' = even seed'
put (Random seed' val')
return val'
updateSeed seed = let (a,b,m) = (1664525, 1013904223, 2^32) in (a*seed + c) `mod` m
And finally:
getNRandSt n = replicateM n nextVal
getNRand :: Int -> Seed -> [Bool]
getNRand n seed = evalState (getNRandStates n) (Random seed True)
Ok, this works fine and give me a list of n pseudo-random Bools for each given seed. But...
I can read what I've done (mainly based on this example: http://www.haskell.org/pipermail/beginners/2008-September/000275.html ) and replicate it to do other things. But I don't think I can understand what's really happening behind the do-notation and monadic functions (like replicateM).
Can anyone help me with some of this doubts?
1 - I've tried to desugar the nextVal function to understand what it does, but I couldn't. I can guess it extracts the current state, updates it and then pass the state ahead to the next computation, but this is just based on reading this do-sugar as if it was english.
How do I really desugar this function to the original >>= and return functions step-by-step?
2 - I couldn't grasp what exactly the put and get functions do. I can guess that they "pack" and "unpack" the state. But the mechanics behind the do-sugar is still elusive to me.
Well, any other general remarks about this code are very welcome. I sometimes fell with Haskell that I can create a code that works and do what I expect it to do, but I can't "follow the evaluation" as I'm accustomed to do with imperative programs.
The State monad does look kind of confusing at first; let's do as Norman Ramsey suggested, and walk through how to implement from scratch. Warning, this is pretty lengthy!
First, State has two type parameters: the type of the contained state data and the type of the final result of the computation. We'll use stateData and result respectively as type variables for them here. This makes sense if you think about it; the defining characteristic of a State-based computation is that it modifies a state while producing an output.
Less obvious is that the type constructor takes a function from a state to a modified state and result, like so:
newtype State stateData result = State (stateData -> (result, stateData))
So while the monad is called "State", the actual value wrapped by the the monad is that of a State-based computation, not the actual value of the contained state.
Keeping that in mind, we shouldn't be surprised to find that the function runState used to execute a computation in the State monad is actually nothing more than an accessor for the wrapped function itself, and could be defined like this:
runState (State f) = f
So what does it mean when you define a function that returns a State value? Let's ignore for a moment the fact that State is a monad, and just look at the underlying types. First, consider this function (which doesn't actually do anything with the state):
len2State :: String -> State Int Bool
len2State s = return ((length s) == 2)
If you look at the definition of State, we can see that here the stateData type is Int, and the result type is Bool, so the function wrapped by the data constructor must have the type Int -> (Bool, Int). Now, imagine a State-less version of len2State--obviously, it would have type String -> Bool. So how would you go about converting such a function into one returning a value that fits into a State wrapper?
Well, obviously, the converted function will need to take a second parameter, an Int representing the state value. It also needs to return a state value, another Int. Since we're not actually doing anything with the state in this function, let's just do the obvious thing--pass that int right on through. Here's a State-shaped function, defined in terms of the State-less version:
len2 :: String -> Bool
len2 s = ((length s) == 2)
len2State :: String -> (Int -> (Bool, Int))
len2State s i = (len2' s, i)
But that's kind of silly and redundant. Let's generalize the conversion so that we can pass in the result value, and turn anything into a State-like function.
convert :: Bool -> (Int -> (Bool, Int))
convert r d = (r, d)
len2 s = ((length s) == 2)
len2State :: String -> (Int -> (Bool, Int))
len2State s = convert (len2 s)
What if we want a function that changes the state? Obviously we can't build one with convert, since we wrote that to pass the state through. Let's keep it simple, and write a function to overwrite the state with a new value. What kind of type would it need? It'll need an Int for the new state value, and of course will have to return a function stateData -> (result, stateData), because that's what our State wrapper needs. Overwriting the state value doesn't really have a sensible result value outside the State computation, so our result here will just be (), the zero-element tuple that represents "no value" in Haskell.
overwriteState :: Int -> (Int -> ((), Int))
overwriteState newState _ = ((), newState)
That was easy! Now, let's actually do something with that state data. Let's rewrite len2State from above into something more sensible: we'll compare the string length to the current state value.
lenState :: String -> (Int -> (Bool, Int))
lenState s i = ((length s) == i, i)
Can we generalize this into a converter and a State-less function, like we did before? Not quite as easily. Our len function will need to take the state as an argument, but we don't want it to "know about" state. Awkward, indeed. However, we can write a quick helper function that handles everything for us: we'll give it a function that needs to use the state value, and it'll pass the value in and then package everything back up into a State-shaped function leaving len none the wiser.
useState :: (Int -> Bool) -> Int -> (Bool, Int)
useState f d = (f d, d)
len :: String -> Int -> Bool
len s i = (length s) == i
lenState :: String -> (Int -> (Bool, Int))
lenState s = useState (len s)
Now, the tricky part--what if we want to string these functions together? Let's say we want to use lenState on a string, then double the state value if the result is false, then check the string again, and finally return true if either check did. We have all the parts we need for this task, but writing it all out would be a pain. Can we make a function that automatically chains together two functions that each return State-like functions? Sure thing! We just need to make sure it takes as arguments two things: the State function returned by the first function, and a function that takes the prior function's result type as an argument. Let's see how it turns out:
chainStates :: (Int -> (result1, Int)) -> (result1 -> (Int -> (result2, Int))) -> (Int -> (result2, Int))
chainStates prev f d = let (r, d') = prev d
in f r d'
All this is doing is applying the first state function to some state data, then applying the second function to the result and the modified state data. Simple, right?
Now, the interesting part: Between chainStates and convert, we should almost be able to turn any combination of State-less functions into a State-enabled function! The only thing we need now is a replacement for useState that returns the state data as its result, so that chainStates can pass it along to the functions that don't know anything about the trick we're pulling on them. Also, we'll use lambdas to accept the result from the previous functions and give them temporary names. Okay, let's make this happen:
extractState :: Int -> (Int, Int)
extractState d = (d, d)
chained :: String -> (Int -> (Bool, Int))
chained str = chainStates extractState $ \state1 ->
let check1 = (len str state1) in
chainStates (overwriteState (
if check1
then state1
else state1 * 2)) $ \ _ ->
chainStates extractState $ \state2 ->
let check2 = (len str state2) in
convert (check1 || check2)
And try it out:
> chained "abcd" 2
(True, 4)
> chained "abcd" 3
(False, 6)
> chained "abcd" 4
(True, 4)
> chained "abcdef" 5
(False, 10)
Of course, we can't forget that State is actually a monad that wraps the State-like functions and keeps us away from them, so none of our nifty functions that we've built will help us with the real thing. Or will they? In a shocking twist, it turns out that the real State monad provides all the same functions, under different names:
runState (State s) = s
return r = State (convert r)
(>>=) s f = State (\d -> let (r, d') = (runState s) d in
runState (f r) d')
get = State extractState
put d = State (overwriteState d)
Note that >>= is almost identical to chainStates, but there was no good way to define it using chainStates. So, to wrap things up, we can rewrite the final example using the real State:
chained str = get >>= \state1 ->
let check1 = (len str state1) in
put (if check1
then state1 else state1 * 2) >>= \ _ ->
get >>= \state2 ->
let check2 = (len str state2) in
return (check1 || check2)
Or, all candied up with the equivalent do notation:
chained str = do
state1 <- get
let check1 = len str state1
_ <- put (if check1 then state1 else state1 * 2)
state2 <- get
let check2 = (len str state2)
return (check1 || check2)
First of all, your example is overly complicated because it doesn't need to store the val in the state monad; only the seed is the persistent state. Second, I think you will have better luck if instead of using the standard state monad, you re-implement all of the state monad and its operations yourself, with their types. I think you will learn more this way. Here are a couple of declarations to get you started:
data MyState s a = MyState (s -> (s, b))
get :: Mystate s s
put :: s -> Mystate s ()
Then you can write your own connectives:
unit :: a -> Mystate s a
bind :: Mystate s a -> (a -> Mystate s b) -> Mystate s b
Finally
data Seed = Seed Int
nextVal :: Mystate Seed Bool
As for your trouble desugaring, the do notation you are using is pretty sophisticated.
But desugaring is a line-at-a-time mechanical procedure. As near as I can make out, your code should desugar like this (going back to your original types and code, which I disagree with):
nextVal = get >>= \ Random seed val ->
let seed' = updateSeed seed
val' = even seed'
in put (Random seed' val') >>= \ _ -> return val'
In order to make the nesting structure a bit clearer, I've taken major liberties with the indentation.
You've got a couple great responses. What I do when working with the State monad is in my mind replace State s a with s -> (s,a) (after all, that's really what it is).
You then get a type for bind that looks like:
(>>=) :: (s -> (s,a)) ->
(a -> s -> (s,b)) ->
(s -> (s,b))
and you see that bind is just a specialized kind of function composition operator, like (.)
I wrote a blog/tutorial on the state monad here. It's probably not particularly good, but helped me grok things a little better by writing it.

Resources