[Haskell-beginners] RandT

Amy de Buitléir amy at nualeargais.ie
Sat Dec 18 05:11:02 CET 2010


The example below shows part of the architecture I'm using for an alife project.

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

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 tried doing that, but I couldn't figure out the syntax. The closest
I got was when I defined a "type Brain g a = (RandomGen g) => RandT g
(State [Neuron]) a". But that a specifies a result type, which doesn't
make sense to me for a record component.

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



More information about the Beginners mailing list