Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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. Re:  Is there a simpler way? Building a monad on  `IO' Monad
      (Daniel Fischer)
   2. Re:  Is there a simpler way? Building a monad on  `IO' Monad
      (Daniel Fischer)
   3.  theStdGen unsafePerformIO (John Smith)
   4. Re:  theStdGen unsafePerformIO (Brent Yorgey)
   5. Re:  theStdGen unsafePerformIO (John Smith)
   6. Re:  theStdGen unsafePerformIO (Edward Z. Yang)
   7. Re:  theStdGen unsafePerformIO (Antoine Latter)
   8. Re:  theStdGen unsafePerformIO (John Smith)
   9. Re:  Is there a simpler way? Building a monad on `IO' Monad
      (Arlen Cuss)


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

Message: 1
Date: Sun, 9 Jan 2011 12:27:51 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Is there a simpler way? Building a
        monad on        `IO' Monad
To: beginners@haskell.org
Message-ID: <201101091227.51709.daniel.is.fisc...@googlemail.com>
Content-Type: text/plain;  charset="utf-8"

On Sunday 09 January 2011 11:47:40, Arlen Cuss wrote:
> Hi all,
>
> Thanks for previous help on this list! I really appreciate it.
>
> Today I wrote a monad and I'm not sure if I took a complicated way about
> it. It's essentially a State monad, except with some specialised
> functions that operate on the `state' if you will (though the state is
> rarely mutated)?you initialise it with two Handles (e.g. stdin, stdout),
> and then a set of specialised functions defined `within' the monad will
> operate on those handles. It saves you from passing the Handles
> throughout the functions and subcalls.
>
> It's quite possible there already exists a monad for this job, or that
> IO will actually let you do this, but I didn't find it in a bit of
> searching, and concluded this would be a fun way to solve the problem.
> If anyone has any advice on shortening the code, or possibly removing
> the need for it, please let me know!
>
> Here's the main monad:
> > import System.IO
> > import Control.Applicative
> >
> > newtype IODirector a = IODirector { runIODirector :: (Handle,Handle)
>
> -> IO (a, (Handle,Handle)) }

Enter Monad transformers (you're not the first to discover them, congrats 
nevertheless :).

You can make it a type synonym

type IODirector = StateT (Handle,Handle) IO

or make it a newtype, where you can let GHC derive all interesting stuff:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.State[.Strict]

newtype IODirector a 
    = IODirector { director :: StateT (Handle,Handle) IO a }
      deriving (Functor, Monad, MonadPlus, MonadState (Handle,Handle), 
MonadIO)

runIODirector = runStateT . director

>
> > instance Monad IODirector where
> >   return a = IODirector $ \hs -> return (a, hs)
> >   m >>= k  = IODirector $ \hs -> do (a, hs) <- runIODirector m hs
> >                                     runIODirector (k a) hs
>
> This is basically the same as State, except we `return' to the IO monad,
> as is the result of the stateful computation an I/O action, IO (a,
> (Handle,Handle)).
>
> We then have a type-class for the actual I/O we can perform within the
>
> monad:
> > class MonadDirectedIO a where
> >   dPutStr :: String -> a ()
> >   dPutStrLn :: String -> a ()
> >
> >   dGetLine :: a String
> >   dGetChar :: a Char
>
> ...
>
> The functions here continue for all the ones from IO I really wanted to
>
> use, and the instance is not surprising:
> > instance MonadDirectedIO IODirector where
> >   dPutStr s = IODirector $ \hs@(_,hOut) -> do hPutStr hOut s
> >                                               return ((), hs)
> >   dPutStrLn = dPutStr . (++ "\n")
> >
> >   dGetLine = IODirector $ \hs@(hIn,_) -> do r <- hGetLine hIn
> >                                             return (r, hs)
> >   dGetChar = IODirector $ \hs@(hIn,_) -> do r <- hGetChar hIn
> >                                             return (r, hs)
>
> I'm aware I didn't have to put this in a type-class, but it seemed a
> reasonable thing to do.
>
> There was a little plumbing work to `enclose' IO within this monad. My
> question is - did I do it right? Or is there a simpler way?

