better fitness
This commit is contained in:
15
app/Main.hs
15
app/Main.hs
@ -86,12 +86,13 @@ loop loopAmount = loop' loopAmount 0
|
||||
putStrLn ""
|
||||
putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":"
|
||||
newPlants <- flip runReaderT e $ do
|
||||
fs <- sequence (fitness <$> plants)
|
||||
! fs <- sequence (fitness <$> plants)
|
||||
let fps = zip plants fs -- gives us plants & their fitness in a tuple
|
||||
sumFitness = sum fs
|
||||
pe <- asks possibleEnzymes
|
||||
tc <- fmap fst <$> asks toxicCompounds
|
||||
tc <- asks toxicCompounds
|
||||
liftIO $ printPopulation tc pe fps
|
||||
liftIO $ hFlush stdout
|
||||
-- generate 100 new plants.
|
||||
sequence . flip fmap [1..100] $ \_ -> do
|
||||
parent' <- liftIO $ randomRIO (0,sumFitness)
|
||||
@ -140,7 +141,7 @@ main = do
|
||||
generatePredators :: Double -> EnzymeTree s (Double,Compound) -> IO [Predator]
|
||||
generatePredators threshold t = do
|
||||
ps <- mapM generatePredators' $ getSubTrees t
|
||||
return $ concat ps
|
||||
return $ filter ((/= []) . irresistance) $ concat ps -- filter out predators that are resistant to everything because this does not make sense in our model.
|
||||
where
|
||||
generatePredators' :: (EnzymeTree s (Double, Compound)) -> IO [Predator]
|
||||
generatePredators' t = do -- not fully resistant to t, but fully resistant to everything in ts
|
||||
@ -162,15 +163,17 @@ printEnvironment (Environment soil pred metaIter maxComp toxic possEnz) =
|
||||
putStrLn $ "Compounds: " ++ show ((toEnum <$> [0..maxComp]) :: [Compound])
|
||||
putStrLn $ "Toxic: " ++ show toxic
|
||||
|
||||
printPopulation :: [Compound] -> [Enzyme] -> [(Plant,Double)] -> IO ()
|
||||
printPopulation :: [(Compound, Amount)] -> [Enzyme] -> [(Plant,Double)] -> IO ()
|
||||
printPopulation toxins es ps = do
|
||||
let padded i str = take i $ str ++ repeat ' '
|
||||
putStr $ padded 50 "Population:"
|
||||
forM_ ps $ \(_,f) -> putStr (printColor f '█')
|
||||
putStrLn colorOff
|
||||
forM_ es $ \e -> do
|
||||
putStr $ if (fst . snd . synthesis $ e) `elem` toxins then "\ESC[31m" ++ padded 50 (show (enzymeName e)) ++ "\ESC[0m"
|
||||
else padded 50 (show (enzymeName e))
|
||||
putStr $ case Data.List.find (\(t,_) -> (t==) . fst . snd . synthesis $ e) toxins of
|
||||
Just (_,toxicity) -> "\ESC[38;5;" ++ show (16 + 36*5 + 6*floor (5*(1-toxicity)) + 0) ++ "m" -- yellow -> red rainbow for tocixity 0 -> 1
|
||||
++ padded 50 (show (enzymeName e)) ++ "\ESC[0m"
|
||||
Nothing -> padded 50 (show (enzymeName e))
|
||||
forM_ ps $ \(Plant g _,_) -> do
|
||||
let curE = sum $ map (\(_,q,a) -> fromIntegral q*a)
|
||||
. filter (\(e',_,_) -> e == e')
|
||||
|
Reference in New Issue
Block a user