Implement bestsBy properly

Only needs something in O(n) now instead of a lot more. Also, returns the
complement.
This commit is contained in:
David Pätzel 2019-10-22 14:33:19 +02:00
parent 0044b6cc18
commit bcf11d61e1
2 changed files with 79 additions and 45 deletions

118
src/GA.hs
View File

@ -78,17 +78,18 @@ class Eq i => Individual i where
isM <- crossover1 i1 i2 isM <- crossover1 i1 i2
maybe (return Nothing) (uncurry (crossover (n - 1))) isM maybe (return Nothing) (uncurry (crossover (n - 1))) isM
-- TODO Perhaps use Data.Vector.Sized for the population?
{-| {-|
It would be nice to model populations as GADTs but then no functor instance were Needed for QuickCheck tests, very simplistic implementation.
possible:
> data Population a where
> Pop :: Individual a => NonEmpty a -> Population a
-} -}
instance Individual Integer where
instance (Arbitrary i) => Arbitrary (Population i) where new _ = sample $ uniform 0 (0 + 100000)
arbitrary = Pop <$> arbitrary
mutate i = sample $ uniform (i - 10) (i + 10)
crossover1 i1 i2 = return $ Just (i1 - i2, i2 - i1)
fitness = return . fromIntegral . negate
type Population i = NonEmpty i type Population i = NonEmpty i
@ -129,74 +130,107 @@ children2 nX i1 i2 = do
i6 <- mutate i4 i6 <- mutate i4
return $ i5 :| [i6] return $ i5 :| [i6]
-- TODO there should be some shuffle here {-|
The best according to a function, return up to @k@ results and the remaining
population.
If @k <= 0@, this returns the best one anyway (as if @k == 1@).
-}
bestsBy
:: (Individual i, Monad m)
=> N
-> (i -> m R)
-> Population i
-> m (NonEmpty i, [i])
bestsBy k f pop@(i :| pop')
| k <= 0 = bestsBy 1 f pop
| otherwise = foldM run (i :| [], []) pop'
where
run (bests, rest) i =
((NE.fromList . NE.take k) &&& (rest <>) . NE.drop k)
<$> sorted (i <| bests)
sorted =
fmap (fmap fst . NE.sortOn (Down . snd)) . traverse (\i -> (i,) <$> f i)
{-| {-|
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.
-} -}
-- TODO do this without a complete sort bestsBy' :: (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] bestsBy' 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)
prop_bestsBy_isBestsBy' k pop =
k > 0
==> monadicIO
$ do
a <- fst <$> bestsBy k fitness pop
b <- bestsBy' k fitness pop
assert $ NE.toList a == b
{-| {-|
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 (NonEmpty i, [i])
worst = flip bestsBy (fmap negate . fitness) worst = flip bestsBy (fmap negate . 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 (NonEmpty i, [i])
bests = flip bestsBy fitness bests = flip bestsBy fitness
-- TODO add top x percent selection (select n guys, sort by fitness first) -- TODO add top x percent parent selection (select n guys, sort by fitness first)
step step
:: (Individual i, MonadRandom m, Monad m) :: (Individual i, MonadRandom m, Monad m)
=> N => N -- ^ number of parents @nParents@ for creating @nParents@ children
-> N -> N -- ^ how many crossover points (the @nX@ in @nX@-point crossover)
-> R -- ^ elitism ratio @pElite@
-> Population i -> Population i
-> m (Population i) -> m (Population i)
step nParents nX pop = do -- TODO parametrize selection: 'proportionate' and 'worst'
iBests <- bests 1 pop step nParents nX pElite pop = do
is <- proportionate nParents pop iParents <- proportionate nParents pop
i :| is' <- children nX is iChildren <- NE.filter (`notElem` pop) <$> children nX iParents
iWorsts <- worst nParents pop let pop' = pop `NE.appendl` iChildren
let popClean = foldr L.delete (NE.toList . unPop $ pop) $ iBests <> iWorsts (iBests, iRests) <- bests bestN pop'
-- TODO why does this not work? (we should use it!) case iRests of
-- Pop <$> (shuffle' . NE.nub $ i :| is' <> popClean <> iBests) [] -> return iBests
return . Pop . NE.nub $ i :| is' <> popClean <> iBests (i : iRests') -> do
(_, iRests') <-
worst (length iBests + length iRests - length pop) (i :| iRests')
return $ iBests `NE.appendl` iRests'
where
bestN = round . (pElite *) . fromIntegral $ NE.length pop
-- TODO prop_step_size =
{-| {-|
Runs the GA, using in each iteration Given an initial population, runs the GA until the termination criterion is
- @nParents@ parents for creating @nParents@ children and fulfilled.
- @nX@-point crossover.
It terminates after the termination criterion is fulfilled. Uses the pipes library to, in each step, 'Pipes.yield' the currently best known
solution.
-} -}
run run
:: (Individual i, Monad m, MonadRandom m) :: (Individual i, Monad m, MonadRandom m)
=> N => N -- ^ number of parents @nParents@ for creating @nParents@ children
-> N -> N -- ^ how many crossover points (the @nX@ in @nX@-point crossover)
-> R -- ^ elitism ratio @pElite@
-> Population i -> Population i
-> Termination i -> Termination i
-> Producer (Int, Maybe R) m (Population i) -> Producer (Int, R) m (Population i)
run nParents nX pop term = step' 0 pop run nParents nX pElite pop term = step' 0 pop
where where
step' t pop step' t pop
| term pop t = return pop | term pop t = return pop
| otherwise = do | otherwise = do
pop' <- lift $ step nParents nX pop pop' <- lift $ step nParents nX pElite pop
iBests <- lift $ bests 1 pop' (iBests, _) <- lift $ bests 1 pop'
case headMay iBests of fs <- lift . sequence $ fitness <$> iBests
Just iBest -> do let fBest = NE.head fs
f <- fitness iBest yield (t, fBest)
yield (t, Just f)
Nothing ->
yield (t, Nothing)
step' (t + 1) pop' step' (t + 1) pop'
-- * Termination criteria -- * Termination criteria

View File

@ -16,12 +16,12 @@ main = do
let t = fromMaybe 100 $ headMay args >>= readMaybe let t = fromMaybe 100 $ headMay args >>= readMaybe
hSetBuffering stdout NoBuffering hSetBuffering stdout NoBuffering
pop <- mkPop pop <- mkPop
pop' <- runEffect $ for (run 2 1 pop (steps t)) log pop' <- runEffect $ for (run 2 1 (5/100) pop (steps t)) log
res <- bests 5 pop' (res, _) <- bests 5 pop'
sequence_ $ format <$> res sequence_ $ format <$> res
where where
format s = do format s = do
f <- liftIO $ fitness s f <- liftIO $ fitness s
putErrText $ show f <> "\n" <> pretty s putErrText $ show f <> "\n" <> pretty s
log = putText . csv log = putText . csv
csv (t, f) = show t <> " " <> maybe "inf" show f csv (t, f) = show t <> " " <> show f