Hi Phil,

On Mon, Jun 15, 2009 at 5:23 PM, Phil <phil@beadling.co.uk> wrote:
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?

I'm interested in how you solve this, but I didn't see any replies yet so I thought I would toss in my thoughts.
 


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

class NormalClass myType where
  generateNormal :: myType Double

This type class might be at the heart of your difficulties.  I think it requires myType to have kind * -> * and it doesn't specify what the input to generateNormal should be.  I also notice you're not using it later in the example code which is another warning sign.
 

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

You used 'type' here, but I bet you want 'newtype' with the newtype deriving feature/extension.  Otherwise, this nice neat stack of transformers that you have is fixed to just one instance of NormalClass, but I suspet you may have multiple ways to generateNormal that use the same stack of transformers.
 


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 is useful to define generateNormal, then why don't you use it here?

What if we go back to your NormalClass type class and redesign it?

If we add a parameter to the type class which depends on the way you implement generateNormal I think we'd be most of the way there.  I'm also going to remove the explicit 'Double', and let that be part of the type of 'myType'.  Untested, but I think this is the syntax for using multiparameter type classes and functional dependencies:

class NormalClass seed myType | myType -> seed where
  generateNormal :: seed -> myType

type Seed = ... -- Whatever type the seed has currently

instance NormalClass Seed (Maybe Double) where
  generateNormal seed = evalState (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)) seed

-- An arbitrary 'pure' example
instance NormalClass () Double where
  generateNormal () = 1.0

Ah, now I see a problem with this approach.  You'll end up putting a newtype on the return value of generateNormal just to allow different instances.  I sort of feel like the way things are designed we are assuming we have subtyping, but Haskell doesn't have that. 



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 have a feeling I'd just 'return' the pure computations into the state monad.  My example code above seems weird and heavy weight to me.

I'd love to see what you figure you.

Jason