[Haskell-cafe] Re: Can we come out of a monad?

Ertugrul Soeylemez es at ertes.de
Sun Aug 1 06:36:33 EDT 2010


Kevin Jardine <kevinjardine at gmail.com> wrote:

> Or is it possible to call a function in a monad and return a pure
> result? I think that is what the original poster was asking?
>
> I know that unsafePerformIO can do this, but I thought that was a bit
> of a hack.

What most people forget is that in Haskell there is /no/ impure stuff
involved.  Even the IO monad is completely pure.  The unsafePerformIO
function breaks this rule, hence it's "unsafe".  Take as an example the
following toy implementation of the 'cat' program:

  main :: IO ()
  main = do
    args <- getArgs
    case args of
      []    -> getContents >>= putStr
      files -> mapM_ (readFile >=> putStr) files

Here the domain-specific language, which is defined by the IO monad, is
used to model a computation, which interacts with the outside world.
All of this code is completely pure.  But the DSL models computations,
which may change the world during (>>=).

Even the 'putStr' function is well referentially transparent.  You can
safely replace its application by its result.  But note that its result
is /not/ of type (), but of type 'IO ()'.  Its result is an IO
computation, i.e. a statement in the DSL defined by IO.  As a clarifying
example look at this function:

  printAndSquare :: Integer -> IO Integer
  printAndSquare x = print x >> return (x^2)

If you write 'printAndSquare 5' somewhere in your code, then you're
calling the function 'printAndSquare' with the argument 5, which gives a
result of type 'IO Integer'.  You can safely replace any occurence of
'printAndSquare 5' by its result.  The following four computations are
equivalent:

  fmap read getLine >>= printAndSquare >>= print

  fmap read getLine >>= (\x -> print x >> return (x^2)) >>= print

  do num <- fmap read getLine
     square <- printAndSquare num
     print square

  do num <- fmap read getLine
     square <- print num >> return (num^2)
     print square

I have made direct use of the referential transparency rule.  The result
of applying the function 'printAndSquare' is not the same as the
run-time result of the computation, which it expresses.

Everything between (>>=) is pure.  You're dealing with normal Haskell
expressions here, and there is no magic involved, since IO is really
just a language.  You never get "out of IO", because as soon as you do
'<-' in do-notation, you are giving the result of an IO computation a
certain name.  Instead of saying

  getContents >>= putStr

you say

  do content <- getContents
     putStr content

The only difference is that you have named the result explicitly.  Don't
try to give this operational meaning.  It's just a different way to
express the same statement in the IO language.

If you want to write a function, which returns a random boolean, the
correct way to do it is one of these:

  randomBool :: RngState -> (Bool, RngState)
  randomBool :: State RngState Bool
  randomBool :: IO Bool

In fact, the two latter examples aren't even functions.  They are simply
values -- statements in a domain-specific language.  For the second
example it's the 'State RngState' language, for the third example it's
the IO language.  The following is also simply a value:

  randomBool :: Bool

But it's really a value of type Bool.  It's not a statement in some DSL.
It's not a computation.  It's not a function.  Just a constant value.


> I'm still trying to understand how monads interact with types so I am
> interested in this as well.

A monad is a type constructor, which is an instance of the Monad class
and which obeys the monad laws.  That's it.


> On Jul 30, 10:11 am, Kevin Jardine <kevinjard... at gmail.com> wrote:
> > Oops, I should have written
> >
> > IO ByteString
> >
> > as the State stuff is only *inside* execState.
> >
> > But a monad none the less?
> >
> > Kevin
> >
> > On Jul 30, 9:59 am, Kevin Jardine <kevinjard... at gmail.com> wrote:
> >
> > > The original poster states that the type of modifiedImage is "simply
> > > ByteString" but given that it calls execState, is that possible?
> >
> > > Would it not be State ByteString?
> >
> > > Kevin
> >
> > > On Jul 30, 9:49 am, Anton van Straaten <an... at appsolutions.com> wrote:
> >
> > > > C K Kashyap wrote:
> > > > > In the code here -
> > > > >http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
> > > > > If I look at the type of modifiedImage, its simply ByteString - but
> > > > > isn't it actually getting into and back out of the state monad? I am of
> > > > > the understanding that once you into a monad, you cant get out of it? Is
> > > > > this breaking the "monad" scheme?
> >
> > > > modifiedImage uses the execState function, which has the following type:
> >
> > > >    execState :: State s a -> s -> s
> >
> > > > In other words, it applies a State monad value to a state, and returns a
> > > > new state.  Its entire purpose is to "run" the monad and obtain the
> > > > resulting state.
> >
> > > > A monadic value of type "State s a" is a kind of delayed computation
> > > > that doesn't do anything until you apply it to a state, using a function
> > > > like execState or evalState.  Once you do that, the computation runs,
> > > > the monad is "evaluated away", and a result is returned.
> >
> > > > The issue about not being able to escape that (I think) you're referring
> > > > to applies to the functions "within" that computation.  A State monad
> > > > computation typically consists of a chain of monadic functions of type
> > > > (a -> State s b) composed using bind (>>=).  A function in that composed
> > > > chain has to return a monadic value, which constrains the ability of
> > > > such a function to escape from the monad.
> >
> > > > Within a monadic function, you may deal directly with states and
> > > > non-monadic values, and you may run functions like evalState or
> > > > execState which eliminate monads, but the function still has to return a
> > > > monadic value in the end, e.g. using "return" to lift an ordinary value
> > > > into the monad.
> >
> > > > Anton
> > > > _______________________________________________
> > > > Haskell-Cafe mailing list
> > > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > > _______________________________________________
> > > Haskell-Cafe mailing list
> > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/




More information about the Haskell-Cafe mailing list