
Hey everyone, I'm making a Game Monad for an assignment (yes, homework) . Here's a little explanation of what I need to do (I can't use anything from Control.Monad.*, I need to do everything myself): I need to define my newtype Game and make it's Monad instance I need to make the function : runGame :: Game a -- A particular game -> Int -- Initial amount of lives -> Maybe (a , Int ) -- Result and remaining lives. I need to make the instance for this class: class Monad m = > GameMonad m where extraLife :: m () getLives :: m Int checkPoint :: m a -> m a die :: m a now what I've done (I was inspired by the State Monad) I defined my Game type as follows:
newtype Game r = Game { execGame :: Int -> Maybe (r,Int) }
My Monad instance like this:
instance Monad Game where return a = Game $ \r -> Just (a,r) m >>= k = Game $ \r -> let x = execGame m r in case x of Just (a, r') -> execGame (k a) r' Nothing -> Nothing
and my GameMonad instance:
instance GameMonad Game where extraLife = Game $ \l -> Just ((),l+1) getLives = Game $ \l -> Just (l,l) die = do n <- getLives Game $ \_ -> Just ((),n-1) -- Here's the problem
so, what's bothering me? Look at the type signature of die in the GameMonad class, it's supposed to return something of type (m a), but I don't know what to return in that case, and whatever I try to return it doesn't work, because when I try to compile it says that it couldn't match expected type 'a' against infered type 'whatever' ('whatever' being anything, from (), to string, or a number). shouldn't 'a' match with anything I put there? Note that I can't change the signatures because they were giving to me that way and I already checked with teacher if they were right. (I fixed it returning Maybe (Maybe a, Int) instead, but I can't change the signature of the function runGame) Thanks you, Hector Guilarte

On 8 July 2010 10:55, Hector Guilarte
newtype Game r = Game { execGame :: Int -> Maybe (r,Int) } My Monad instance like this: instance Monad Game where return a = Game $ \r -> Just (a,r) m >>= k = Game $ \r -> let x = execGame m r in case x of Just (a, r') -> execGame (k a) r' Nothing -> Nothing and my GameMonad instance: instance GameMonad Game where extraLife = Game $ \l -> Just ((),l+1) getLives = Game $ \l -> Just (l,l) die = do n <- getLives Game $ \_ -> Just ((),n-1) -- Here's the problem so, what's bothering me? Look at the type signature of die in the GameMonad class, it's supposed to return something of type (m a), but I don't know what to return in that case, and whatever I try to return it doesn't work, because when I try to compile it says that it couldn't match expected type 'a' against infered type 'whatever' ('whatever' being anything, from (), to string, or a number). shouldn't 'a' match with anything I put there? Note that I can't change the signatures because they were giving to me that way and I already checked with teacher if they were right. (I fixed it returning Maybe (Maybe a, Int) instead, but I can't change the signature of
Hey everyone, I'm making a Game Monad for an assignment (yes, homework) . Here's a little explanation of what I need to do (I can't use anything from Control.Monad.*, I need to do everything myself): I need to define my newtype Game and make it's Monad instance I need to make the function : runGame :: Game a -- A particular game -> Int -- Initial amount of lives -> Maybe (a , Int ) -- Result and remaining lives. I need to make the instance for this class: class Monad m = > GameMonad m where extraLife :: m () getLives :: m Int checkPoint :: m a -> m a die :: m a now what I've done (I was inspired by the State Monad) I defined my Game type as follows: the function runGame)
The `die' function doesn't make much sense, because as you've intuited it must be of _any_ type. You could have "die = return undefined" which matches the type signature, but isn't very helpfull, especially if you try to use the value inside the Monad. The only other option you have is to use `error', similar to the default fail method in Monad but with a set message. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Are you sure you are interpreting what 'die' should do properly? Your code makes sense if die should decrement your life counter and continue along, however if 'die' is meant to end your whole game, then there is another implementation that does type check. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Wed, Jul 7, 2010 at 8:48 PM, John Meacham
Are you sure you are interpreting what 'die' should do properly? Your code makes sense if die should decrement your life counter and continue along, however if 'die' is meant to end your whole game, then there is another implementation that does type check.
John
You're absolutely right, I sen't the wrong code, here's the "correct" one and a little bit more explanation about what checkpoint does. The result of die makes sense for the checkPoint function since there are three cases for it: 1) The player died and has no remaining lifes. The game can't continue, I just return Noting in the die function and in checkpoint make the corresponding case. 2) The player died and has remaining lifes. The game can be retried with a life subtracted. I would need to tell checkpoint that I died and I want to retry, that's where I think the result is important, because of the next case. 3) The player didn't died, it finished the particular game and checkpoint m equals m. Here I would need to see if the result of the game was different from the result from die, and continue. instance GameMonad Game where extraLife = Game $ \l -> Just ((),l+1) getLives = Game $ \l -> Just (l,l) die = do n <- getLives if n <= 0 then Game $ \_ -> Nothing else Game $ \_ -> Just ("player died",n-1) checkPoint a = do n <- getLives case execGame a n of Nothing -> Game $ \_ -> Nothing Just c -> gameOn $ fst c where gameOn "player died" = a >>= \_ -> (checkPoint a) gameOn _ = a Obviously this fails to compile because I'm returning a String and it doesn't match with a either, but the idea of what I think I need to do is right there. Ivan Miljenovic told me to use error, and actually I though something like that. in STM retry combined with atomically does something similar as what I need checkpoint and die to do, and they use exceptions to accomplish it. I really think that's the solution I want, but then I have another question, when I 'throw' the exception in die and 'catch' it in checkpoint to call it again, is the number of lives gonna be lives - 1? Thanks for answering so quickly, Hector Guilarte Pd: Here's an example run of how my homework should work after is finished printLives :: ( GameMonad m , MonadIO m ) = > String -> m () printLives = do n <- getLives liftIO $ putStrLn $ s ++ " " ++ show n test1 :: ( GameMonad m , MonadIO m ) = > m () test1 = checkPoint $ do printLives " Vidas : " die liftIO $ putStrLn " Ganamos ! " lastChance :: GameMonad m = > m () lastChance = do n <- getLives if n == 1 then return () else die test2 :: ( GameMonad m , MonadIO m ) = > m String test2 = checkPoint $ do printLives " Inicio " n <- getLives if n == 1 then do liftIO $ putStrLn " Final " return " Victoria ! " else do checkPoint $ do printLives " Checkpoint anidado " lastChance extraLife printLives " Vida extra ! " die AND THE OUTPUT TO SOME CALLS ghci > runGameT test1 3 Vidas : 3 Vidas : 2 Vidas : 1 Nothing ghci > runGameT test2 3 Inicio 3 Checkpoint anidado 3 Checkpoint anidado 2 Checkpoint anidado 1 Vida extra ! 2 Inicio 1 Finish Just ( " Victoria ! " ,1) --
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey! I just wanted to let you know I made it. I just changed the newtype declaration to:
newtype Game r = Game { execGame :: Int -> (Maybe r,Int) } and from there everything went just fine.
Thank you for your responses,
Hector Guilarte
On Wed, Jul 7, 2010 at 9:24 PM, Hector Guilarte
On Wed, Jul 7, 2010 at 8:48 PM, John Meacham
wrote: Are you sure you are interpreting what 'die' should do properly? Your code makes sense if die should decrement your life counter and continue along, however if 'die' is meant to end your whole game, then there is another implementation that does type check.
John
You're absolutely right, I sen't the wrong code, here's the "correct" one and a little bit more explanation about what checkpoint does.
The result of die makes sense for the checkPoint function since there are three cases for it: 1) The player died and has no remaining lifes. The game can't continue, I just return Noting in the die function and in checkpoint make the corresponding case. 2) The player died and has remaining lifes. The game can be retried with a life subtracted. I would need to tell checkpoint that I died and I want to retry, that's where I think the result is important, because of the next case. 3) The player didn't died, it finished the particular game and checkpoint m equals m. Here I would need to see if the result of the game was different from the result from die, and continue.
instance GameMonad Game where extraLife = Game $ \l -> Just ((),l+1) getLives = Game $ \l -> Just (l,l) die = do n <- getLives if n <= 0 then Game $ \_ -> Nothing else Game $ \_ -> Just ("player died",n-1) checkPoint a = do n <- getLives case execGame a n of Nothing -> Game $ \_ -> Nothing Just c -> gameOn $ fst c where gameOn "player died" = a >>= \_ -> (checkPoint a) gameOn _ = a
Obviously this fails to compile because I'm returning a String and it doesn't match with a either, but the idea of what I think I need to do is right there.
Ivan Miljenovic told me to use error, and actually I though something like that. in STM retry combined with atomically does something similar as what I need checkpoint and die to do, and they use exceptions to accomplish it. I really think that's the solution I want, but then I have another question, when I 'throw' the exception in die and 'catch' it in checkpoint to call it again, is the number of lives gonna be lives - 1?
Thanks for answering so quickly,
Hector Guilarte
Pd: Here's an example run of how my homework should work after is finished
printLives :: ( GameMonad m , MonadIO m ) = > String -> m () printLives = do n <- getLives liftIO $ putStrLn $ s ++ " " ++ show n test1 :: ( GameMonad m , MonadIO m ) = > m () test1 = checkPoint $ do printLives " Vidas : " die liftIO $ putStrLn " Ganamos ! "
lastChance :: GameMonad m = > m () lastChance = do n <- getLives if n == 1 then return () else die test2 :: ( GameMonad m , MonadIO m ) = > m String test2 = checkPoint $ do printLives " Inicio " n <- getLives if n == 1 then do liftIO $ putStrLn " Final " return " Victoria ! " else do checkPoint $ do printLives " Checkpoint anidado " lastChance extraLife printLives " Vida extra ! " die
AND THE OUTPUT TO SOME CALLS
ghci > runGameT test1 3 Vidas : 3 Vidas : 2 Vidas : 1 Nothing ghci > runGameT test2 3 Inicio 3 Checkpoint anidado 3 Checkpoint anidado 2 Checkpoint anidado 1 Vida extra ! 2 Inicio 1 Finish Just ( " Victoria ! " ,1)
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Hector Guilarte
-
Ivan Miljenovic
-
John Meacham