[Haskell-cafe] Advice for clean code.
Don Stewart
dons at galois.com
Mon Dec 3 22:28:46 EST 2007
stefanor:
> On Mon, Dec 03, 2007 at 08:47:48PM -0600, David McBride wrote:
> > I am still in the early stages learning haskell, which is my first foray
> > into functional programming. Well there's no better way to learn than to
> > write something, so I started writing a game.
> >
> > Mostly the thing looks good so far, far better than the C version did.
> > However, my problem is that code like the following is showing up more
> > often and it is becoming unwieldy.
> >
> > gameLoop :: World -> IO ()
> > gameLoop w = do
> > drawScreen w
> >
> > action <- processInput
> >
> > let (result, w') = processAction action w
> >
> > case result of
> > MoveOutOfBounds -> putStrLn "Sorry you can't move in that direction."
> > MoveBadTerrain a -> case a of
> > Wall -> putStrLn "You walk into a wall."
> > Tree -> putStrLn "There is a tree in the way."
> > otherwise -> putStrLn "You can't move there."
> > otherwise -> return ()
> >
> > let w'' = w' { window = updateWindowLocation (window w') (location $
> > player w')}
> >
> > unless (action == Quit) (gameLoop w'')
> >
> > Where world contains the entire game's state and so I end up with w's with
> > multiple apostrophes at the end. But at the same time I can't really break
> > these functions apart easily. This is error prone and seems pointless.
> >
> > I have been reading about control.monad.state and I have seen that I could
> > run execstate over this and use modify but only if each function took a
> > world and returned a world. That seems really limiting. I'm not even sure
> > if this is what I should be looking at.
> >
> > I am probably just stuck in an imperative mindset, but I have no idea what
> > to try to get rid of the mess and it is only going to get worse over time.
> > Any suggestions on what I can do about it?
>
> I'd recommend using StateT World IO. You can always run other functions
> using 'lift'; for instance lift can be :: IO () -> StateT World IO ().
The fact your passing state explicitly, which is error prone, pretty much
demands a State monad., And the IO in the main loop seems needless -- the game
is really just a function from :: World -> [Event] -> [(World',Action)]
So strongly consider lifting the IO out of the main loop, and just have your
game be a function from input events, to output game states, Which you draw as
they're received.
The game would run in an environment something like:
newtype Game a = Game (StateT World IO) a
deriving (Functor, Monad, MonadState World)
The inner loop would be something like:
game :: Event -> Game Action
game Quit = exitWith ExitSuccess
game Left = ... >> return MoveOK
game Right = ... >> return MoveOK
game Up = return MoveOutOfBounds
game Down = return (MoveBadTerrain Tree)
Running the game over the input events, producing a sequence of screens
to print:
runGame :: [Event] -> [(Board,Action)]
runGame es = evalState (mapM game es) 0
Use show for the result action, to avoid ugly print statements,
data Action
= MoveOutOfBounds
| MoveBadTerrain Object
| MoveOK
-- How to display results
instance Show Action where
show MoveOutOfBounds = "Sorry you can't move in that direction."
show (MoveBadTerrain a) = case a of
Wall -> "You walk into a wall."
Tree -> "There is a tree in the way."
otherwise -> "You can't move there."
show MoveOk = "Good move."
And at the top level,
main = do
events <- map processInput <$> getContents
mapM_ print (runGame events)
This isn't real code, just a sketch.
-- Don
More information about the Haskell-Cafe
mailing list