6

I am trying to follow the movement of an object, on a 2D plane, which has been given a list of commands "forward, left or right".

So far I have functions that take in the components of a state of the object (direction, position and moves) and return the final state after all moves have been completed or all the positions passed along the way.

The state of the object is in the form Sstate (Dir dx dy) (Pos px py) [m] and a move consists of recursively applying the head of the list of moves to generate new states

ie Sstate (Dir 1 0) (Pos 0 0) "fff" -> Sstate (Dir 1 0) (Pos 0 1) "ff"

type Mov = Char

data Pos = Pos Int Int
 deriving (Show, Eq)

data Dir = Dir Int Int
 deriving (Show, Eq)

data Sstate = Sstate Dir Pos [Mov]
 deriving (Show, Eq)

move :: Sstate -> Sstate
move (Sstate (Dir dx dy) (Pos px py) []    )  = Sstate  (Dir dx dy) (Pos px py) []
move (Sstate (Dir dx dy) (Pos px py) (m:ms))
 | m == 'f'  = ss dx    dy    (dx + px) (dy + py) ms
 | m == 'l'  = ss (-dy) dx    px        py        ms
 | m == 'r'  = ss dy    (-dx) px        py        ms
 | otherwise = ss dy    dx    px        py        []
 where
   ss a b c d = Sstate (Dir a b) (Pos c d)

end :: Dir -> Pos -> [Mov] -> Sstate
end d p ms = iterate move initialState !! n
 where
   initialState = Sstate d p ms
   n = length ms + 1

position :: Sstate -> Pos
position (Sstate _ p _) = p

route :: Dir -> Pos -> [Mov] -> [Pos]
route d p ms = map position . take n . iterate  move $ initialState
 where
   initialState = Sstate d p ms
   n = length ms + 1

giving

λ: let x = Sstate (Dir 0 1) (Pos 0 2) "ff"

λ: move x
Sstate (Dir 0 1) (Pos 0 3) "f"

λ: end (Dir 0 1) (Pos 0 2) "ff"
Sstate (Dir 0 1) (Pos 0 4) ""

λ: route (Dir 0 1) (Pos 0 2) "ff"
[Pos 0 2,Pos 0 3,Pos 0 4]

This seems to work but it also seems that this is something that is asking for the State monad. I find the State monad confusing but feel that it would help me my understanding if someone would be kind enough to show how it could be used here.

Benjamin Hodgson
  • 42,952
  • 15
  • 108
  • 157
