Re: [Haskell-cafe] introspection | meta data

2004-08-06 Thread Crypt Master
Can you name these fields?  If so, haskell has (sorta clumsy) named 
records,
and you can select and update fields by name, and you can replace
'setSFField 3 sf x' with 'sf {somefield=x}'
I did think of this, but unfortunatly my algorithm cant use names (without 
hard coding all possible combinations )

> So what is the general haskell approach to this type of 
introspection/meta
> data problem... ?

A C array of pointers maps closest to a MutableArray, which is mostly a 
list
with different performance.  Unless you're casting pointers, in which case
Dynamic types or the Generic stuff is maybe what you want.  Or a redesign 
;)
I looked at haskell arrays, but since I cant point to an element in my tuple 
it wont work out. The ANSI C use of arrays is a really simple (but nasty) 
way to provide a means for me to loop over a fixed struct record. The 
Generic library looks super, only had time to browse some slides thus far, 
but will defiantly try understand that.

As for a redesign and
Others have given good answers for this, but I suspect you may have chosen 
the
wrong data structure...
I would be keen on any ideas you have on how to design this in haskell. 
Learning to think in haskell is after all the goal :-) The example below is 
trivial and real world, both reasons why I chose to use it.

Any comments welcome, none expected :-)
Thanks,
--
I idea is to perform a search over a number fields in a hierachical fashion 
where each field can have a wild card. The real world example is printer 
selection. In a multi-national company all users tend to be on one (or a 
few) central servers, but require there printouts to come to them locally 
whereever they are. Users typically range in 1000s and so "by user" 
defintions are out.

Simplified Search fields:
Environemnt, Users, Report, Version, Host  Printer
-- --
The "most" speicific field is host on the right with it becomming more 
general moving to towards the left.

Setup data could choose to override all of report "RPT1" version "Ver1" to 
Printer "Bobs Printer"

*ALL, *ALL, "RPT1", "Ver1", "*ALL",  "Bobs Printer"
but Simon may be an exception, then a record could be added like so:
*ALL, "SIMON", "RPT1", "Ver1", *ALL, "Simons Printer"
This record would be found first for simon, but former found found for 
everyone else.

A search starts from fully specific data i.e no wild cards.
The basic algortihm I worked out is:
1. Search setup data
2. If no record found
  2a:  Set current field to most specific field (host in this case)
  2b: Toggle current field  ( if Wildcard then make it value, if value make 
it wildcard )
  2c:  if current field is *ALL goto 1 above (we stop here to perform a 
search on the current permutation)
  2d: Loop to 2b until no more fields

And my haskell working proto type is this:
module Main where
  -- Env   User Report Version HostPrinter
egdata1 = [(("PD7334EU", "*ALL",  "*ALL","*ALL", "*ALL"), "Default 
Printer"),
  (("PD7334EU", "USER1", "*ALL","*ALL", "*ALL"), 
"User1Printer"),
  (("PD7334EU", "USER2", "Report1", "Version1", "*ALL"), 
"User1Report1Printer"),
  (("PD7334EU", "*ALL",  "Report2", "*ALL", "*ALL"), 
"Report2Printer")]

type SearchFilter = (String, String, String, String, String)
type Record   = (SearchFilter, String)
findPrinter :: String -> String -> String -> String -> String -> [Record]
-> String
findPrinter env user report version host printerdata =
 findPrinter' sf sf printerdata
  where
   sf = (env, user, report, version, host)
findPrinter' :: SearchFilter -> SearchFilter -> [Record] -> String
findPrinter' ("*ALL", "*ALL", "*ALL", "*ALL", "*ALL") _ _ = ""
findPrinter' sf origsf printerdata
   | printer == ""   =  findPrinter' (toggle sf origsf 5) origsf
printerdata
   | otherwise   =  printer
 where
 printer = searchPrinter sf printerdata
searchPrinter :: SearchFilter -> [Record] -> String
searchPrinter _ [] = ""
searchPrinter sf ((x,p):xa)
   | sf == x= p
   | otherwise  = searchPrinter sf xa
toggle :: SearchFilter -> SearchFilter -> Int -> SearchFilter
toggle sf origsf 0 = sf
toggle sf origsf n
   | newValue == "*ALL"   = newSF
   | otherwise= toggle newSF origsf (n-1)
 where
  newValue = toggleField (getSFField n sf) (getSFField n origsf)
  newSF= setSFField n sf newValue
toggleField :: String -> String -> String
toggleField "*ALL" x = x
toggleField _ _ = "*ALL"
getSFField :: Int -> SearchFilter -> String
getSFField 1 (x,_,_,_,_) = x
getSFField 2 (_,x,_,_,_) = x
getSFField 3 (_,_,x,_,_) = x
getSFField 4 (_,_,_,x,_) = x
getSFField 5 (_,_,_,_,x) = x
setSFField :: Int -> SearchFilter -> String -> SearchFilter
setSFField 1 (a,b,c,d,e) f = (f,b,c,d,e)
setSFField 2 (a,b,c,d,e) f = (a,f,c,d,e)
setSFField 3 (a,b,c,d,e) f = (a,b,f,d,e)
setSFField 4 (a,b,c,d,e) f = (a,b,c,f,e)
setSFField 5 (a,b,c,d,e) f = (a,b,c,d

[Haskell-cafe] introspection | meta data

2004-08-05 Thread Crypt Master
Hi
I recently had to implement an algorthm in C, and found the time to give it 
a go in Haskell to aid in learning haskell.

I found myself "needing" runtime meta information on data types (well tuples 
which are data (a,b) = (a,b)). Does haskell allow this ?

Basically I need to loop over the fields in my record. I came up with 
functions like this:

-- Toggle fields to/from generic value
toggle sf origsf 0 = sf
toggle sf origsf n
   | newValue == "*ALL"   = newSF
   | otherwise= toggle newSF origsf (n-1) -- <- 
Loop through fields by No
 where
  newValue = toggleField (getSFField n sf) (getSFField n origsf)--  
< accessor functions
  newSF= setSFField n sf newValue


getSFField :: Int -> SearchFilter -> String
getSFField 1 (x,_,_,_,_) = x
getSFField 2 (_,x,_,_,_) = x

setSFField :: Int -> SearchFilter -> String -> SearchFilter
setSFField 1 (a,b,c,d,e) f = (f,b,c,d,e)
setSFField 2 (a,b,c,d,e) f = (a,f,c,d,e)

The only problem with this is that if I want to add or remove a field, I 
need to change a lot of code.

In most OO lanaguages I could use "reflection" to loop through my fields.
In C (which also doesnt have meta data) I got round it by using pointers in 
an array. To add or remove a field just requires adding or removing a 
pointer to my array which is one line of code.

The only thought I had was of using lists, but the this would mean I loose 
pattern matching against all values at once which is appealing for calrify 
of code.

So what is the general haskell approach to this type of introspection/meta 
data problem... ?

Thanks,
_
Protect your PC - get McAfee.com VirusScan Online 
http://clinic.mcafee.com/clinic/ibuy/campaign.asp?cid=3963

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-07-20 Thread Crypt Master
*grin* its so obvious once you know the answer :-)
Thx
Original Message Follows
On Tue, 20 Jul 2004, Crypt Master wrote:
> Exmaple:
>
> 
> type Fitness = Integer
> data Population a = Population [(Fitness, a)]
> deriving (Show)
>
> data GAParams = GAParams { randomNums :: [Integer] ,
>someFunc :: (Int->Int->(Population a))}
> 
Like for 'Population a' you have to specify a type parameter for
'GAParams', i.e.
  |
  v
data GAParams a = GAParams { randomNums :: [Integer] ,
 someFunc :: (Int->Int->(Population a))}
_
Protect your PC - get McAfee.com VirusScan Online 
http://clinic.mcafee.com/clinic/ibuy/campaign.asp?cid=3963

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-07-20 Thread Crypt Master
Hi
How do I include polymorphic function type signatures in a data element ?
Exmaple:

type Fitness = Integer
data Population a = Population [(Fitness, a)]
   deriving (Show)
data GAParams = GAParams { randomNums :: [Integer] ,
  someFunc :: (Int->Int->(Population a))}

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


data GAParams = GAParams { randomNums :: [Integer] ,
  someFunc :: (Int->Int->GAParams) }
/
I am just having issues with polymorphic types.
Any ideas ?
The context is included below in case it helps:

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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] so how does one convert an IO a into an a ?

