
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

In the code below the "RandT ..." monad transformer is replaced by a
simple "State ..." monad. And the Animal is now a type family with the
brain being one of it's instances. This way functions that work on
specific parts of the animal will have "Animal Brain" in the signature
and ones that work with all parts of the animal will have "Animal a".
-deech
{-# LANGUAGE PackageImports, RankNTypes, FlexibleContexts,
TypeFamilies, EmptyDataDecls #-}
import "mtl" Control.Monad.State
import Control.Monad.Random
type Neuron = Int
data Brain
type family Animal a
type instance Animal Brain = [Neuron]
stimulateBrain :: (RandomGen g) => Int -> [Double] -> State (Animal Brain,g) ()
stimulateBrain n xs = do
(a,g) <- get
g' <- return $ next g
a' <- return $ stimulate n xs g' a
put (a',g')
where
next :: (RandomGen g) => g -> g
next = snd . split
stimulate :: (RandomGen g) => Int -> [Double] -> g -> Animal Brain ->
Animal Brain
stimulate n xs g neurons = undefined
On Fri, Dec 17, 2010 at 10:11 PM, Amy de Buitléir
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Actually "stimulateBrain" could be refactored to :
stimulateBrain :: (RandomGen g) => Int -> [Double] -> State (Animal Brain,g) ()
stimulateBrain n xs = do
modify (\(a,g) -> (stimulate n xs g a , next g))
where
next :: (RandomGen g) => g -> g
next = snd . split
-deech
On Sat, Dec 18, 2010 at 11:30 PM, aditya siram
In the code below the "RandT ..." monad transformer is replaced by a simple "State ..." monad. And the Animal is now a type family with the brain being one of it's instances. This way functions that work on specific parts of the animal will have "Animal Brain" in the signature and ones that work with all parts of the animal will have "Animal a".
-deech
{-# LANGUAGE PackageImports, RankNTypes, FlexibleContexts, TypeFamilies, EmptyDataDecls #-} import "mtl" Control.Monad.State import Control.Monad.Random
type Neuron = Int data Brain
type family Animal a type instance Animal Brain = [Neuron]
stimulateBrain :: (RandomGen g) => Int -> [Double] -> State (Animal Brain,g) () stimulateBrain n xs = do (a,g) <- get g' <- return $ next g a' <- return $ stimulate n xs g' a put (a',g') where next :: (RandomGen g) => g -> g next = snd . split
stimulate :: (RandomGen g) => Int -> [Double] -> g -> Animal Brain -> Animal Brain stimulate n xs g neurons = undefined
On Fri, Dec 17, 2010 at 10:11 PM, Amy de Buitléir
wrote: 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thank you so much, deech and Brent. You've both given me good ideas, not just for this particular component, but for other parts of my code too.
participants (3)
-
aditya siram
-
Amy de Buitléir
-
Brent Yorgey