[Haskell-cafe] How do I include polymorphic function type signatures in a data element ?

Crypt Master cryptmaster at hotmail.com
Tue Jul 20 12:01:41 EDT 2004


Hi

How do I include polymorphic function type signatures in a data element ?

Exmaple:

<CODE>
type Fitness = Integer
data Population a = Population [(Fitness, a)]
                    deriving (Show)

data GAParams = GAParams { randomNums :: [Integer] ,
                           someFunc :: (Int->Int->(Population a))}
</CODE>

This errors with parse input error on '}'. However something like this works 
fine:

<CODE>
data GAParams = GAParams { randomNums :: [Integer] ,
                           someFunc :: (Int->Int->GAParams) }
/<CODE>

I am just having issues with polymorphic types.

Any ideas ?


The context is included below in case it helps:

<CODE>
import Random

type Fitness = Integer
data Population a = Population [(Fitness, a)]
                    deriving (Show)

data GAParams = GAParams { randomNums :: [Integer] ,
                           someFunc :: (Int->Int->GAParams) }

gaSolutionSpaceFrom :: Population a -> GAParams -> [Population a]
gaSolutionSpaceFrom p gaParams = (evolvePopulation p gaParams) : 
gaSolutionSpaceFrom p newGAParams
                              where
                                 (r,rs) = splitAt (length pl) (randomNums 
gaParams)
                                 Population pl = p
                                 newGAParams = (gaParams{randomNums=rs})

evolvePopulation :: Population a -> GAParams -> Population a
evolvePopulation p gaParams = (mutate (cross (select p)))

selectMatingPoolByRouletteWheel :: Population a -> GAParams -> Population a
selectMatingPoolByRouletteWheel (Population popList) gaParams =
     (Population [ (rwSelect rw rnd) | rnd <- rndNums ])
        where
            rw = createRW (Population popList)
            rndNums = (randomNums gaParams)

rwSelect :: [(Fitness, a)] -> Fitness -> (Fitness, a)
rwSelect [] _ = error "rwSelect random number outside roullete wheel range 
or list empty"
rwSelect ((x,a):xs) z = if x <= z then
                         rwSelect xs z
                          else
                            (x,a)

createRW                 :: Population a -> [(Fitness, a)]
createRW (Population xs) =  (scanl1 f xs)
                             where f (n,a) (m,b) = (n + m, a)
select p = p
cross  p = p
mutate p = p

_________________________________________________________________
MSN 8 with e-mail virus protection service: 2 months FREE* 
http://join.msn.com/?page=features/virus



More information about the Haskell-Cafe mailing list