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

Kevin Jardine kevinjardine at gmail.com
Fri Jul 30 05:32:34 EDT 2010


I think that these are therefore the responses to the original
questions:

> I am of the understanding that once you into a monad, you cant get out of it?

You can run monadic functions and get pure results. So it looks like
in that sense you can "get out of it".

>  Is this breaking the "monad" scheme?

Apparently not. Although functions that do this for monads that have
side effects are unsafe, so use them carefully.

Cheers,
Kevin

On Jul 30, 11:17 am, Anton van Straaten <an... at appsolutions.com>
wrote:
>  >> 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?
>
>  >> Oops, I should have written
>  >>
>  >> IO ByteString
>  >>
>  >> as the State stuff is only *inside* execState.
>  >>
>  >> But a monad none the less?
>
> State is a pure monad that doesn't involve IO.  It works by threading a
> state value through the monadic computation, so old states are discarded
> and new states are passed on, and no actual mutation is involved.  This
> means there's no need to bring IO into it.
>
> If you look at the type signature of execState, you'll see that unless
> the state type 's' involves IO, the return type can't involve IO.
>
> It can help to run little examples of this.  Here's a GHCi transcript:
>
> Prelude> :m Control.Monad.State
> Prelude Control.Monad.State> let addToState :: Int -> State Int ();
> addToState x = do s <- get; put (s+x)
> Prelude Control.Monad.State> let mAdd4 = addToState 4
> Prelude Control.Monad.State> :t mAdd4
> m :: State Int ()
> Prelude Control.Monad.State> let s = execState mAdd4 2
> Prelude Control.Monad.State> :t s
> s :: Int
> Prelude Control.Monad.State> s
> 6
>
> In the above, addToState is a monadic function that adds its argument x
> to the current state.  mAdd4 is a monadic value that adds 4 to whatever
> state it's eventually provided with.  When execState provides it with an
> initial state of 2, the monadic computation is run, and the returned
> result is 6, which is an Int, not a monadic type.
>
> > 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?
>
> If you use a function like execState (depending on the monad), you can
> typically run a monadic computation and get a non-monadic result.
> However, if you're doing that inside a monadic function, you still have
> to return a value of monadic type - so typically, you use 'return',
> which lifts a value into the monad.
>
> > I know that unsafePerformIO can do this, but I thought that was a bit
> > of a hack.
>
> IO is a special monad which has side effects.  unsafePerformIO is "just"
> one of the functions that can run IO actions, but because the monad has
> side effects, this is unsafe in general.  With a pure monad like State,
> there's no such issue.
>
> Anton
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list