2004-07-10 Thread Crypt Master
Hi
Thanks for all the usefull responses, from theory to practical :-). I am 
busy digesting it all. I have more questions, but more and more I can answer 
them myself :-)

Till the next misunderstanding ;-)
C
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] so how does one convert an IO a into an a ?

2004-07-08 Thread Crypt Master
Hi
Thanks for your help so far, but I am still not getting this IO stuff. After 
reading your previous help and reading several articles on it I still cant 
phathom how you convert the IO Int into an Int.

One person mentioned how random just returns an interative program which 
when eveluated returns the Int. Also from the school of expression book he 
says " The right way to think of (>>=) above is simply this: It "Executes" 
e1 ..." in relation to "do pat <- e1 ...".

so I have this:

rollDice :: IO Int
rollDice = getStdRandom (randomR (1,6))
rl :: [Int]
rl = [ (getRndNum x) | x <- [1..] ]
getRndNum :: Int -> Int
getRndNum x = do n <- rollDice
  return n
  *PS Pretend return is correctly aligned under n. dont what ahppens 
in copy and paste*

now my understanding therefore is that "do n <- rollDice" should execute the 
the itererative program returned by rollDice. So now n should be my Int 
since IO Int was a program which when evaluted returns an Int ?

However this is what haskell thinks of my thoery:
*** Term   : getRndNum
*** Type   : Int -> IO (Maybe Int)
*** Does not match : Int -> Int
So I am still in IO Int land despite having used the >>= in the do syntax. 
Worse Still I am in IO (Maybe Int) land. Monads within Monads.

In yours, and many other examples I found online, the results are always 
passed to print which seems to know how to deal with an IO Int. Is this 
specially coded or overloaded or something ?

There are plenty of examples which use return like so:
do k <- getKey w
   return k
which is what I tried above to no avail.
It seems awefully complicated just to get hold a simple Int, but naturally 
complicity is directly related to ones understanding. Mine is sumewhat 
lacking ... any help would be appreciated.

Thanks,
S
_
Tired of spam? Get advanced junk mail protection with MSN 8. 
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random Numbers for the beginner ?

2004-07-06 Thread Crypt Master
Hi
I have tried I swear, even googled for 45 minutes, but I cant seem to get 
random numbers working.

In the documentation is has:
rollDice :: IO Int
rollDice = getStdRandom (randomR (1,6))
But if I type "getStdRandom (randomR (1,6))" into hugs in the context of 
module which imports Random, I get get errors.

ERROR - Unresolved overloading
*** Type   : (Random a, Num a) => IO a
*** Expression : getStdRandom (randomR (1,6))
Roll dice takes no parameters and returns an IO Int. So in thoery (mine at 
least ;-) ) running this as an expresion should work. I should get an IO Int 
back from the interpreter ?

So I added RollDice to my module. This doesnt error, but it doesnt return 
anything except blank spaces:

HasGal> rollDice
HasGal>
Integers or nums should automatically have show correct? So this should show 
me something ?

Ultimatly I want to get randomRs infinite list working so I can build
   randNums = (take (length popList) [1..])
where the length of pop list is how many random numbers I want.  My code 
works as it, just need to replace [1..] with some random numbers.

