
Hi Man, your a genius :-) Thanks for the help , still dijesting it. Interestingly enough I was playing with how to use sacnl1 just before I got this message from you, but as you mentioned I was battling with "kind" errors so I never got to test my idea besides on paper. Am I correct in assuming that your definition of Popoulation is now using tuple and not product types ? If so it it better to use tuples ? In the book the craft of func programing, it shows product type examples like this: data People = Person Name Age type Name = String type Age = Int Later it shows polymoric definitions like this: data Pairs a = Pr a a You mentioned that I had applied the polymorphic type "a" to Fitness, but but in the above example of person and people they have done the exactly what I did ? Used a space to seperate elements. So I am a little confused as to why mine didnt work. Regarding the use of newtype and data I saw another thread on this and I will use that get some insights on the differences. Your "rw" took some following until I realised currying was invovled *grin*
rw (Population xs) = Population (scanl1 f xs) where f (n, a) = (+ n) `pair` id
Can I ask one question, I am not concerned with performance at this point, but what sort of overhead does a function like id have. It seems unneccesary to me ( I am not critising your solution, I am vert thankfull for your help ) in a large populations you will land up doing a fair amount of extra but simple "reductions" ( I hope thats the right word. ) just to "copy" the unkown "a". Or does it have to be a function for some reason and so you had to use "id" ? Thanks, S ----Original Message Follows---- Crypt Master, CM> I need to be able to work with a list of items whos CM> structure is onyl partially know. That is at the level CM> of this module I dont care about what rest of it is. CM> So I have this: < type Fitness = Integer < data Population a = Population [Fitness a] Well, first of all: this will not compile. You've declared Fitness to be an synonym of Integer and Integer is not a parametric data type, i.e. it has kind *. In your definition for Population, however, you apply Fitness to a type argument. This will give you a kind error. CM> Hopefully this reads Population is constructed using CM> the Population constructor and is a list who elements CM> each conists a fitness value and some other value. So, no, it does not. I guess this is what you want:
type Fitness = Integer data Population a = Population [(Fitness, a)] deriving (Show)
Now Population constructs a Population value from a list of which the elements are pairs of a Fitness value and a value of a specified type a. CM> Since I cant do poloymorphioc types with synonyms I CM> went with the data type. Well, actually, you can:
type Population' a = [(Fitness, a)]
but type synonyms have the restriction that they cannot be partially applied. Another option might be
newtype Population'' a = Population'' [(Fitness, a)]
which is only slightly different from the definition above involving data. CM> My current task is to build a roulette wheel CM> distribution of the fitness value. Basically I want to CM> build and incremental summing of the fitness value so CM> that each individual is paired with its upper range CM> like so CM> CM> Population [10 x, 20 y, 30 z] CM> New Population = [10 x, 20+10 y, 30+30 z] This can be accomplished by
rw :: Population a -> Population a rw (Population xs) = Population (scanl1 f xs) where f (n, a) = (+ n) `pair` id
where pair is the maps a pair of functions to a function on pairs:
pair :: (a -> c) -> (b -> d) -> (a, b) -> (c, d) f `pair` g = h where h (a, b) = (f a, g b)
A little test:
main :: IO () main = print $ rw (Population [(10, 2), (20, 3), (30, 5)])
This prints: "Population [(10,2),(30,3),(60,5)]". HTH, Stefan _________________________________________________________________ MSN 8 helps eliminate e-mail viruses. Get 2 months FREE*. http://join.msn.com/?page=features/virus

