[Haskell-cafe] does () match with a??

Hector Guilarte hectorg87 at gmail.com
Fri Jul 9 00:56:10 EDT 2010


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 <hectorg87 at gmail.com> wrote:

>
> On Wed, Jul 7, 2010 at 8:48 PM, John Meacham <john at repetae.net> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100708/8ba57bd5/attachment-0001.html


More information about the Haskell-Cafe mailing list