Repeatedly applying function to game board in Haskell - 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.

Related

IO in Haskell not visible

I have a little interactive game program. The interactive part looks like this,
main :: IO ()
main = playGame newGame
where
playGame :: Game -> IO ()
playGame game =
do putStr $ show game
putStr $ if gameOver game then "Another game? (y or n) > "
else show (whoseMove game) ++ " to play (row col) > "
moveWords <- fmap (words . fmap cleanChar ) getLine
if stopGame game moveWords
then return ()
else playGame $ if gameOver game then newGame else makeMove game moveWords
This works fine. It displays the game state, asks for the next move, applies that move to the state, displays the new state, etc.
Then I saw a video by Moss Collum in which he showed a game that uses the following strategy for interacting with the user.
...
userInput <- getContents
foldM_ updateScreen (12, 40) (parseInput userInput) where
...
I couldn't find a reference to foldM_ but assuming it was some sort of fold I tried this. (I actually tried a number of things, but this seems clearest.)
main' :: IO ()
main' = do
moveList <- fmap (map words . lines . map cleanChar) getContents
let states = scanl makeMove newGame moveList
foldl (\_ state -> putStr . show $ state) (return ()) states
When I run it, I never get the game state printed out until after hitting end-of-file, at which point the correct final game state is printed. Before that, I can enter moves, and they are processed properly (according to the final game state), but I never see the intermediate states. (The idea is that lazy evaluation should print the game states as they become available.)
I'd appreciate help understanding why I don't see the intermediate states and what, if anything, I can do to fix it.
Also, after entering end-of-file (^Z on Windows) the program refuses to play again, saying that the handle has been closed. To play again I have to restart the program. Is there a way to fix that?
First, let's start with foldM:
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
a is the type of things in our container, and b is our result type. It takes a b (the value we've accumulated so far in our fold, ana(then ext thing in the list, and returns an m b, meaning it returns a b and does some monadic actions in the monad m.
Then it takes an initial value, a container of a's, and it returns an
This is basically like a normal fold function, but each step of the fold is monadic, and the final result is monadic. So the actions will actually be performed if you use foldM.
Now let's look at foldM_:
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
Source
This is the same, but the final result is m (). This is for the case where we don't care about the final result. We keep the intermediate results and use them to perform monadic actions at each step, but when we finish, we only care about what we did in the monad, so we throw away the result.
In your case, t would be List, and m would be IO. So foldM_ iterates through the list, doing the selected IO actions at each stage, then throws away the final result.
fold doesn't actually sequence the actions together, it just folds over your list normally, even if your final result is IO. So your foldl creates an IO action, namely putStr . show $ state, then passes it to the next step of the fold. But, you ignore the first argument of your fold, so it throws the IO away without ever doing anything with it!
This is a tricky thing in Haskell. A value of type IO Something doesn't actually do the action when you create it. It just creates an IO value, which is just an instruction to the runtime of what to do when it runs main. If you throw it away, and it never gets sequenced into an IO that your main performs, then the side-effect will never happen.

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.

STM with fclabels

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.

Getting rid of Haskell's IO ( )

I am wiriting simple application which has functionality of saving/loading its current state.
Save function looks as below:
doSave :: BoardType -> Field -> [Char] -> Bool
doSave board player fileName = do
let x = encodeFile fileName (board :: BoardType, player :: Field)
True -- there will be exception handling
And my load function:
doLoad :: [Char] -> IO (BoardType, Field)
doLoad fileName = decodeFile fileName :: IO (BoardType, Field)
And there's my problem, after loading, I have IO (BoardType, Field) which does not fit my program and other functions which probably should not accept IO parameters. If I have followed this IO escalation, there would be all IOs in my application - is it necessary (or - normal in haskell language)?
And finally - is there a simple way I can get rid of this IO?
It takes a little while to get used to.
Some monads let you extract the "inner value" after some work, but IO never does.
There is no way that e.g. returning the system time can ever be "pure" so any calculations you make with it need to remain wrapped in IO.
However, that doesn't mean most of your code lives in IO-land.
main = do
(bt, fld) <- doLoad "somefilename"
let bResult = doSomethingPureWithBoard bt
let fResult = doSomethingPureWithField fld
let bt2 = updateBoard bt bResult fResult
doSave "someFilename" bt2 fld -- This should also be in IO
You can always call pure functions from IO, just not the other way around. The <- gives you the "unwrapped" values while you are in an IO function. Actually it's passing the results as parameters to the next "statement" - google around "de-sugaring do notation" and similar.
is it necessary (or - normal in haskell language)
Your application will typically have an outer wrapper of IO actions, beginning with main :: IO () and the repeatedly restricted code that has less and less privledges, until you're only dealing with pure code.

Can I create a function in Haskell that will encapsulate reading data from file and returning me a simple list of data?

Consider the code below taken from a working example I've built to help me learn Haskell. This code parses a CSV file containing stock quotes downloaded from Yahoo into a nice simple list of bars with which I can then work.
My question: how can I write a function that will take a file name as its parameter and return an OHLCBarList so that the first four lines inside main can be properly encapsulated?
In other words, how can I implement (without getting all sorts of errors about IO stuff) the function whose type would be
getBarsFromFile :: Filename -> OHLCBarList
so that the grunt work that was being done in the first four lines of main can be properly encapsulated?
I've tried to do this myself but with my limited Haskell knowledge, I'm failing miserably.
import qualified Data.ByteString as BS
type Filename = String
getContentsOfFile :: Filename -> IO BS.ByteString
barParser :: Parser Bar
barParser = do
time <- timeParser
char ','
open <- double
char ','
high <- double
char ','
low <- double
char ','
close <- double
char ','
volume <- decimal
char ','
return $ Bar Bar1Day time open high low close volume
type OHLCBar = (UTCTime, Double, Double, Double, Double)
type OHLCBarList = [OHLCBar]
barsToBarList :: [Either String Bar] -> OHLCBarList
main :: IO ()
main = do
contents :: C.ByteString <- getContentsOfFile "PriceData/Daily/yhoo1.csv" --PriceData/Daily/Yhoo.csv"
let lineList :: [C.ByteString] = C.lines contents -- Break the contents into a list of lines
let bars :: [Either String Bar] = map (parseOnly barParser) lineList -- Using the attoparsec
let ohlcBarList :: OHLCBarList = barsToBarList bars -- Now I have a nice simple list of tuples with which to work
--- Now I can do simple operations like
print $ ohlcBarList !! 0
If you really want your function to have type Filename -> OHLCBarList, it can't be done.* Reading the contents of a file is an IO operation, and Haskell's IO monad is specifically designed so that values in the IO monad can never leave. If this restriction were broken, it would (in general) mess with a lot of things. Instead of doing this, you have two options: make the type of getBarsFromFile be Filename -> IO OHLCBarList — thus essentially copying the first four lines of main — or write a function with type C.ByteString -> OHLCBarList that the output of getContentsOfFile can be piped through to encapsulate lines 2 through 4 of main.
* Technically, it can be done, but you really, really, really shouldn't even try, especially if you're new to Haskell.
Others have explained that the correct type of your function has to be Filename -> IO OHLCBarList, I'd like to try and give you some insight as to why the compiler imposes this draconian measure on you.
Imperative programming is all about managing state: "do certain operations to certain bits of memory in sequence". When they grow large, procedural programs become brittle; we need a way of limiting the scope of state changes. OO programs encapsulate state in classes but the paradigm is not fundamentally different: you can call the same method twice and get different results. The output of the method depends on the (hidden) state of the object.
Functional programming goes all the way and bans mutable state entirely. A Haskell function, when called with certain inputs, will always produce the same output. Simple examples of
pure functions are mathematical operators like + and *, or most of the list-processing functions like map. Pure functions are all about the inputs and outputs, not managing internal state.
This allows the compiler to be very smart in optimising your program (for example, it can safely collapse duplicated code for you), and helps the programmer not to make mistakes: you can't put the system in an invalid state if there is none! We like pure functions.
The exception to the rule is IO. Code that performs IO is impure by definition: you could call getLine a hundred times and never get the same result, because it depends on what the user typed. Haskell handles this using the type system: all impure functions are marred with the IO type. IO can be thought of as a dependency on the state of the real world, sort of like World -> (NewWorld, a)
To summarise: pure functions are good because they are easy to reason about; this is why Haskell makes functions pure by default. Any impure code has to be labelled as such with an IO type signature; this tells the compiler and the reader to be careful with this function. So your function which reads from a file (a fundamentally impure action) but returns a pure value can't exist.
Addendum in response to your comment
You can still write pure functions to operate on data that was obtained impurely. Consider the following straw-man:
main :: IO ()
main = do
putStrLn "Enter the numbers you want me to process, separated by spaces"
line <- getLine
let numberStrings = words line
let numbers = map read numberStrings
putStrLn $ "The result of the calculation is " ++ (show $ foldr1 (*) numbers + 10)
Lots of code inside IO here. Let's extract some functions:
main :: IO ()
main = do
putStrLn "Enter the numbers you want me to process, separated by spaces"
result <- fmap processLine getLine -- fmap :: (a -> b) -> IO a -> IO b
-- runs an impure result through a pure function
-- without leaving IO
putStrLn $ "The result of the calculation is " ++ result
processLine :: String -> String -- look ma, no IO!
processLine = show . calculate . readNumbers
readNumbers :: String -> [Int]
readNumbers = map read . words
calculate :: [Int] -> Int
calculate numbers = product numbers + 10
product :: [Int] -> Int
product = foldr1 (*)
I've pulled logic out of main into pure functions which are easier to read, easier for the compiler to optimise, and more reusable (and so more testable). The program as a whole still lives inside IO because the data is obtained impurely (see the last part of this answer for a more thorough treatment of this argument). Impure data can be piped through pure functions using fmap and other combinators; you should try to put as little logic in main as possible.
Your code does seem to be most of the way there; as others have suggested you could extract lines 2-4 of your main into another function.
In other words, how can I implement (without getting all sorts of errors about IO stuff) the function whose type would be
getBarsFromFile :: Filename -> OHLCBarList
so that the grunt work that was being done in the first four lines of main can be properly encapsulated?
You cannot do this without getting all sorts of errors about IO stuff because this type for getBarsFromFile misses an IO. Probably that's what the errors about IO stuff are trying to tell you. Did you try understanding and fixing the errors?
In your situation, I would start by abstracting over the second to fourth line of your main in a function:
parseBars :: ByteString -> OHLCBarList
And then I would combine this function with getContentsOfFile to get:
getBarsFromFile :: FilePath -> IO OHLCBarList
This I would call in main.

Resources