[Haskell-cafe] Stacking State on State.....

Phil pbeadling at mail2web.com
Sat Feb 28 07:23:51 EST 2009


Hi,

I¹ve been teaching myself Monads recently ­ with some success, but I¹ve hit
a snag when I tried to look at transformers.  I¹m not sure if the problem is
my understanding of transformer use at a theoretical level or if I¹m just
getting the syntax wrong.

If I stick a (hopefully) fairly simple example below, I was wondering if
people could comment:

Bit of background ­ I have no problem using the State Monad and find it very
useful for holding the state or say a homemade random number generator.  I
written several little bits of code like this:

VanDerCorput :: Int-> ( Double, Int )
VanDerCorput state = ( output, state+1 )
  where
    output = reflect state

getVanDC :: State Int Double
getVanFC = State VanDerCorput

This is just holding an incremental state and each time it is evaluated the
next number in the Van Der Corput sequence in generated ­ this is just a
quasi random sequence the implementation details of the sequence are
irrelevant ­ safe to say that the sequence is generated from
N=1,2,3,4.....Infinity.

The above example is so trivial it can of course be implemented easily in
purely functional code by threading the state as a parameter to a pure
function and then mapping that function to an ³iterate (+1) 1² statement,
but that is not the point of the exercise!

The next step of the program is to wrap the above example up in another
function which takes the Van Der Corput sequence as input and provides
output depending on*it¹s own* state.  I¹m passing it to a Box-Muller
transform.  Very quickly the Box-Muller transform requires TWO inputs from
VanDerCourput to produce TWO outputs itself, however we only ever need one
at a time, so the Box-Muller transform itself must hold state saying weather
it has already saved the 2nd output from a previous call, and thus doesn¹t
need to call Van Der Corput this time to produce output ­ it just returns
its own state.  

(P.S. If you know what I¹m doing from a maths point of view please ignore
the fact using a 1D Van Der Corput with Box Muller is a very bad idea ­ I
know this; I¹m keeping the example simple and Haskell orientated!)

In C-like imperative code you¹d could do something like the below ­ not that
this is massively elegant, but it shows the case-in-point:

Boxmuller()
{
    // The ³outer² states of Box Muller
    static bool myState = False;
    static double storedNormal = 0.;
    // Local copy of current state
    bool currentState = myState;
    // State always flips each run
    myState = not myState;
    // If we don¹t have a stored value from a previous run
    if currentState == False
    {
       // Generate two new Van Der Corputs ­ this would increment a state in
getNextVanDerCorput() twice ­ producing different output each time
        double rand1 = getNextVanDerCorput();
        double rand2 = getNextVanDerCorput();
        // Store one result for the NEXT run of Boxmuller()
        storedNormal = SOME_TRANSFORM(rand2);
        // Return the other
        return SOME_TRANSFORM(rand1);
    }
    // We have a leftover value from a previous run ­ get a local copy
    double currentNormal = storedNormal;
    // Reset the stored value to zero
    storedNormal = 0.;
    // Return the local copy of the stored value
    return currentNormal;
}

getNextVanDerCorput()
{
    // Starting state
    state int n = 1;
    int currentState = n;
    // Incremented each time we call the function
    ++n;
    // Value computed on the internal state of this function
    return SOME_OTHER_TRANSFORM(currentState);
}


Right, hopefully that explains explicitly what I¹m trying to do ­ apologies
for dropping into C, it¹s easier to explain in code than in words.

It struck me that this could be done using a plain and simple State Monad in
Haskell carrying ALL states for both functions around in a tuple.  This is
pretty ugly tho, and I figure both BoxMuller and VanDerCorput should have
their own internal states ­ so they can be used as building blocks in other
functionality too ­ so one big ugly Monad is bad code design, even if it
would work for this specific example.  Let¹s not go there.

The VanDerCorput building block is just the Monad at the start of this post.

The problem is ­ HOW DO I WRAP ANOTHER INDEPENDENT STATE AROUND THIS?

After some googling it looked like the answer may be Monad Transformers.
Specifically we could add a StateT transform for our Box Muller state to our
VanDerCorput State Monad.
Google didn¹t yield a direct answer here ­ so I¹m not even sure if my
thinking is correct, people describe the process of using a transform as
Œwrapping one monad in another¹ or Œthreading one monad into another¹.  What
we want to do is have some internal state controlled by an independent outer
state -  this sounds about right to me?
 
So I started playing around with the code, and got the below to compile.

test ::  StateT (Bool,Double) (State Int) Double
test = do (isStored,normal) <- get
          let (retNorm,storeNorm) = if isStored
                                    then (normal,0)
                                    else (n1,n2)
                                            where
                                              n1 = 2
                                              n2 = 3
          put (not isStored, storeNorm)
          return retNorm

Now this is incomplete and may be even wrong!  I¹ll Explain my thinking:

(Bool,Double) is equivalent to myState and storedNormal in the C example
The last Double is the return value of the BoxMuller Monad
The (State Int) is supposed to represent the VanDerCorput monad ­ but the
compiler (GHC 6.10) will only let me specify one parameter with it ­ so I¹ve
put the state and left the return type to the gods!!.... As I said this
isn¹t quite right ­ any ideas how to specify the type?

The next few lines get and test the BoxMuller state, this seems to work OK
to me, the problem is when I try to look at the STATE OF THE INTERNAL monad.
n1 and n2 should evaluate and increment the state of VanDerCorput monad ­
but I can¹t get anything to compile here.  2 and 3 are just dummy values to
make the thing compile so I could debug.

My last gripe is how to actually call this from a pure function ­ do I need
to use both evalStateT and evalState ­ I can¹t see how to initialize both
the inner and outer state ?

OK ­ I think that¹s more than enough typing, apologies for the war&peace
sized post.

Any help muchly muchly appreciated,

Many Thanks,

Phil.

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090228/47f918ef/attachment.htm


More information about the Haskell-Cafe mailing list