[Haskell-cafe] monad question

Andrew Harris andrew.unit at gmail.com
Sun Sep 19 13:40:59 EDT 2004


Hi everyone,

  Well, I'm trying to build a soccer server client and am using
Haskell.  I thought I was muddling through well enough... but I have
some questions.  I am using the Robot monad that I copied from Hudak's
book HSOE from page 272 (assuming I would understand it later).

Here's the monad code I copied:

newtype Robot a = Robot (RobotState -> IO (RobotState, a))

instance Monad Robot where
        return a = Robot (\s -> return (s, a))
        Robot sf0 >>= f =
              Robot (\s0 -> do
                               (s1, a1) <- sf0 s0
                               let Robot sf1 = f a1
                               (s2, a2) <- sf1 s1
                               return (s2, a2))

updateState :: (RobotState -> RobotState) -> Robot ()
updateState u = Robot (\s -> return (u s, ()))

queryState :: (RobotState -> a) -> Robot a
queryState q = Robot (\s -> return (s, q s))

I defined myself a comfortable "chunk of state" (comfortable for today
at least):

data RobotState =
    RobotState { player_type :: RobotType,
                 team_name :: String,
                 my_current_position :: Position,
                 visible_flags :: [ObjInfo],
                 visible_ball :: [ObjInfo],
                 visible_friends :: [ObjInfo],
                 visible_foes :: [ObjInfo],
                 audible_player_messages :: [String],
                 my_current_mode :: RobotMode,
                 debug_level :: [RobotDebugLevel],
                 my_uniform_number :: Integer,
                 game_mode :: GameMode,
                 game_clock :: Integer } deriving Show

In addition, I added some support functions similar to the ones he
wrote in Section 19.3.1:

assign_flags :: [ObjInfo] -> Robot ()
assign_flags flaglist = updateState (\s -> s {visible_flags = flaglist})

assign_friends :: [ObjInfo] -> Robot ()
assign_friends friendlist = updateState (\s -> s {visible_friends = friendlist})

assign_foes :: [ObjInfo] -> Robot ()
assign_foes foelist = updateState (\s -> s {visible_foes = foelist})

assign_ball :: [ObjInfo] -> Robot ()
assign_ball balllist = updateState (\s -> s {visible_ball= balllist})

Now, I read several online monad tutorials and kind of understand the
notion of a thread of function calls.  And I know that the do notation
is syntactic sugar for the bind operation.  But the code I've written
is really nasty.  For example, here is part of my code that handles a
see record and returns a new RobotState:

handleSeeRecord :: [SeeObjInfo_type] -> RobotState -> IO (RobotState, ())
handleSeeRecord seeobjlist p = do flaglist <- return (morphToList
flagFinder seeobjlist)
                                 balllist <- return (morphToList
ballFinder seeobjlist)
                                 friendlist <- return (morphToList
friendFinder seeobjlist)
                                 foelist <- return (morphToList
foeFinder seeobjlist)
                                 Robot e <- return (assign_flags
(flagSpread flaglist))
                                 Robot f <- return (assign_ball balllist)
                                 Robot g <- return (assign_friends friendlist)
                                 Robot h <- return (assign_foes foelist)
                                 (r', ()) <- e p
                                 (r'', ()) <- f r'
                                 (r''', ()) <- g r''
                                 h r'''

This actually works, but I think it can be improved with the bind
operation >>= somehow.  I tried a few alternatives but couldn't find
one that worked.  I ended up with this because it seems I had to
"strip" the type off of "return (assign_flags (flagSpread flaglist))"
and get the "e" that was a function.  Might someone have a suggestion
on how to improve this?

thanks
-andrew


More information about the Haskell-Cafe mailing list