
Hi all, I'm a student and I got recently a task to do (and I want to do it in haskell). I have to implement "genetic algorithm for knapsack problem" and it would be nice if it will be fast. So my question is: what haskell datatypes, modules etc. should I use for this algorithm to achieve this goal? I mean fast as compared to implementation in imperative languages like C. Any advices ? Best regards, Karol Samborski

Karol,
I don't know if you have looked at this module on Hackage or whether it will
even help you, but there is an evolution algorithm the individual functions
of which might be useful to you and is described as follows:
AI.SimpleEA
A framework for simple evolutionary algorithms. Provided with a function for
evaluating a genome's fitness, a function for probabilistic selection among
a pool of genomes, and recombination and mutation operators,
runEAfile:///Users/aj/Library/Haskell/ghc-7.0.3/lib/SimpleEA-0.1.1/doc/html/AI-Si...
will
run an EA that lazily produces an infinite list of generations.
AI.SimpleEA.Utils contains utilitify functions that makes it easier to write
the genetic operators.
ajsher
On Thu, May 12, 2011 at 10:24 AM, Karol Samborski
Hi all,
I'm a student and I got recently a task to do (and I want to do it in haskell). I have to implement "genetic algorithm for knapsack problem" and it would be nice if it will be fast. So my question is: what haskell datatypes, modules etc. should I use for this algorithm to achieve this goal? I mean fast as compared to implementation in imperative languages like C.
Any advices ?
Best regards, Karol Samborski
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- AJ Sherbondy

Thank you for your answer.
I'll try it and then put some code for comments ;)
Best regards,
Karol Samborski
2011/5/12 AJ Sherbondy
Karol, I don't know if you have looked at this module on Hackage or whether it will even help you, but there is an evolution algorithm the individual functions of which might be useful to you and is described as follows: AI.SimpleEA
A framework for simple evolutionary algorithms. Provided with a function for evaluating a genome's fitness, a function for probabilistic selection among a pool of genomes, and recombination and mutation operators, runEA will run an EA that lazily produces an infinite list of generations.
AI.SimpleEA.Utils contains utilitify functions that makes it easier to write the genetic operators.
ajsher
On Thu, May 12, 2011 at 10:24 AM, Karol Samborski
wrote: Hi all,
I'm a student and I got recently a task to do (and I want to do it in haskell). I have to implement "genetic algorithm for knapsack problem" and it would be nice if it will be fast. So my question is: what haskell datatypes, modules etc. should I use for this algorithm to achieve this goal? I mean fast as compared to implementation in imperative languages like C.
Any advices ?
Best regards, Karol Samborski
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- AJ Sherbondy

When I was a student I built genetic algorithms in C and Java. I know
that building them in Haskell would be easy, with some little and very
descriptive code, but I have no experience with Haskell's performance.
It would be easy to tweak the algorithm and that's were you should
make you first attempts towards a faster implementation, but the
difficult part may be memory consumption, strict and lazy evaluation
strategies, etc (see
http://users.aber.ac.uk/afc/stricthaskell.html#seq).
On Fri, May 13, 2011 at 3:43 AM, Karol Samborski
Thank you for your answer. I'll try it and then put some code for comments ;)
Best regards, Karol Samborski
2011/5/12 AJ Sherbondy
: Karol, I don't know if you have looked at this module on Hackage or whether it will even help you, but there is an evolution algorithm the individual functions of which might be useful to you and is described as follows: AI.SimpleEA
A framework for simple evolutionary algorithms. Provided with a function for evaluating a genome's fitness, a function for probabilistic selection among a pool of genomes, and recombination and mutation operators, runEA will run an EA that lazily produces an infinite list of generations.
AI.SimpleEA.Utils contains utilitify functions that makes it easier to write the genetic operators.
ajsher
On Thu, May 12, 2011 at 10:24 AM, Karol Samborski
wrote: Hi all,
I'm a student and I got recently a task to do (and I want to do it in haskell). I have to implement "genetic algorithm for knapsack problem" and it would be nice if it will be fast. So my question is: what haskell datatypes, modules etc. should I use for this algorithm to achieve this goal? I mean fast as compared to implementation in imperative languages like C.
Any advices ?
Best regards, Karol Samborski
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- AJ Sherbondy
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

I wrote this for now and it's working pretty well ;) Any comments? import AI.SimpleEA import AI.SimpleEA.Utils import Control.Monad.Random import Data.List import System.Environment (getArgs) import Control.Monad (unless) data Item = Item { mass :: Double, value :: Double } instance Show Item where show i = "(" ++ show (mass i) ++ "," ++ show (value i) ++ ")" type Gene = (Bool, Item) capacity = 10.0 items = [ Item 5.0 0.2 , Item 2.4 0.8 , Item 1.7 1.9 , Item 6.0 0.5 , Item 0.5 0.1 , Item 2.2 1.2 , Item 1.4 7.8 , Item 0.7 1.4 , Item 6.9 0.3 , Item 1.5 0.2 , Item 4.2 0.5 ] genes = [ zip [True, False, True, True, False, True, False, True, True, True, True ] items ,zip [True, True, False, False, True, True, True, False, False, True, True ] items ,zip [False, False, False, False, False, False, True, False, False, True, True ] items ,zip [False, True, False, True, True, True, True, False, True, True, True ] items ,zip [False, True, False, True, True, False, False, False, True, False, False] items ] fitness :: FitnessFunc Gene fitness g _ | massSum > capacity = 0.0 | otherwise = valSum where massSum = foldr (\i s -> s + (mass $ snd i) ) 0.0 $ filter fst g valSum = foldr (\i s -> s + (value $ snd i) ) 0.0 $ filter fst g select :: SelectionFunction Gene select gs = select' (take 4 $ elite gs) where scaled = zip (map fst gs) (sigmaScale (map snd gs)) select' gs' = if length gs' >= length gs then return gs' else do p1 <- fitPropSelect scaled p2 <- fitPropSelect scaled let newPop = p1:p2:gs' select' newPop recombination :: Double -> RecombinationOp Gene recombination p (g1,g2) = do t <- getRandomR (0.0, 1.0) if t < p then do r <- getRandomR (0, length g1-1) return (take r g1 ++ drop r g2, take r g2 ++ drop r g1) else return (g1,g2) mutate :: Double -> MutationOp Gene mutate p g = do t <- getRandomR (0.0, 1.0) if t < p then do r <- getRandomR (0, length g-1) return (take r g ++ flipItem (g !! r) : drop (r+1) g) else return g where flipItem (False, i) = (True, i) flipItem (True, i) = (False, i) main = do args <- getArgs g <- newStdGen let (g1,g2) = split g let gs = take 401 $ runEA genes fitness select (recombination 0.75) (mutate 0.01) g2 let fs = avgFitnesses gs let ms = maxFitnesses gs let ds = stdDeviations gs mapM_ print $ zip5 (map head gs) [1..] fs ms ds unless (null args) $ writeFile (head args) $ getPlottingData gs Regards, Karol Samborski
participants (3)
-
AJ Sherbondy
-
Federico Mastellone
-
Karol Samborski