matt
  • 1,817
  • 14
  • 35
  • Read [this tutorial](http://learnyouahaskell.com/for-a-few-monads-more) about a few monads, including the `State` monad. – Bakuriu Jun 10 '16 at 13:18
  • What I found confusing with the state monad is that the state itself is not actually the monad. what is a xmonad is a function modifying the state and return a value : s -> (a, s) – mb14 Jun 10 '16 at 17:28
  • @mb14 One way to understand it is that the state is both an additional parameter and an additional return value; a function of type `a -> b` becomes a function of type `a -> s -> (b, s)`. Currying lets you think of this as taking a value of type `a` and returning a new function that, when given a state, can return a value of type `b` and a new state (`a -> (s -> (b, s))`. The monad, via the `>>=` operator, is just what lets you chain such functions together. Ultimately, you wind up with a function of type `s -> (t, s)`, which turns an initial state into a value of type `t`. – chepner Jun 10 '16 at 18:15
  • 1
    This is irrelevant, but I would recommend using something like `data Mov = Fwd | Lft | Rght | ... deriving (Eq, Show)` instead of making it a synonym for `Char`. This will make it easy to get GHC to help you see if you caught all the cases if you use `-Wall` or `-fwarn-incomplete-patterns`, and generally makes your intent clearer. – dfeuer Jun 10 '16 at 20:10

2 Answers2

2

Note that you don't directly need to use the State monad here, as end and route can be written using foldl' and scanl' once you consider a Mov as something that operates on a state, rather than being part of the state. Record syntax for Sstate also helps.

type Mov = Char
data Pos = Pos Int Int deriving (Show, Eq)
data Dir = Dir Int Int deriving (Show, Eq)
data Sstate = Sstate {direction :: Dir, position :: Pos} deriving (Show, Eq)

-- A helper to simplify move
changeDir :: Mov -> Dir -> Dir
changeDir 'l' (Dir x y) = Dir (-y) x
changeDir 'r' (Dir x y) = Dir y (-x)
changeDir m (Dir x y) = Dir y x

move :: Mov -> Sstate -> Sstate
move 'f' oldState@(Sstate (Dir dx dy) (Pos px py))  = oldState { position = Pos (dx + px) (dy + py) }
move  m  oldState@(Sstate dir _) = oldState { direction = changeDir m dir }

end :: [Mov] -> Sstate -> Sstate
end ms initialState = foldl' (flip move) initialState ms

route :: [Mov] -> Sstate -> [Pos]
route ms initialState = map position $ scanl' (flip move) initialState ms

Then your examples become:

λ: let x = Sstate {direction = Dir 0 1, position = Pos 0 2}

λ: move 'f' x
Sstate {direction = Dir 0 1, position = Pos 0 3}

λ: end "ff" x
Sstate {direction = Dir 0 1, position = Pos 0 4}

λ: route "ff" x
[Pos 0 2,Pos 0 3,Pos 0 4]

I'll leave it as an exercise (or to someone more knowledgeable and less lazy than me) to adapt

move :: Mov -> Sstate -> Sstate
end :: [Mov] -> Sstate -> Sstate
route :: [Mov] -> Sstate -> [Pos]

to

move :: Mov -> State Sstate ()
-- or possibly move :: Mov -> State Sstate Sstate ?
-- Like I said, more knowledgeable than me
end :: [Mov] -> State Sstate Sstate
route :: [Mov] -> State Sstate [Pos]
chepner
  • 497,756
  • 71
  • 530
  • 681
1

Here is some simple 'starter' code extending your module with some reformulations in terms of state. You will need to look at a tutorial like the LYAH chapter while fiddling with them, I'd think. I omit the signatures, which become increasingly complicated, but querying the types in ghci will be instructive. You need to add

import Control.Monad.State
import Control.Monad.Writer -- for the position-remembering example

Then the following should all work using your definition of move

step = do                        -- step the state once with your `move`,
 sstate <- get                   -- whatever the state is
 put (move sstate)
-- this little program could also be written: `modify move` which shows the
-- link between what you wrote and State a little more clearly

steps = do                       -- repeatedly apply `step` to the state
  Sstate _ _ ls <- get           -- til there are no moves, then stop
  if null ls 
  then return ()       -- could be: unless (null ls) $ do step ; steps
  else step >> steps

stepsIO = do                     -- do all steps as with `steps`, but print
  sstate@(Sstate a b ls) <- get  -- the current state at each state update
  liftIO $ print sstate
  if null ls then liftIO (putStrLn "Done!")
             else step >> stepsIO

stepsPrintPosition = do           -- do all steps as with `steps`, printing 
  Sstate _ b ls <- get            -- only position at each state update
  liftIO $ do putStr "current position: " 
              print b
  if null ls then liftIO (putStrLn "Done!")
             else do step 
                     stepsPrintPosition  

stepsAccumulatePositions = do    -- move through all states as with `steps`
  sstate@(Sstate a b ls) <- get  -- but use `tell` to keep adding the current
  tell [b]                       -- position to the underlying list 
  if null ls then return ()      -- of positions 
             else step >> stepsAccumulatePositions

example = Sstate (Dir 0 1) (Pos 0 2) "ffff"

To use things like step, steps, stepsIO etc, we apply runState; this gives us a function from a state to a new state

runStateT :: StateT s m a -> s -> m (a, s)

This of course is just the accessor for the newtype definition

newtype StateT s m a  = StateT {runStateT :: s -> m (a, s)}

The wrapping permits us to write fancy s -> m (a, s) things, using simpler s -> m (a, s) bits, but under the newtype hood, its always just a function s -> m (a, s) we are writing in the do notation.

Of course, once we unwrap with runStateT and have our function s -> m (a, s), we need to supply it with an initial state. It's easiest to see how this works by testing in ghci

>>> example
Sstate (Dir 0 1) (Pos 0 2) "ffff"

>>> runStateT step example            -- we step the state once with move
((),Sstate (Dir 0 1) (Pos 0 3) "fff")

>>> runStateT steps example           -- we keep stepping till there are no moves
((),Sstate (Dir 0 1) (Pos 0 6) "")

>>> runStateT stepsIO example         -- we print state at each state update
Sstate (Dir 0 1) (Pos 0 2) "ffff"
Sstate (Dir 0 1) (Pos 0 3) "fff"
Sstate (Dir 0 1) (Pos 0 4) "ff"
Sstate (Dir 0 1) (Pos 0 5) "f"
Sstate (Dir 0 1) (Pos 0 6) ""
Done!
((),Sstate (Dir 0 1) (Pos 0 6) "")

>>> runStateT stepsPrintPosition  example   -- print position only at state updates
current position: Pos 0 2
current position: Pos 0 3
current position: Pos 0 4
current position: Pos 0 5
current position: Pos 0 6
Done!
((),Sstate (Dir 0 1) (Pos 0 6) "") 


-- the WriterT examples accumulate a 'monoid' of things you keep
-- adding to with `tell xyz` Here we accumulate a [Position]
-- execXYZ and evalXYZ, where they exist, return less information than runXYZ

>>>  runWriterT $ runStateT stepsAccumulatePositions   example
(((),Sstate (Dir 0 1) (Pos 0 6) ""),[Pos 0 2,Pos 0 3,Pos 0 4,Pos 0 5,Pos 0 6])

>>>  execWriterT $ evalStateT stepsAccumulatePositions   example
[Pos 0 2,Pos 0 3,Pos 0 4,Pos 0 5,Pos 0 6]

In the code above I am using the mtl typeclasses and then using runStateT and runWriterT to "interpret" or specialize the class involving signatures. These are pertain to concrete types StateT and WriterT defined in Control.Monad.Trans.{State/Writer} One could omit the classes, and just write directly with those concrete types, importing those modules. The only difference would be that you need to do lift $ tell [b] in the one case where I combine two effects, state and writing or whatever you want to call it.

There is plenty to be said about the analysis of state you are working with but it will emerge how you might rework it, if you think the above through.

Michael
  • 2,889
  • 17
  • 16