[Haskell-cafe] one-way monads

Jeremy Shaw jeremy at n-heptane.com
Tue May 20 03:29:18 EDT 2008


Hello,

You *can* get things out of the IO monad with:

System.IO.Unsafe.unsafePerformIO :: IO a -> a

but, in almost all cases you shouldn't. The name 'unsafe' is there for
a reason :)

The IO monad does not explicitly contain any state -- it's entire
purpose is to ensure that operations which can have side-effects
happen in a specific order. So, if you do:

 do writeFile "foo.txt"
    moveFile "foo.txt" "bar.txt"

it is *really* important than the writeFile is run first and moveFile
is run second. If you did:

 let a = unsafePerformIO (writeFile "foo.txt")
     b = unsafePerformIO (moveFile "foo.txt" "bar.txt")
 in
  (a,b)

Then the order the actions occured in would depend on how the result
was used. You will notice that many of the monads have a functions
like, execWriter, execReader, execState, etc, to convert the monadic
values into non monadic values. If you create your own monad you can
make it 'one-way' by simply not exporting execYourMonad. Of course,
that may make your monad pretty useless. The IO monad is useful
because the code that calls main knows what to do with something of
type 'IO ()'.

The exact internals of the IO monad depend on the compiler, but it is
usually a bit like:

newtype RealWorld = RealWorld
newtype IO a = IO { unIO :: RealWorld -> (a, RealWorld) }

instance Monad IO where
   return a = IO (\rw -> (a, rw))
   m >>= f = IO $ \rw ->
          let (a, rw') = (unIO m) rw
	  in (unIO (f a)) rw'

(or something close to that).

RealWorld is basically just a token that gets pass around to enforce
the ordering of the IO actions. It contains no explicit
state. However, it implicitly represents that state of everything in
the real world (file handles, RAM, what you are about to type on the
keyboard).

This is why you might still consider Haskell to be 'pure' even with
the addition of the IO monad. main is basically a function:

main :: RealWorld -> ((), RealWorld)
main = ...

and functions like getLine would be like:

getLine :: RealWorld -> (String, RealWorld)

In theory, getLine takes the RealWorld that was passed in, extracts
the String, and returns a new RealWorld where the String has been
read. 

Assuming you pass in the same "real world" you should always get the
same answer. However, there in no instance of Eq for the real world,
so ensuring things are equal is left up to the operator. For a simple
application, such as a haskell version of 'echo', that might just mean
ensuring it is called with the same command-line arguments, enough
free memory, etc. For other apps, it would be impossible to recreate
the a suitably equal "real world".

In summary, the IO monad is pretty much like an other Monad, and there
is even a function to get things out of the IO monad. But, for the
most part, we pretend that unsafePerformIO does not exist, because
that lets us safely pretend that the RealWorld type actually does
contain (and determine) the state of the real world. If you want to
use unsafePeformIO, it is your responsibility to ensure the illusion
is not destroyed.

In concurrent clean, they use a similar abstraction, but instead of
using monads to pass around RealWorld, they explicity pass it
around. A bit like:

main world = 
  let world' = getLine world
      world'' = putStr "foo" world'
  in
   world''

However, you have to be careful not to write:

main world = 
  let world' = getLine world
      world'' = putStr "foo" world'
      world''' = putStr "boo" world'
  in
   (world'', world''')

because that would create two parallel universes, one where "foo" was
written stdout and one where "boo" was written to stdout. Because they
both start with the same world' but ended up with different worlds
(aka, world'' and world'''). The designers of clean decided that
letting programmers create parallel universes was too much power and
might destroy the space-time continuum. So the clean type system uses
'uniqueness typing' to ensure that you can only alter world' once,
limiting your impact to a single universe.

So, if you tried to compile the second example, it would abort when it
saw, putStr "boo" world', because you already altered that state of
the universe in the previous line. You don't get to travel back in
time and make a second parallel universe where the other choice was
taken instead.

Anyway, I hope this helps.
j.

At Tue, 20 May 2008 07:54:33 +0200,
Zsolt SZALAI wrote:
> 
> Hi!
> 
> Now, i'm getting familiar with monads, but there is a little discredit
> about one-way monads.
> For example, in monads presented in Monads for Functional Programming
> by  Philip Wadler, they are all two-way monads, internal data can be
> extracted from the monad, and these data, call them state, are in deed
> _local_ to a function using the monadic computation, so the state
> there is just a little magic, and they are really just functions(as in
> a pure language).
> An other example is Random. I've figured out, that when initializing a
> generator, it uses the actual timestamp and cputime to initialize. If
> it wouldnt happen, two distinct uses of Random in a program would
> result the same random number sequence.
> 
> Here comes IO and one-way monads, where the internal state can not be
> extacted, and seems, that the internal data is global to the program.
> Hows that could be? Is it just because main::IO() or because the
> implementation of IO uses external C functions and there are no
> internal state in the monad itself at all?
> And why one can not write a function that makes an IO computation and
> the return type does not include and IO contructor? It is a feature of
> the language and specific to IO, or anybody  could write a monad with
> this property(one-way), assuming the implementation does not use
> external languages?
> Or the one-way property is just that, there is no such functions, that
> allow extracting internal data?
> Also, is there any other monad, that has the one-way property?
> 
> Thanks,
> --
> Zsolt
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list