Don's code intrigued me, so I fired up my trusty emacs and ghci, and turned it into actual code, which type-checks. Well, ok, I kind of randomly poked at it, while begging for help, which I received in abundance from #haskell, particularly oerjan, and Don himself. Anyway, here's the code:
{-# OPTIONS -fglasgow-exts #-} module Game where import Control.Applicative import Control.Monad.State import System newtype Game a = Game (StateT World IO a) deriving (Functor, Monad, MonadState World, MonadIO) data Event = Quit | LeftE | RightE | Up | Down data Board = Board [Int] deriving (Show) data World = World [Int] game :: Event -> Game Action game Quit = liftIO $ exitWith ExitSuccess game LeftE = return MoveOK game RightE = return MoveOK game Up = return MoveOutOfBounds game Down = return (MoveBadTerrain "Tree") runGame :: [Event] -> IO [Action] runGame es = evalStateT s (World [0]) where Game s = mapM game es data Action = MoveOutOfBounds | MoveBadTerrain String | 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." main = do events <- map processInput <$> getContents mapM_ print =<< runGame events processInput :: Char -> Event processInput = undefined On Dec 3, 2007 10:28 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > 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 > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe