[Haskell-beginners] RandT

Brent Yorgey byorgey at seas.upenn.edu
Sun Dec 19 18:29:46 CET 2010


On Sat, Dec 18, 2010 at 04:11:02AM +0000, Amy de Buitléir wrote:
> 
> Q2: The "Animal" type includes a "brain" component. I implemented that
> as a simple list, but perhaps it would be better to use a monad
> here?

I am not 100% sure I understand this question, but I'm pretty sure the
answer is "no", the way you have defined the Animal type looks fine to
me.

> Q1: My implementation of "simulateBrain" seems clumsy. Is there a
> better way to do this?

Well, it's fine for what it is, but I would generalize it a bit, to
make it more widely applicable.

The key challenge is that stimulateBrain is supposed to be a
computation using a whole Animal as state, but it is to be defined in
terms of a computation operating simply on the Brain as state.
Unfortunately that means the types will not match, so we need some
sort of adapter, as you figured out.  But this problem is not specific
to Animal and Brain: what if later we wanted to use a computation
which has access only to the Pancreas, etc.?

We can define a generic adapter as follows:

withComponent :: (RandomGen g) => 

  -- | "Extractor" function to allow us to extract the piece of state s'
  --   from the larger state s
  (s -> s') ->

  -- | "Setter" function to update the larger state with a new s'
  (s' -> s -> s) ->

  -- | The state computation to run over the smaller state...
  RandT g (State s') a ->

  -- | ...which we can now use as a state computation over the larger state
  RandT g (State s) a
withComponent extract set m = do
  s <- get
  g <- getSplit
  let (a, s') = runState (evalRandT m g) (extract s)
  put $ set s' s
  return a


Now stimulateBrain is just

stimulateBrain :: (RandomGen g) => Int -> [Double] -> RandT g (State Animal) ()
stimulateBrain n xs = withComponent brain (\b a -> a { brain = b }) (stimulate n xs)

and you can also easily write stimulatePancreas or whatever.

We can generalize this further in two ways, which I will leave for you
to explore if you are interested:

  (1) use something like data-accessor for automatically deriving the
      'extractor' and 'setter' functions.
  (2) generalizing withComponent so that it works with other monad stacks.

-Brent


> 
> Thank you,
> Amy
> 
> ----- SAMPLE CODE -----
> 
> {-# LANGUAGE PackageImports, RankNTypes, FlexibleContexts #-}
> 
> import "mtl" Control.Monad.State
> import Control.Monad.Random
> 
> type Neuron = Int -- The real type is more complex
> 
> -- An "Alife" animal
> data Animal = Animal
>   {
>      brain :: [Neuron]
>      -- There are other fields too, of course
>   } deriving (Show, Read)
> 
> -- | Stimulates an animal's brain, and allows it to react.
> stimulateBrain :: (RandomGen g)
>   -- | The number of cycles
>   => Int
>   -- | The signals to apply to the sensor neurons
>   -> [Double]
>   -- | The animal
>   -> RandT g (State Animal) ()
> stimulateBrain n xs = do
>   c <- get
>   g <- getSplit
>   let b' = execState (evalRandT (stimulate n xs) g) (brain c)
>   put $ c{brain=b'}
> 
> 
> -- | Feeds some input signals into a brain, and allow it to react.
> stimulate :: (RandomGen g)
>   -- | The number of cycles
>   => Int
>   -- | The signals to apply to the sensor neurons
>   -> [Double]
>   -- | The neuron states
>   -> RandT g (State [Neuron]) ()
> stimulate k xs = return () -- The real implementation is more complex
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



More information about the Beginners mailing list