Divide step and run, add progress support via pipes
This commit is contained in:
parent
531cb74aac
commit
6c41743dbd
11
default.nix
11
default.nix
|
@ -1,5 +1,5 @@
|
||||||
{ mkDerivation, base, bytestring, cassava, monad-loops, MonadRandom
|
{ mkDerivation, base, monad-loops, MonadRandom, pipes, protolude
|
||||||
, protolude, QuickCheck, quickcheck-instances, random, random-fu
|
, QuickCheck, quickcheck-instances, random, random-fu
|
||||||
, random-shuffle, stdenv, text
|
, random-shuffle, stdenv, text
|
||||||
}:
|
}:
|
||||||
mkDerivation {
|
mkDerivation {
|
||||||
|
@ -9,13 +9,12 @@ mkDerivation {
|
||||||
isLibrary = true;
|
isLibrary = true;
|
||||||
isExecutable = true;
|
isExecutable = true;
|
||||||
libraryHaskellDepends = [
|
libraryHaskellDepends = [
|
||||||
base cassava monad-loops MonadRandom protolude QuickCheck
|
base monad-loops MonadRandom pipes protolude QuickCheck
|
||||||
quickcheck-instances random random-fu random-shuffle text
|
quickcheck-instances random random-fu random-shuffle text
|
||||||
];
|
];
|
||||||
executableHaskellDepends = [
|
executableHaskellDepends = [
|
||||||
base bytestring cassava monad-loops MonadRandom protolude
|
base monad-loops MonadRandom pipes protolude QuickCheck
|
||||||
QuickCheck quickcheck-instances random random-fu random-shuffle
|
quickcheck-instances random random-fu random-shuffle text
|
||||||
text
|
|
||||||
];
|
];
|
||||||
license = stdenv.lib.licenses.gpl3;
|
license = stdenv.lib.licenses.gpl3;
|
||||||
}
|
}
|
||||||
|
|
2
ga.cabal
2
ga.cabal
|
@ -20,6 +20,7 @@ library
|
||||||
, random
|
, random
|
||||||
, random-fu
|
, random-fu
|
||||||
, random-shuffle
|
, random-shuffle
|
||||||
|
, pipes
|
||||||
, protolude
|
, protolude
|
||||||
, QuickCheck
|
, QuickCheck
|
||||||
, quickcheck-instances
|
, quickcheck-instances
|
||||||
|
@ -40,6 +41,7 @@ executable ga
|
||||||
, random
|
, random
|
||||||
, random-fu
|
, random-fu
|
||||||
, random-shuffle
|
, random-shuffle
|
||||||
|
, pipes
|
||||||
, protolude
|
, protolude
|
||||||
, QuickCheck
|
, QuickCheck
|
||||||
, quickcheck-instances
|
, quickcheck-instances
|
||||||
|
|
79
src/GA.hs
79
src/GA.hs
|
@ -3,13 +3,12 @@
|
||||||
{-# LANGUAGE DeriveTraversable #-}
|
{-# LANGUAGE DeriveTraversable #-}
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
{-# LANGUAGE TupleSections #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
|
||||||
module GA where
|
module GA where
|
||||||
|
|
||||||
-- NEXT commit everything
|
-- MAYBE add factory floor optimizer:
|
||||||
-- TODO add factory floor optimizer:
|
|
||||||
-- [2019-07-15] GA that optimizes factory floor
|
-- [2019-07-15] GA that optimizes factory floor
|
||||||
-- - data: graph of workstations with edge weights being the number of walks between them
|
-- - data: graph of workstations with edge weights being the number of walks between them
|
||||||
-- - desired: optimal configuration that reduces crossings
|
-- - desired: optimal configuration that reduces crossings
|
||||||
|
@ -21,11 +20,11 @@ import qualified Data.List.NonEmpty as NE
|
||||||
import Data.Random
|
import Data.Random
|
||||||
import Data.Random.Distribution.Categorical
|
import Data.Random.Distribution.Categorical
|
||||||
import Data.Random.Sample
|
import Data.Random.Sample
|
||||||
|
import Pipes
|
||||||
import Pretty
|
import Pretty
|
||||||
import Protolude
|
import Protolude
|
||||||
import Test.QuickCheck hiding (sample, shuffle)
|
import Test.QuickCheck hiding (sample, shuffle)
|
||||||
import Test.QuickCheck.Instances
|
import Test.QuickCheck.Instances
|
||||||
import Test.QuickCheck.Monadic
|
|
||||||
|
|
||||||
-- TODO Enforce this being > 0
|
-- TODO Enforce this being > 0
|
||||||
type N = Int
|
type N = Int
|
||||||
|
@ -135,32 +134,30 @@ children2 nX i1 i2 = do
|
||||||
The @k@ best individuals in the population when comparing using the supplied
|
The @k@ best individuals in the population when comparing using the supplied
|
||||||
function.
|
function.
|
||||||
-}
|
-}
|
||||||
bestBy :: (Individual i, Monad m) => N -> (i -> m R) -> Population i -> m [i]
|
bestsBy :: (Individual i, Monad m) => N -> (i -> m R) -> Population i -> m [i]
|
||||||
bestBy k f =
|
bestsBy k f =
|
||||||
fmap (NE.take k . fmap fst . NE.sortBy (comparing (Down . snd)))
|
fmap (NE.take k . fmap fst . NE.sortBy (comparing (Down . snd)))
|
||||||
. traverse (\i -> (i,) <$> f i)
|
. traverse (\i -> (i,) <$> f i)
|
||||||
. unPop
|
. unPop
|
||||||
|
|
||||||
-- TODO no trivial instance for worst
|
|
||||||
-- prop_worstLength :: Int -> Population Int -> Property
|
|
||||||
-- prop_worstLength k pop = monadicIO $ (k ==) . length <$> worst k pop
|
|
||||||
{-|
|
{-|
|
||||||
The @k@ worst individuals in the population.
|
The @k@ worst individuals in the population.
|
||||||
-}
|
-}
|
||||||
worst :: (Individual i, Monad m) => N -> Population i -> m [i]
|
worst :: (Individual i, Monad m) => N -> Population i -> m [i]
|
||||||
worst = flip bestBy (fmap (1 /) . fitness)
|
-- TODO (1 /) might not be stable regarding floating point precision
|
||||||
|
worst = flip bestsBy (fmap (1 /) . fitness)
|
||||||
|
|
||||||
{-|
|
{-|
|
||||||
The @k@ best individuals in the population.
|
The @k@ best individuals in the population.
|
||||||
-}
|
-}
|
||||||
bests :: (Individual i, Monad m) => N -> Population i -> m [i]
|
bests :: (Individual i, Monad m) => N -> Population i -> m [i]
|
||||||
bests = flip bestBy fitness
|
bests = flip bestsBy fitness
|
||||||
|
|
||||||
{-|
|
{-|
|
||||||
Runs the GA and prints the @nResult@ best individuals.
|
Runs the GA and prints the @nResult@ best individuals.
|
||||||
-}
|
-}
|
||||||
ga' nParents nX pop term nResult = do
|
ga' nParents nX pop term nResult = do
|
||||||
pop <- ga nParents nX pop term
|
pop <- run nParents nX pop term
|
||||||
res <- bests nResult pop
|
res <- bests nResult pop
|
||||||
sequence $ format <$> res
|
sequence $ format <$> res
|
||||||
where
|
where
|
||||||
|
@ -170,6 +167,19 @@ ga' nParents nX pop term nResult = do
|
||||||
f <- liftIO $ fitness s
|
f <- liftIO $ fitness s
|
||||||
putText $ show f <> "\n" <> pretty s
|
putText $ show f <> "\n" <> pretty s
|
||||||
|
|
||||||
|
step
|
||||||
|
:: (Individual i, MonadRandom m, Monad m)
|
||||||
|
=> N
|
||||||
|
-> N
|
||||||
|
-> Population i
|
||||||
|
-> m (Population i)
|
||||||
|
step nParents nX pop = do
|
||||||
|
is <- proportionate nParents pop
|
||||||
|
i :| is' <- children nX is
|
||||||
|
iWorsts <- worst nParents pop
|
||||||
|
let popClean = foldr L.delete (NE.toList . unPop $ pop) iWorsts
|
||||||
|
return . Pop $ i :| is' <> popClean
|
||||||
|
|
||||||
{-|
|
{-|
|
||||||
Runs the GA, using in each iteration
|
Runs the GA, using in each iteration
|
||||||
- @nParents@ parents for creating @nParents@ children and
|
- @nParents@ parents for creating @nParents@ children and
|
||||||
|
@ -177,40 +187,27 @@ Runs the GA, using in each iteration
|
||||||
|
|
||||||
It terminates after the termination criterion is fulfilled.
|
It terminates after the termination criterion is fulfilled.
|
||||||
-}
|
-}
|
||||||
ga
|
run
|
||||||
:: (Individual i, MonadRandom m, Monad m)
|
:: (Individual i, Monad m, MonadRandom m)
|
||||||
=> N
|
=> N
|
||||||
-> N
|
-> N
|
||||||
-> Population i
|
-> Population i
|
||||||
-> Termination i
|
-> Termination i
|
||||||
-> m (Population i)
|
-> Producer (Int, Maybe R) m (Population i)
|
||||||
ga nParents nX pop term = ga' nParents nX pop term 0
|
run nParents nX pop term = step' 0 pop
|
||||||
where
|
where
|
||||||
ga'
|
step' t pop
|
||||||
:: (Individual i, MonadRandom m, Monad m)
|
| term pop t = return pop
|
||||||
=> N
|
| otherwise = do
|
||||||
-> N
|
pop' <- lift $ step nParents nX pop
|
||||||
-> Population i
|
iBests <- lift $ bests 1 pop'
|
||||||
-> Termination i
|
case headMay iBests of
|
||||||
-> N
|
Just iBest -> do
|
||||||
-> m (Population i)
|
f <- fitness iBest
|
||||||
ga' nParents nX pop term t = do
|
yield (t, Just f)
|
||||||
-- trace (show t <> ": " <> show (length pop)) $ return ()
|
Nothing ->
|
||||||
is <- proportionate nParents pop
|
yield (t, Nothing)
|
||||||
i :| is' <- children nX is
|
step' (t + 1) pop'
|
||||||
-- traceShow (length is') $ return ()
|
|
||||||
iWorsts <- worst nParents pop
|
|
||||||
-- traceShow (length iWorsts) $ return ()
|
|
||||||
let popClean = foldr L.delete (NE.toList . unPop $ pop) iWorsts
|
|
||||||
-- traceShow (length popClean) $ return ()
|
|
||||||
-- for the fromList to not fail, n < length pop
|
|
||||||
-- replace the worst ones
|
|
||||||
let pop' = Pop $ i :| is' <> popClean
|
|
||||||
-- replace fitness proportionally
|
|
||||||
-- let pop' = Pop <$> proportionate (length pop) (pop <> Pop is')
|
|
||||||
if term pop' t
|
|
||||||
then return pop'
|
|
||||||
else ga' nParents nX pop' term (t + 1)
|
|
||||||
|
|
||||||
-- * Termination criteria
|
-- * Termination criteria
|
||||||
|
|
||||||
|
|
26
src/Main.hs
26
src/Main.hs
|
@ -1,12 +1,26 @@
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
import Protolude
|
import Protolude hiding (for)
|
||||||
|
import Pretty
|
||||||
import WS19
|
import WS19
|
||||||
|
import Pipes
|
||||||
main = do
|
import System.IO
|
||||||
pop <- mkPop
|
|
||||||
ga' 2 1 pop (steps 10000) 10
|
|
||||||
putText "Done."
|
|
||||||
|
|
||||||
mkPop = population 100 (I prios [])
|
mkPop = population 100 (I prios [])
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
hSetBuffering stdout NoBuffering
|
||||||
|
pop <- mkPop
|
||||||
|
pop' <- runEffect $ for (run 2 1 pop (steps 100)) log
|
||||||
|
res <- bests 5 pop
|
||||||
|
sequence_ $ format <$> res
|
||||||
|
where
|
||||||
|
format :: (Individual i, MonadIO m, Pretty i) => i -> m ()
|
||||||
|
format s = do
|
||||||
|
f <- liftIO $ fitness s
|
||||||
|
putErrText $ show f <> "\n" <> pretty s
|
||||||
|
log = putText . csv
|
||||||
|
csv (t, f) = show t <> " " <> maybe "inf" show f
|
||||||
|
|
Loading…
Reference in New Issue
Block a user