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

Anton van Straaten anton at appsolutions.com
Sat Jul 31 06:08:12 EDT 2010


Jason Catena wrote:
> On Jul 30, 11:17 am, Anton van Straaten wrote:
>> 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
> 
> By this example State doesn't seem to give you anything more than a
> closure would

Sure, the example was just intended to show a value being extracted from 
a monad, which was what was being asked about.

> since it doesn't act like much of an accumulator (by,
> for example, storing 6 as its new internal value).

Actually, in the example, the "put (s+x)" does store 6 as the new value 
of the state.  It's just that the example doesn't do anything with this 
new state other than extract it using execState.

You can use functions like addToState in a larger expression, though. 
E.g., the following updates the internal state on each step and returns 14:

   execState (addToState 4 >> addToState 5 >> addToState 3) 2

> Could you use State for something like storing the latest two values
> of a Fibonacci series?
>
> For example, each time you call it, it
> generates the next term, discards the oldest term, and stores the
> newly-generated term?

You should really try to implement this as an exercise, in which case 
don't read any further!

*

*

*

(OK, now I've assuaged my guilt about providing answers)

Here's the simplest imaginable implementation of your spec (the type 
alias is purely for readability):

type Fib a = State (Integer, Integer) a

fibTerm :: Fib Integer
fibTerm = do
     (a,b) <- get
     put (b,a+b)
     return a

When you run the Fib monad, you provide it with a pair of adjacent 
Fibonacci numbers such as (0,1), or, say, (55,89).

If you only run one of them, all it does is return the first element of 
the state it's provided with.  Chaining a bunch together gives you a 
Fibonacci computation.

For convenience and readability, here's a runner for the Fib monad:

runFib :: Fib a -> a
runFib = flip evalState (0,1)

> And could you then use this Fibonacci State monad in a lazy
> computation, to grab for example the first twenty even Fibonacci
> numbers, without computing and storing the series beyond what the
> filter asks for?

Easily:

fibList :: [Integer]
fibList = runFib $ sequence (repeat fibTerm)

main = print $ take 20 (filter even fibList)

> We can generate Fibonacci series double-recursively in a lazy
> computation.  Would it be more or less efficient to use a Fibonacci
> State monad instead?  

If you're thinking of comparing to a non-memoizing implementation, then 
the Fib monad version is a bajillion times faster, just because it 
avoids repeated computation.

But your mention of "lazy" makes me think you might be referring to a 
list-based implementation (since laziness doesn't help a naive 
implementation at all).  Using lists is much more efficient since it 
effectively memoizes.  E.g. this:

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

...is faster and more memory efficient than the Fib monad, but not so 
much that it'd matter for most purposes.  Fib's performance could be 
improved in various ways, too.

> Would the State implementation provide a larger
> range before it blew the stack (which tail-recursion should prevent),
> or became too slow for impatient people?

The Fib monad performs very well.  "fib 50000" takes 1.6 seconds on my 
machine.  The non-memoizing double-recursing version can only get to 
about fib 27 in the same time, with similar memory usage, but that may 
not have been what you wanted to compare to.

> Would Haskell memoize already-generated values in either case?  Could
> we write a general memoizer across both the recursive and State
> implementations, or must we write a specific one to each case?

By using a list in fibList above, we get memoization for free.  Although 
it may not be quite what you were asking for, lists in Haskell can be 
thought of as a kind of general memoizer.

Anton



More information about the Haskell-Cafe mailing list