Thanks,
C
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using Product Algebraic types

2004-07-05 Thread Crypt Master
-

   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.



Sorry to have produced the *sigh* factor. I asked the question only to start 
learning,  which your answer has certainly helped me with.

Maybe I can present a differnt persepctive on performance though. I have to 
say up front though that if I was interested in squeezing the last drop of 
performance out of everything I wouldnt be learning haskell as all the web 
sites warn you about this :-) I do beleive in clarity, readbaility, 
correctness, time to develop etc.., it just that performance is one of those 
factors.

My day job is all mostly about performance (from iterative programming 
perspective), I make complex business applications useable from a 
perfromance perspective. While most people say "just buy more hardware" or 
make it "correct or readable" first, my experince shows this leads to a lot 
of wasted effort which could have been avoided with a few seconds thought. 
Have you ever tried telling an IT Director that his 500 000 - 1 000 000 
pound equipment purchase isnt cutting it for a "simple" business application 
:-) Let me tell you, they can have really selective hearing when it suits 
them :-)

In my world, getting a program "correct" includes effieincy within reason. 
For exmaple, a 5 minute response time for interactive process can be pushed 
on employees with a relativilty minial cost of a small loss in productivity. 
However 5 minutes as a response for customer sitting on your web site is 
going to cost you millions and probably put you out of business. There are 
dozens of senarios like this where a "correct" program is as good as no 
program if it doesnt perform fast enough.

What you say about guessing at performance is correct. I have given lectures 
on performance which start off with slides which say the trick to 
performance tuning is:

"Measure, Measure, Measure"
But I have found through experience (in the iterative world) that certian 
patterns of bad performance are easily avoided at development time because 
we know from experince they are bad at runtime.

Performance has 3 flavours in my mind:
1) Hard Core
2) Design (Algortihms and data representation)
3) Common sense coding
The fiirst, Hard code, invovles assemlber optimizations, branch reductions 
using boolean algebra etc.. No one argues these are mostly not worth the 
effort and so these are mostly ingnored expect for very special 
cercumstances. The phrase "buy more hardware" applies in this case 99% of 
the time.

At the other end of the spectrum you have design. Few people will argue that 
getting your design right up front is very important. Changing Algorithms or 
Data Representation usually invovles changes of a significance that you have 
wasted your time on the "incorrect" version as you are starting mostly from 
scratch. Admitatly this looks a lot easier in haskell than in other 
impertive lanaguages.

The 3rd area is where I differ from most people. Common sense coding is 
simply not calculating or looking something up over and over in an inner 
loop etc... While the programs can be changed afterwards to incorporate 
these, a few seconds thought by the developer avoids the bottle neck in the 
first place. An Example of the impact of such ineffiencies is this:  
Recenetly I "optimized" an interactive job which was taking over 10 minutes 
to run. Without understanding much about it (its highly complex) I was able 
to bring it down to < 1 minute applying simple common sense things. I never 
changed or looked at the "logic" behind it. Happy user base = productive 
company  :-)

That said haskell compiler seem pretty smart from what you have shown me so 
far ... which is a welcome change :-)

Thanks for your reponse. This is the most helpfull community I have 
encountered so far .. :-)

_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie questions

2004-07-05 Thread Crypt Master
Hi
Thanks for responding and taking the time to respond so fully. Its much 
appreciated!

>From what I can see, a key difficulty you're having is with the
"evolvepopulation" function. You've given it the type a -> a, which
pretty much requires it to be an identity function, because it's not
allowed to make any assumptions about the values it takes.
I was going trying for generic as possible, I am keen to expore how much 
more expressive one can be in functional lanaguages.