Crypt Master,
data Population a = Population [(Fitness, a)]
CM> Am I correct in assuming that your definition of CM> Popoulation is now using tuple and not product types ? Yes, you are. If you really want to use a new product, you can of course:
data FitnessProd a = FProd Fitness a data Population' a = Population' [FitnessProd a]
A pair, i.e. a binary tuple, is a product type itself, be it one with special syntax. You can think of it as being defined by < data (,) a b = (,) a b CM> If so it it better to use tuples? As always: it depends. I guess it is a design matter. If your product really represents some distinct entity, you might want to go for a new data type. If your product is merely just a pair, using tuples is more straightforward. CM> You mentioned that I had applied the polymorphic type CM> "a" to Fitness, but but in the above example of person CM> and people they have done the exactly what I did ? CM> Used a space to seperate elements. So I am a little CM> confused as to why mine didnt work. As I said, you encountered a kind error. You have Paul Hudak's book, haven't you? In section 18.3 he explains how kinding works. You may want to read about that. To see where things went wrong, examine your definitions once again. First, you defined Fitness to be a synonym of Integer.
type Fitness = Integer
Integer is a data type that does not take any type arguments. You can think of it as being defined by < data Integer = ... | -2 | -1 | 0 | 1 | 2 | ... A type constructor that does not take any type arguments to produce a type is said to be of kind *. Here, Integer is of kind *, and, therefore, so is Fitness. Now consider, the following type:
data Fork a = Fork a a
The type constructor Fork takes one type argument and therefore it has a function kind: k -> *, for some k. From the right-hand side we can infer that k is *, so the kind of Fork is * -> *. This means that the type constructor Fork can be applied on a type of kind *, for example Integer.
type ForkedInteger = Fork Integer
However, Fitness, which is of kind *, cannot be applied to any type argument, so the following is illegal: < type FitnessedInteger = Fitness Integer -- kind error! This is exactly what you tried: applying Fitness to some other type. CM> Can I ask one question, I am not concerned with CM> performance at this point, but what sort of overhead CM> does a function like id have. It seems unneccesary to CM> me ( I am not critising your solution, I am vert CM> thankfull for your help in a large populations you CM> will land up doing a fair amount of extra but simple CM> "reductions" ( I hope thats the right word. ) just to CM> "copy" the unkown "a". Or does it have to be a CM> function for some reason and so you had to use "id" ?
rw (Population xs) = Population (scanl1 f xs) where f (n, a) = (+ n) `pair` id pair :: (a -> c) -> (b -> d) -> (a, b) -> (c, d) f `pair` g = h where h (a, b) = (f a, g b)
Well, the unknown a-values should be transferred from the input list to the output list, so there's not much choice here. In fact, the f function does nothing more than
f :: (Fitness, a) -> (Fitness, a) -> (Fitness, a) f (m, _) (n, a) = (n + m, a)
which seems quite minimal. HTH, Stefan

Crypt Master writes:
Am I correct in assuming that your definition of Popoulation is now using tuple and not product types ?
Actually, tuples *are* product types. They just have some syntactic sugar defined for them in the language. For example, Main> ('x',5) :: (Char,Int) ('x',5) Main> ('x',5) :: (,) Char Int ('x',5)
If so it it better to use tuples ? In the book the craft of func programing, it shows product type examples like this:
data People = Person Name Age type Name = String type Age = Int
Later it shows polymoric definitions like this:
data Pairs a = Pr a a
You mentioned that I had applied the polymorphic type "a" to Fitness, but but in the above example of person and people they have done the exactly what I did ? Used a space to seperate elements. So I am a little confused as to why mine didnt work.
Pairs has kind * -> *. Given a type, it constructs a new type. (Pr has type a -> a -> Pairs a. For any type a, it takes two values of type a and returns a value of type Pairs a). Your code looked like: type Fitness = Integer data Population a = Population [Fitness a] The kinds involved are: Population :: * -> * Fitness :: * [] :: * -> * It's the list type constructor that's causing you problems. Specifically, what you have is equivalent to: data Population a = Population ([] (Fitness a)) It's trying to apply a to Fitness, which doesn't work because Fitness is a type, not a type constructor. What you need is a single type containing a and Fitness. You could either declare a new one and use that: data IndividualWithFitness a = IWF a Fitness data Population a = Population [IWF a] -- equivalent to: -- Population a = Population ([] (IWF a)) Or just use a generic pair type: data Population a = Population [(a,Fitness)] -- equivalent to: -- Population a = Population ([] ((,) a Fitness)) (,) has kind * -> * -> *, so it takes two type arguments ("a" and "Fitness") and constructs a new one ("(a,Fitness)").
rw (Population xs) = Population (scanl1 f xs) where f (n, a) = (+ n) `pair` id
Can I ask one question, I am not concerned with performance at this point, but what sort of overhead does a function like id have. It seems unneccesary to me ( I am not critising your solution, I am vert thankfull for your help ) in a large populations you will land up doing a fair amount of extra but simple "reductions" ( I hope thats the right word. ) just to "copy" the unkown "a". Or does it have to be a function for some reason and so you had to use "id" ?
You need id if you're using pair, because pair requires two functions.
If that turned out to be a performance bottleneck, you could factor out
pair and write f directly:
rw (Population xs) = Population (scanl1 f xs)
where
f (n,a) (m,b) = (n + m, a)
--
David Menendez

David Menendez wrote:
[...] If that turned out to be a performance bottleneck, you could factor out pair and write f directly: [...]
... or directly complain to your compiler supplier if the compiler in question does not do this simple transformation for you. :-) <sigh> I always get a bad feeling when people start to think about efficiency right from the beginning: First get your program correct and readable, then measure, and only then optimize (if at all). Programmers are notoriously bad when guessing about efficiency, which even more true for lazy functional programs. </sigh> Let's e.g. have a look at the code generated by GHC for the "inefficient" version: --------------------------------------------------------------------------------- helper :: (Fitness, a) -> (Fitness, a) -> (Fitness, a) helper = \ds eta -> case ds of (f, a) -> case eta of (g, b) -> (g `plusInteger` f, b) rw :: Population a -> Population a rw = \ds -> case ds of Population xs -> Population (case xs of (x:xs1) -> scanl helper x xs1 [] -> []) --------------------------------------------------------------------------------- Or in a more readable, but equivalent, form: --------------------------------------------------------------------------------- helper :: (Fitness, a) -> (Fitness, a) -> (Fitness, a) helper (f, a) (g, b) = (g `plusInteger` f, b) rw :: Population a -> Population a rw (Population xs) = Population (case xs of (x:xs1) -> scanl helper x xs1 [] -> []) --------------------------------------------------------------------------------- What has happened? `pair', `id', and `scanl1' were completely inlined and instead of the overloaded (+), an Integer-specific addition was chosen (`plusInteger', it's not the real name, just something for presentation purposes). Although these are all only O(1) optimizations (nothing "really clever"), one can hardly do better by hand... So keep the program in a form which is most comprehensible, even if this seems to imply some "superfluous" things at first. This enables you to have more time for more interesting things which could really have some effect on performance, like clever algorithms etc. Cheers, S.

