[Haskell-cafe] Catering for similar operations with and without state

Phil phil at beadling.co.uk
Mon Jun 15 20:23:12 EDT 2009


Hi,

I'm trying to think around a problem which is causing me some difficulty in
Haskell.

I'm representing a stateful computation using a State Transform - which
works fine.  Problem is in order to add flexibility to my program I want to
performs the same operation using different techniques - most of which
require no state.

My program at the moment is a stack of state monads/transforms.  I have a
random number generator as a state monad (seed=state), feeding a Box Muller
(normal) generator implemented as a state transform (state is 'maybe'
normal, so it only spits out 1 normal at a time), which in turn feeds
another state machine.

This all works fine, but I want to add flexibility so that I can chop and
change the Box Muller algorithm with any number of other normal generators.
Problem is most of them do not need to carry around state at all.
This leaves me with a messy solution of implementing lots of state monads
that don't actually have a state, if I want to maintain the current
paradigm.

This strikes me as really messy - so I'm hoping someone can point me in the
direction of a more sensible approach?

Currently I have my Box Muller implemented as below - this works:

class NormalClass myType where
  generateNormal :: myType Double

type BoxMullerStateT = StateT (Maybe Double)
type BoxMullerRandomStateStack = BoxMullerStateT MyRngState

instance NormalClass BoxMullerRandomStateStack where
  generateNormal = StateT $ \s -> case s of
                  Just d  -> return (d,Nothing)
                  Nothing -> do qrnBaseList <- nextRand
                                        let (norm1,norm2) = boxMuller (head
qrnBaseList) (head $ tail qrnBaseList)
                                        return (norm1,Just norm2)


But say I have another instance of my NormalClass that doesn't need to be
stateful, that is generateNormal() is a pure function.  How can I represent
this without breaking my whole stack?

I've pretty much backed myself into a corner here as my main() code expects
to evalStateT on my NormalClass:

main = do let sumOfPayOffs = evalState normalState (1,[3,5]) -- (ranq1Init
981110)
                where
                  mcState = execStateT (do replicateM_ iterations mc) 0
                  normalState = evalStateT mcState Nothing

If it wasn't for this I was thinking about implementing the IdentityT
transformer to provide a more elegant pass-through.
I've never tried designing my own Monad from scratch but this crossed my
mind as another possibillity - i.e. a Monad that either has a state of maybe
double, or has no state at all?
I may be talking rubbish here of course :-) I'm pretty daunted by where to
even start - but I want to improve this as the quick and dirty solution of
implementing a load of state monads with no state just to cater for the
above method strikes me as very ugly,  and as I can easily see ways of doing
this in C or C++, I figure there must be a better approach in Haskell - I'm
just thinking in the right way!

Any advice or hints would be great,

Cheers,

Phil.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090615/8c81c749/attachment.html


More information about the Haskell-Cafe mailing list