[Haskell-beginners] RandT
aditya siram
aditya.siram at gmail.com
Sun Dec 19 06:40:58 CET 2010
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 <aditya.siram at gmail.com> wrote:
> 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 <amy at nualeargais.ie> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
More information about the Beginners
mailing list