Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Learning Monads with 'setjmp' and 'longjmp'      like actions
      (Michael Roth)


----------------------------------------------------------------------

Message: 1
Date: Sun, 24 Jul 2016 19:17:08 +0200
From: Michael Roth <l...@mroth.net>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: [Haskell-beginners] Learning Monads with 'setjmp' and
        'longjmp'       like actions
Message-ID: <5794f814.5010...@mroth.net>
Content-Type: text/plain; charset=utf-8; format=flowed

Hi,

I'm really trying hard to understand monads but I guess my brain is 
trapped in the imperative world.

Below what I have done so far. But now I would like to implement 
something like this:

do
    foo
    (label, jumped) <- setjmp
    bar
    longjmp label

But I'm stuck. How can I implement 'setjmp' and 'longjmp' with my monad?
I'm not able to grasp how can I design 'setjmp' and somehow create a 
label to use in 'longjmp'.
Maybe my monad structure is not appropriate?


Code follows:
---------------------------------------------------------------

data World = SomeWorld
     deriving (Eq, Show)

data ProgramResult a =
     Result      { world :: World, result :: a }
   | Continue    { world :: World, continue :: Program a }
   | Stopped     { world :: World }


newtype Program a = Program { runProgram :: World -> ProgramResult a }


runComplete :: Program a -> World -> (World, a)
runComplete prg world0 =
     case runProgram prg world0 of
          (Result world1 x1)     -> (world1, x1)
          (Continue world1 prg1) -> runComplete prg1 world1


nop :: Program ()
nop = return ()


yield :: Program ()
yield = Program $ \world -> Continue world nop


stop :: Program ()
stop = Program $ \world -> Stopped world


instance Functor Program where
     fmap = liftM

instance Applicative Program where
     pure  = return
     (<*>) = ap

instance Monad Program where
     return x = Program $ \world0 -> Result world0 x

     ma >>= fb = Program $ \world0 ->
         case runProgram ma world0 of
              (Result world1 x1)         -> runProgram (fb x1) world1
              (Continue world1 prg1)     -> Continue world1 (prg1 >>= fb)
              (Stopped world1)           -> Stopped world1



------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 97, Issue 13
*****************************************

Reply via email to