There is a simpler way, with MonadState (Handle,Handle) (btw., perhaps it's 
better to use a self-defined record than to use a pair, if you access the 
fields by name you can't confuse the positions of in and out) and MonadIO:

outIO :: (Handle -> a -> IO b) -> a -> IODirector b
outIO action value = do
   hOut <- gets snd   -- gets outHandle
   liftIO $ action hOut value

inIO :: (Handle -> IO a) -> IODirector a
inIO action = do
   hIn <- gets fst    -- gets inHandle
   liftIO $ action hIn

>
> Of course, if there's already such functionality in the built-in, I'd
> also be interested to hear ... ;-)

Mostly yes (you have to fill in a particular details of course), the Monad 
transformers provided by the libraries (mtl, transformers, others; I 
recommend using mtl [now a wrwpper around transformers] or transformers) 
have most of the functionality you need.

As you've seen, combining Monads is quite useful. Fortunately, there have 
been clever people who have found that out before, so you need not 
implement everything yourself.

>
> Cheers!
>
> Arlen

Cheers,
Daniel




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

Message: 2
Date: Sun, 9 Jan 2011 13:43:16 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Is there a simpler way? Building a
        monad on        `IO' Monad
To: beginners@haskell.org
Message-ID: <201101091343.16584.daniel.is.fisc...@googlemail.com>
Content-Type: text/plain;  charset="utf-8"

On Sunday 09 January 2011 11:47:40, Arlen Cuss wrote:
> Hi all,
>
> Thanks for previous help on this list! I really appreciate it.
>
> Today I wrote a monad and I'm not sure if I took a complicated way about
> it. It's essentially a State monad, except with some specialised
> functions that operate on the `state' if you will (though the state is
> rarely mutated)

If it is not mutated at all (which seems not entirely unlikely with a pair 
(stdin,stdout) of Handles), you should use

ReaderT (Handle,Handle) IO

instead of

StateT (Handle,Handle) IO

btw.

Cheers,
Daniel



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

Message: 3
Date: Sun, 09 Jan 2011 17:55:41 +0200
From: John Smith <volderm...@hotmail.com>
Subject: [Haskell-beginners] theStdGen unsafePerformIO
To: beginners@haskell.org
Message-ID: <igclpt$n8...@dough.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Why does theStdGen require unsafePerformIO? I recompiled the Random module with

theStdGen :: IO (IORef StdGen)
theStdGen  = do
                 rng <- mkStdRNG 0
                 newIORef rng

The implementations of a few functions needed to change slightly (to extract 
the IORef from IO), but no other type 
signatures needed changing, and nothing blew up.




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

Message: 4
Date: Sun, 9 Jan 2011 11:16:47 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] theStdGen unsafePerformIO
To: beginners@haskell.org
Message-ID: <20110109161646.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Jan 09, 2011 at 05:55:41PM +0200, John Smith wrote:
> Why does theStdGen require unsafePerformIO? I recompiled the Random module 
> with
> 
> theStdGen :: IO (IORef StdGen)
> theStdGen  = do
>                 rng <- mkStdRNG 0
>                 newIORef rng
> 
> The implementations of a few functions needed to change slightly (to
> extract the IORef from IO), but no other type signatures needed
> changing, and nothing blew up.

With your definition, theStdGen is a computation that gives you a
*new*, *different* IORef (containing yet another generator initialized
with a seed of zero) every time you call it.  The original definition
with unsafePerformIO generates a single, global IORef which is
accessed by every subsequent call to getStdGen.

-Brent



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