To make things easier to read, try defining types for Population and
Individual (they can always be generalized later).
> type Individual = Int
> type Population = [Individual]
A use fill tip, thanks.
[Snip]
It looks like you're defining evolution as the composition of mutate,
cross, and select, but got tripped up by the order of evaluation.
Specifically, "mutate cross select p" is the same as "((mutate cross)
select) p", which probably isn't what you want.
It only recently dawned on me that functions are left asscoaitive and your 
absolutly right its not what i had in mind.

If you have:
> mutate :: Population -> Population
> cross  :: Population -> Population
> select :: Population -> Population
Then you could define
> evolve p = mutate (cross (select p))
>
> -- alternative:
> -- evolve = mutate . cross . select
I now get what the f.g is as well :-) Thanks, the alternate format with the 
original has just clicked something else into place.

Starting from an initial population, you want to generate a sequence by
iterating evolve, starting from an initial population. Haskell provides
a function "iterate" for this purpose, or you can define your own.
Yeah other posters suggested this as well. I now have the the same function 
as you mentioned which is very nice:

gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom = iterate evolvePopulation
[snip]
I found it helpful to remember that you can think of a function f :: a
-> b -> c as taking two arguments of types a and b and returning a
result c, or as taking a single argument of type a and returning a
result of type b -> c. Once you become comfortable with partial
application, a lot of Haskell code starts to make more sense.
I understood the partial application when explained in simple terms, but I 
find I have a hard time when it used in more coimplicated examples. The 
currying in the "The Haskell School of Expression" left with a big "Huh", 
even though a simple application makes sense to me.

"The craft of Functional Programming" it seesm thicker more methdoical, so I 
may get some more of the basics down in the next few weeks.

Thanks again.
--
Message: 8
Date: Sat, 03 Jul 2004 08:38:55 +
From: "Crypt Master" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-cafe] Newbie questions
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; format=flowed
[Snip]
People say function application in Haskell is written without brackets
but this can be misleading, here you do need brackets to indicate that
'gaSolutionSpace [1,2,3,4,5]' is one argument and not two. So you should
write:
take 5 (gaSolutionSpace [1,2,3,4,5])
[Snip]
Thanks alot, this was very helpfull. It also makes more sense now that I
looked up the associativity of functions and found it to be left assoc. For
some reason I assumed it would automaically bracket form the right as such
(take (5 (gaSolutionSpace [1,2,3,4,5])))
but its actually this
(((take 5) gaSolutionSpace) [1,2,3,4,5])
Thanks again.
_
Tired of spam? Get advanced junk mail protection with MSN 8.
http://join.msn.com/?page=features/junkmail

--
Message: 9
Date: Sat, 03 Jul 2004 08:46:24 +
From: "Crypt Master" <[EMAIL PROTECTED]>
Subject: [Haskell-cafe] Re: Newbie questions
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; format=flowed
>-- gaSolutionSpace :: [a] -> [a]
>>gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)
-Stop deceiving yourself until it's too late.
-Why did you comment out the type annotation?
*Sheepish Grin* its historical, my original thought and attempt was that you
would recieve a list of populations and evolve it to a bigger list of
populations. Hence the [a] -> [a]. It didnt work out too well as this is
what I came up with:
gaSolSpace [x:xs] = gaSolutionSpace [x : evolePopulation x]
Eventually i realised that I needed to evolve a single population, not a
list, which let to a -> [a] and thanks to Keith I now have this:
gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom = iterate evolvePopulation
Thanks
_
Add photos to your e-mai

RE: [Haskell-cafe] Using Product Algebraic types

2004-07-04 Thread Crypt Master
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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Question on Exercise from SOE

2004-07-04 Thread Crypt Master
Hi
Not looking to get flamed, just offering my opinion.
I got the SOE first, and while I like the higher level of it, the way he 
thinks etc... I found it hard to learn haskell from it. I just recieved 
"Haskell: The Craft of cuntional Programming" this weekend, and have made 
huge leaps forward (for me) based on the information within. I would have 
prefered to start with this book in place of SOE. So my advice is SOE is 
great but back it up with The craft ..

S
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Using Product Algebraic types

2004-07-04 Thread Crypt Master
Hi
My question is how do I select or work with product Alhebraic types ? Let 
you give you some context:

I need to be able to work with a list of items whos structure is onyl 
partially know. That is at the level of this module I dont care about what 
rest of it is. So I have this:

type Fitness = Integer
data Population a = Population [Fitness a]
Hopefully this reads Population is constructed using the Population 
constructor and is a list who elements each conists a fitness value and some 
other value. Since I cant do poloymorphioc types with synonyms I went with 
the data type.

My current task is to build a roulette wheel distribution of the fitness 
value. Basically I want to build and incremental summing of the fitness 
value so that each individual is paired with its upper range like so

Population [10 x, 20 y, 30 z]
New Population = [10 x, 20+10 y, 30+30 z]
My first thought was a list comprehension:
rwList :: Population -> Population
rwList (Population popList) = Population [ (rwListSum i)  | i <- popList]
rwListSum :: [a] -> [a]
rwListSum (fitness individual) = (fitness*2, individual)
ingoring for a minute that this wont achieve the above goal, I immediatly 
ran into the issue of how do I represent in the inner portion of the 
Population List, i.e "Fitness a".

"(fitness individual)" doesnt work ? I tried treating it as 2 normal 
arguments, but of course how can I return it then ... ? A function can only 
return one thing. If its not a tuple then it wont work. Hence my question of 
how you represent product types ?

I did come up with one idea, that is of making the internal part a type on 
its own so now I have this:

type Fitness = Integer
data InternalIndividual a = InternalIndividual Fitness a
data Population a = Population [InternalIndividual a]
...
rwList :: Population -> Population
rwList (Population popList) = Population [ (rwListSum i)  | i <- popList]
rwListSum :: InternalIndividual -> InternalIndividual
rwListSum (InternalIndividual fitness individual) = (InternalIndividual 
fitness*2 individual)

To my surpirse this compiles. I have been able to fully test it yet though.
So is there a way to do this without a extra type ? Is there a better way to 
represent this ?

Thanks for your time,
PS Sorry for all the dumb questions, I always find asking better than just 
wondering for ages.

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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] List syntax -- [] vs ()

2004-07-03 Thread Crypt Master
Hi
Thanks. A light bulb just went on :). I am still in awe of how much "special 
syntax" is made of such simple base. Haskell certainly is an interesting 
thing to learn, its like fractals, complexity and beuty from simplicity.

S
Original Message Follows----
Crypt Master,
  CM> I have noticed that lists seem to swtich between
  CM> using [] and  using (). for example:
  CM>
  CM> listSum [] = 0
  CM> listSum (x:xs) = x + listsum xs
The parentheses are just 'normal' parentheses that are needed because
application binds stronger than (:). Without the parentheses, you would get
  listSum x : xs
which is the same as
  (listSum x) : xs .
HTH,
Stefan
_
MSN 8 helps eliminate e-mail viruses. Get 2 months FREE*. 
http://join.msn.com/?page=features/virus

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Running Total or Incremental Sum as a higher order type ?

2004-07-03 Thread Crypt Master
Hi
I was attempting to get a running a total of a list i.e
for [1,2,3]
the result should be
[1,3,6]   -- [1, 1+2, 2+3]
I build this function:
incrementalSum [] x = []
incrementalSum (x:xs) runningTotal = currentSum : incrementalSum xs 
currentSum
where
  currentSum = 
runningTotal + x

I was trying to see how I could higher order functions for this but came up 
empty. Surely this is a pattern which has been abstracted ? I feel I have 
missed the obvious here.

Thanks,
S
_
MSN 8 helps eliminate e-mail viruses. Get 2 months FREE*. 
http://join.msn.com/?page=features/virus

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] List syntax -- [] vs ()

2004-07-03 Thread Crypt Master
Hi
I have noticed that lists seem to swtich between using [] and using (). for 
example:

listSum [] = 0
listSum (x:xs) = x + listsum xs
but when specificy lists you use [] as in [1,2,3].
or type signatures are [a] -> [a]
It also seems when they mentioned on the right hand side it also always [].
Is it just for pattern matching that you use the "tuple" syntax ? How does 
haskell know we dont mean a tuple ? Or do we mean a tuple when we say (x:xs) 
?

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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie questions

2004-07-03 Thread Crypt Master
Hi
Very very helpful, thanks. I wasnt sure about the "From" on the end, but I 
get the subtle change in way you see it. Much better than mine.

Using you other advice I got:
gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom p = iterate evolvePopulation p
and even managed to curry it :-)   :
gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom = iterate evolvePopulation
Thanks again.
--
Kieth:
[Snip]
I think you mean:
gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom x = x : gaSolutionSpaceFrom (evolvepopulation x)
gaSolutionSpace = gaSolutionSpaceFrom createRandomPopulation
Note that "a" above should be replaced with your population type.
Also note the "iterate" function in the standard library does just this.
_
Tired of spam? Get advanced junk mail protection with MSN 8. 
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Newbie questions

2004-07-03 Thread Crypt Master
-- gaSolutionSpace :: [a] -> [a]
gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)
-Stop deceiving yourself until it's too late.
-Why did you comment out the type annotation?
*Sheepish Grin* its historical, my original thought and attempt was that you 
would recieve a list of populations and evolve it to a bigger list of 
populations. Hence the [a] -> [a]. It didnt work out too well as this is 
what I came up with:

gaSolSpace [x:xs] = gaSolutionSpace [x : evolePopulation x]
Eventually i realised that I needed to evolve a single population, not a 
list, which let to a -> [a] and thanks to Keith I now have this:

gaSolutionSpaceFrom :: a -> [a]
gaSolutionSpaceFrom = iterate evolvePopulation
Thanks
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie questions

2004-07-03 Thread Crypt Master
[Snip]
People say function application in Haskell is written without brackets
but this can be misleading, here you do need brackets to indicate that
'gaSolutionSpace [1,2,3,4,5]' is one argument and not two. So you should
write:
take 5 (gaSolutionSpace [1,2,3,4,5])
[Snip]
Thanks alot, this was very helpfull. It also makes more sense now that I 
looked up the associativity of functions and found it to be left assoc. For 
some reason I assumed it would automaically bracket form the right as such
(take (5 (gaSolutionSpace [1,2,3,4,5])))

but its actually this
(((take 5) gaSolutionSpace) [1,2,3,4,5])
Thanks again.
_
Tired of spam? Get advanced junk mail protection with MSN 8. 
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie questions

2004-07-01 Thread Crypt Master
Hi
I consider myself a pretty good imperative programmer, been at it for 
decades, and am tryibng my hand at Haskell now. Unfrituantly I am not 
"getting" it all that quickly despite having the multimedia haskell book.

To start ghetting some hands on, I thought iI owuld do something which i 
have done many times before in imperatives, a basic Genetic Algorithm 
Library. Unfortunatly I am comming unstuck straight away and was hoping some 
of you kind folk could point in the direction of dry land :-)

iIf your not familiar with GAs its not too important, simply a GA searches 
over the whole solution space randomly. Well not quiet, its a guided search, 
its guided by evolution ie by the fitness of each indicidual of a random 
initial population. Evolution is simulated by 3 basic operators, selection, 
cross over and mutation. selection is which indiviuals get to breed, cross 
over is how they breed, and mutation is just things intetresting.

So after reading the multimedia book, Iimmediately thought of a defining the 
solution space as a infinite list. I was hoping then I could do things like 
take 5 gaSolutionSpace to get 5 iterations or generations. My first attempt 
tied to use lis syntax [], but it wouldnt compile and after seeing 
"numsFrom" ina  tutorial I redefined it as such. Here is what I have so far:

-- gaSolutionSpace :: [a] -> [a]
-- gaSolutionSpace [] = gaSolutionSpace createRandomPopulation -- recursive 
base case
gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)

evolvepopulation :: a -> a
evolvepopulation p = mutate cross select p
-- createRandomPopulation :: [Num a]
createRandomPopulation = [1,23,4,5,6]
cross p  = p
mutate p = p
select p = p

The take operator doesnt work on this. from hugs:
HAGA> take 5 gaSolutionSpace [1,2,3,4,5]
ERROR - Type error in application
*** Expression : take 5 gaSolutionSpace [1,2,3,4,5]
*** Term   : take
*** Type   : Int -> [e] -> [e]
*** Does not match : a -> b -> c -> d
I am not sure I follow this. I assume its cause I didnt use the list 
notation in definaing gaSolutionSpace. Any ideas on how to do that. ? What 
about using map. It occurs to me that you can define gaSolutionspace as a 
map of the evolvolepopuloation function acrossan infinite solution space, 
but I dont know how to makethis  infinte list to map over ...?

There ar 2 papaers on GAs in haskell, but they use monads. I realise for 
performance I will probably have to use them too, but for now I would liek 
to do it without mondas even if performance isnt optimal.

Sorry again for the newbie questions, but any help is appreciated.
Stephen
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie questions

2004-07-01 Thread Crypt Master
Hi
I consider myself a pretty good imperative programmer, been at it for 
decades, and am tryibng my hand at Haskell now. Unfrituantly I am not 
"getting" it all that quickly despite having the multimedia haskell book.

To start ghetting some hands on, I thought iI owuld do something which i 
have done many times before in imperatives, a basic Genetic Algorithm 
Library. Unfortunatly I am comming unstuck straight away and was hoping some 
of you kind folk could point in the direction of dry land :-)

iIf your not familiar with GAs its not too important, simply a GA searches 
over the whole solution space randomly. Well not quiet, its a guided search, 
its guided by evolution ie by the fitness of each indicidual of a random 
initial population. Evolution is simulated by 3 basic operators, selection, 
cross over and mutation. selection is which indiviuals get to breed, cross 
over is how they breed, and mutation is just things intetresting.

So after reading the multimedia book, Iimmediately thought of a defining the 
solution space as a infinite list. I was hoping then I could do things like 
take 5 gaSolutionSpace to get 5 iterations or generations. My first attempt 
tied to use lis syntax [], but it wouldnt compile and after seeing 
"numsFrom" ina  tutorial I redefined it as such. Here is what I have so far:

-- gaSolutionSpace :: [a] -> [a]
-- gaSolutionSpace [] = gaSolutionSpace createRandomPopulation -- recursive 
base case
gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)

evolvepopulation :: a -> a
evolvepopulation p = mutate cross select p
-- createRandomPopulation :: [Num a]
createRandomPopulation = [1,23,4,5,6]
cross p  = p
mutate p = p
select p = p

The take operator doesnt work on this. from hugs:
HAGA> take 5 gaSolutionSpace [1,2,3,4,5]
ERROR - Type error in application
*** Expression : take 5 gaSolutionSpace [1,2,3,4,5]
*** Term   : take
*** Type   : Int -> [e] -> [e]
*** Does not match : a -> b -> c -> d
I am not sure I follow this. I assume its cause I didnt use the list 
notation in definaing gaSolutionSpace. Any ideas on how to do that. ? What 
about using map. It occurs to me that you can define gaSolutionspace as a 
map of the evolvolepopuloation function acrossan infinite solution space, 
but I dont know how to makethis  infinte list to map over ...?

There ar 2 papaers on GAs in haskell, but they use monads. I realise for 
performance I will probably have to use them too, but for now I would liek 
to do it without mondas even if performance isnt optimal.

Sorry again for the newbie questions, but any help is appreciated.
Stephen
_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe