[Haskell-cafe] Re: do

ChrisK haskell at list.mightyreason.com
Mon Oct 15 14:45:47 EDT 2007


jerzy.karczmarczuk at info.unicaen.fr wrote:
> Peter Verswyvelen writes about non-monadic IO, unique "external worlds":
>> But... isn't this what the Haskell compiler & runtime do internally
>> when IO monads are executed? Passing the RealWorld "singleton" from
>> "action" to "action"? 

In GHC, yes.

> 
> I never looked into any Haskell compiler. Chalmers, or York, don't
> remember,
> used continuations, this seems a bit different from the Clean approach, but
> I don't really know the gory details.
>> To me, no real difference exists between IO monads and Clean's uniques
>> types; it's just a different approach to tackle the same problem. 
> 
> Yes, *different approach*. So, there *are* differences. Compilers, anyway,
> are special applications. I wanted to see - responding to Brandon - a
> "normal" Haskell program, which does IO without monads, that't all.

> The problem is then when you hide something, you hide. It is possible to
> superpose a kind of monadic framework on unique worlds, files, etc. in
> Clean, but the reverse operation goes beyond my horizons.

> Some examples, anybody?
> Jerzy Karczmarczuk

I don't have examples, but I can show you where the gory details are hiding:

The Haskell 98 standard specifies the API for input/output to be using the IO
monad.  If you want to use Haskell 98 to do input/output without the IO monad
then you will find that you cannot do so. I see three ways to go around Haskell98.

Common caveat: The thing that using the provided IO monad does is provide a
standard way of sequencing two input/output operations.   Once you avoid that
sequencing then you indeterminism unless you provide your own sequencing manually.

The first, which you may decide does not really count, is using
"unsafePerformIO" or "unsafeInterleaveIO" and avoiding the sequencing provided
by the IO monad.  This still does nothing to tell you about the gory details.

As a cheat: If you use the FFI addendum then you can access all the impure c
input/output functions and lie about their type so that are not in IO.  Then you
could manually manage their sequencing and control everything.  This comes
closer to understanding how the standard IO operations are implemented in the
gory details.

For the GHC implementation of Haskell it is possible to go inside the IO monad
and operate using the same gory details that GHC uses.  This is probably what
you want to see, but note that it is not the only compiler or the only way to do
this.

The details are in the source at
http://darcs.haskell.org/ghc-6.6/packages/base/GHC/
in IOBase.lhs and IO.hs and so on...

>From IOBase.lhs I see that GHC uses a newtype around a function of type
State b -> (State b, a) to represent IO a.
The State b is actually an unboxed type "State# RealWorld".  The tuple is
likewise an unboxed "(# , #)" tuple.

> newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
> 
> unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
> unIO (IO a) = a

Also in IOBase.lhs this is made into a Functor and, inevitably, a monad:

> instance  Functor IO where
>    fmap f x = x >>= (return . f)
> 
> instance  Monad IO  where
>     {-# INLINE return #-}
>     {-# INLINE (>>)   #-}
>     {-# INLINE (>>=)  #-}
>     m >> k      =  m >>= \ _ -> k
>     return x	= returnIO x
> 
>     m >>= k     = bindIO m k
>     fail s	= failIO s

> returnIO :: a -> IO a
> returnIO x = IO (\ s -> (# s, x #))

> bindIO :: IO a -> (a -> IO b) -> IO b
> bindIO (IO m) k = IO ( \ s ->
>   case m s of 
>     (# new_s, a #) -> unIO (k a) new_s
>   )

> failIO :: String -> IO a
> failIO s = ioError (userError s)
>
> -- | Raise an 'IOError' in the 'IO' monad.
> ioError         :: IOError -> IO a 
> ioError		=  ioException
>
> ioException	:: IOException -> IO a
> ioException err =  IO $ raiseIO# (IOException err)
> 

Where raiseIO# is from GHC.Prim
http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Prim.html
http://darcs.haskell.org/ghc/compiler/prelude/primops.txt.pp



More information about the Haskell-Cafe mailing list