Message: 5
Date: Sun, 09 Jan 2011 19:34:59 +0200
From: John Smith <volderm...@hotmail.com>
Subject: Re: [Haskell-beginners] theStdGen unsafePerformIO
To: beginners@haskell.org
Message-ID: <igcrk2$gs...@dough.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 09/01/2011 18:16, Brent Yorgey wrote:
> With your definition, theStdGen is a computation that gives you a
> *new*, *different* IORef (containing yet another generator initialized
> with a seed of zero) every time you call it.  The original definition
> with unsafePerformIO generates a single, global IORef which is
> accessed by every subsequent call to getStdGen.

How does it do this?




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

Message: 6
Date: Sun, 09 Jan 2011 12:40:31 -0500
From: "Edward Z. Yang" <ezy...@mit.edu>
Subject: Re: [Haskell-beginners] theStdGen unsafePerformIO
To: John Smith <volderm...@hotmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID: <1294594776-sup-1...@ezyang>
Content-Type: text/plain; charset=UTF-8

Because unsafePerformIO returns a pure value 'a', GHC only computes it
once and then reuses it later (it's also why when you do this
you need to make sure you tell GHC not to inline the computation, which
will obviously change the semantics.)

Cheers,
Edward



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

Message: 7
Date: Sun, 9 Jan 2011 10:14:56 -0600
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] theStdGen unsafePerformIO
To: John Smith <volderm...@hotmail.com>
Cc: beginners@haskell.org, haskell mailing list
        <haskell-c...@haskell.org>
Message-ID:
        <aanlktinzx7qdnsjmgghr7jd41anqgae4ozuptiq8w...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

You might get more answers to this sort of question on the
haskell-cafe list. Even there, I think you might need to ask whoever
the authors were for a question like this :-)

On Sun, Jan 9, 2011 at 9:55 AM, John Smith <volderm...@hotmail.com> wrote:
> Why does theStdGen require unsafePerformIO? I recompiled the Random module
> with
>
> theStdGen :: IO (IORef StdGen)
> theStdGen ?= do
> ? ? ? ? ? ? ? ?rng <- mkStdRNG 0
> ? ? ? ? ? ? ? ?newIORef rng
>
> The implementations of a few functions needed to change slightly (to extract
> the IORef from IO), but no other type signatures needed changing, and
> nothing blew up.
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

Message: 8
Date: Sun, 09 Jan 2011 19:56:46 +0200
From: John Smith <volderm...@hotmail.com>
Subject: Re: [Haskell-beginners] theStdGen unsafePerformIO
To: beginners@haskell.org
Message-ID: <igcssu$o4...@dough.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 09/01/2011 19:40, Edward Z. Yang wrote:
> Because unsafePerformIO returns a pure value 'a', GHC only computes it
> once and then reuses it later (it's also why when you do this
> you need to make sure you tell GHC not to inline the computation, which
> will obviously change the semantics.)

theStdGen doesn't have NOINLINE. Is the pragma on unsafeDupablePerformIO 
sufficient for any caller of unsafePerformIO?




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

Message: 9
Date: Mon, 10 Jan 2011 19:26:55 +1100
From: Arlen Cuss <cel...@sairyx.org>
Subject: Re: [Haskell-beginners] Is there a simpler way? Building a
        monad on `IO' Monad
To: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Cc: beginners@haskell.org
Message-ID: <1294648015.2365.3.ca...@asu>
Content-Type: text/plain; charset="utf-8"

Hi Daniel,

> If it is not mutated at all (which seems not entirely unlikely with a pair 
> (stdin,stdout) of Handles), you should use
> 
> ReaderT (Handle,Handle) IO
> 
> instead of
> 
> StateT (Handle,Handle) IO

Thank you so much! Your careful exposition of the avenues available to
me in the previous email was amazing, and is most, most appreciated! I
had a feeling what I was doing was probably a common occurrence, but
haven't seen enough real-world Haskell code to know what to call it yet!

> Cheers,
> Daniel

Thanks again;

Arlen
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110110/611c59b4/attachment.pgp>

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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 31, Issue 7
****************************************

Reply via email to