[Haskell-beginners] If I only had a brain

aditya siram aditya.siram at gmail.com
Sun Dec 12 21:53:20 CET 2010


Does this help? I don't know what Neuron is so I've made it an Int to
get the code to compile.

Other than that it is my understanding that if you just want to alias
an existing type using "type ..." is better than "data ..." which
creates a fresh type.

Does this help?
-deech

{-# LANGUAGE PackageImports #-}
import Control.Monad.Random
import "mtl" Control.Monad.State
type Neuron = Int
type Brain g a = (RandomGen g) => RandT g (State [Neuron]) a

stimulate :: Int -> [Double] -> Brain g ()
stimulate = undefined

On Sun, Dec 12, 2010 at 2:26 PM, Amy de Buitléir <amy at nualeargais.ie> wrote:
> I have a class with some functions that have type signatures of the form
>
>  (RandomGen g) => some parameter types -> RandT g (State [Neuron]) something
>
> For example:
>
>  stimulate :: (RandomGen g) => Int -> [Double] -> RandT g (State [Neuron]) ()
>
> That "RandT g (State [Neuron])" is my implementation of a "brain", so
> I'd like to call it that. I tried:
>
>  data (RandomGen g) => Brain g a = RandT g (State [Neuron]) a
>
> But I got this error:
>
>    `State [Neuron]' is not applied to enough type arguments
>    Expected kind `?', but `State [Neuron]' has kind `* -> *'
>    In the type `State [Neuron]'
>    In the definition of data constructor `RandT'
>    In the data type declaration for `Brain'
>
> Do I need higher ranked types or existential types in order to do
> that? Or am I going about this the wrong way?
>
> Thank you in advance,
> Amy
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list