Sven Panne writes:
David Menendez wrote:
[...] If that turned out to be a performance bottleneck, you could factor out pair and write f directly: [...]
.... or directly complain to your compiler supplier if the compiler in question does not do this simple transformation for you. :-)
Sure. It's a longer-term strategy, though. :-)
Let's e.g. have a look at the code generated by GHC for the "inefficient" version:
Neat! Are you getting this from -ddump-simpl?
--------------------------------------------------------------------- helper :: (Fitness, a) -> (Fitness, a) -> (Fitness, a) helper = \ds eta -> case ds of (f, a) -> case eta of (g, b) -> (g `plusInteger` f, b)
rw :: Population a -> Population a rw = \ds -> case ds of Population xs -> Population (case xs of (x:xs1) -> scanl helper x xs1 [] -> []) ---------------------------------------------------------------------- <snip> What has happened? `pair', `id', and `scanl1' were completely inlined and instead of the overloaded (+), an Integer-specific addition was chosen (`plusInteger', it's not the real name, just something for presentation purposes). Although these are all only O(1) optimizations (nothing "really clever"), one can hardly do better by hand... So keep the program in a form which is most comprehensible, even if this seems to imply some "superfluous" things at first. This enables you to have more time for more interesting things which could really have some effect on performance, like clever algorithms etc.
I completely agree.
Actually, I might have suggested using (***) or first from Control.Arrow
rather than defining pair, since they effectively do the same thing. But
looking at the Core output I see that:
rw2 :: Population a -> Population a
rw2 (Population xs) = Population (scanl1 f xs)
where
f (n,a) = (+n) *** id
yields (if I'm interpreting it right):
helper2 = \ds eta ->
case ds of
(n,a) -> ( case eta of
(x,y) -> x `plusInt` y
, case eta of
(x,y) -> y
)
rw2 = \ds ->
case ds of
Population xs ->
Population (case xs of
(x:xs1) -> scanl helper2 x xs1
[] -> []
)
I don't know what to make of that. Semantically, helper2 is identical to
helper, but I'm not brave enough to look at the C output to see if they
produce different results.
--
David Menendez

David Menendez wrote:
Neat! Are you getting this from -ddump-simpl?
Yep, that's the most readable intermediate form to look at IMHO.
[...] helper2 = \ds eta -> case ds of (n,a) -> ( case eta of (x,y) -> x `plusInt` y , case eta of (x,y) -> y ) [...] I don't know what to make of that. Semantically, helper2 is identical to helper, but I'm not brave enough to look at the C output to see if they produce different results.
Well, they are almost equivalent: If you keep the second element of the result of helper2 alive without having it evaluated, you keep the first element of the second argument of helper2 alive, too. Depending on the usage of helper2, this might make a difference in the space behaviour, but in our current example it doesn't matter very much. If in doubt, use e.g. GHC's profiling facility, which can produce nice & colourful graphs, useful for impressing your friends... :-) Cheers, S.
participants (4)
-
Crypt Master
-
David Menendez
-
Stefan Holdermans
-
Sven Panne