Simulation looks ok-ish. Needs incentive to foster productive enzymes
This commit is contained in:
57
app/Main.hs
57
app/Main.hs
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE BangPatterns #-}
|
||||
module Main where
|
||||
|
||||
import Text.Printf
|
||||
@ -6,6 +7,7 @@ import Numeric.LinearAlgebra
|
||||
import Data.List
|
||||
import System.Random
|
||||
import Control.Concurrent
|
||||
import Control.Parallel.Strategies
|
||||
import qualified Debug.Trace as Debug
|
||||
import System.IO
|
||||
|
||||
@ -30,18 +32,18 @@ greenfly = Predator [] 0.2 -- killed by any toxic Component
|
||||
|
||||
-- Environment
|
||||
|
||||
exampleEnvironment :: Int -> [Enzyme] -> Environment
|
||||
exampleEnvironment addedC es =
|
||||
exampleEnvironment :: Int -> [Enzyme] -> [(Predator,Probability)] -> [(Compound,Amount)] -> Environment
|
||||
exampleEnvironment addedC es pred tox =
|
||||
Environment
|
||||
{ soil = [ (Nitrate, 2)
|
||||
, (Phosphor, 3)
|
||||
, (Photosynthesis, 10)
|
||||
]
|
||||
, predators = [ (greenfly, 0.1) ]
|
||||
, predators = pred -- [ (greenfly, 0.1) ]
|
||||
, metabolismIteration = 100
|
||||
, maxCompound = maxCompoundWithoutGeneric + addedC
|
||||
, toxicCompounds = [(Produced FPP,0.5)] --FPP kills 100% if produced amount above 0.2 units
|
||||
, possibleEnzymes = [pps,fpps] ++ es
|
||||
, toxicCompounds = tox --[(Produced FPP,0.1)] ++ tox
|
||||
, possibleEnzymes = es -- [pps,fpps] ++ es
|
||||
}
|
||||
|
||||
-- Plants
|
||||
@ -84,11 +86,12 @@ 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
|
||||
liftIO $ printPopulation pe fps
|
||||
tc <- fmap fst <$> asks toxicCompounds
|
||||
liftIO $ printPopulation tc pe fps
|
||||
-- generate 100 new plants.
|
||||
sequence . flip fmap [1..100] $ \_ -> do
|
||||
parent' <- liftIO $ randomRIO (0,sumFitness)
|
||||
@ -110,12 +113,18 @@ main :: IO ()
|
||||
main = do
|
||||
hSetBuffering stdin NoBuffering
|
||||
hSetBuffering stdout NoBuffering
|
||||
randomCompounds <- generateTreeFromList 10 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly 10 compounds
|
||||
let env = exampleEnvironment (getTreeSize randomCompounds) (generateEnzymeFromTree randomCompounds)
|
||||
emptyPlants = replicate 100 emptyPlant
|
||||
randomCompounds <- makeHead (Substrate Photosynthesis) <$> generateTreeFromList 40 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly x compounds
|
||||
ds <- randoms <$> newStdGen
|
||||
probs <- randomRs (0.2,0.7) <$> newStdGen
|
||||
let emptyPlants = replicate 100 emptyPlant
|
||||
poisonedTree = poisonTree ds randomCompounds
|
||||
poisonCompounds = foldMap (\(a,b) -> if a > 0.5 then [(b,a)] else []) $ poisonedTree
|
||||
predators <- generatePredators 0.5 poisonedTree
|
||||
let env = exampleEnvironment (getTreeSize randomCompounds) (generateEnzymeFromTree randomCompounds) (zip predators probs) poisonCompounds
|
||||
printEnvironment env
|
||||
writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 $ poisonedTree
|
||||
putStr "\ESC[?1049h"
|
||||
loop 100 emptyPlants env
|
||||
loop 200 emptyPlants env
|
||||
putStrLn "Simulation ended. Press key to exit."
|
||||
_ <- getChar
|
||||
putStr "\ESC[?1049l"
|
||||
@ -128,6 +137,21 @@ main = do
|
||||
-- printf "%15.2f" f
|
||||
-- putStr "\n"
|
||||
|
||||
generatePredators :: Double -> EnzymeTree s (Double,Compound) -> IO [Predator]
|
||||
generatePredators threshold t = do
|
||||
ps <- mapM generatePredators' $ getSubTrees t
|
||||
return $ concat ps
|
||||
where
|
||||
generatePredators' :: (EnzymeTree s (Double, Compound)) -> IO [Predator]
|
||||
generatePredators' t = do -- not fully resistant to t, but fully resistant to everything in ts
|
||||
let comps = foldMap (\(a,b) -> if a > threshold then [(a,b)] else []) t
|
||||
amount <- randomRIO (0,length comps + 1) :: IO Int
|
||||
forM [1..amount] $ \_ -> do
|
||||
impact <- randomRIO (0.2,0.7)
|
||||
rands <- randoms <$> newStdGen
|
||||
let unresists = foldMap (\((a,b),r) -> if r*2 < a then [b] else []) $ zip comps rands
|
||||
return $ Predator unresists impact
|
||||
|
||||
printEnvironment :: Environment -> IO ()
|
||||
printEnvironment (Environment soil pred metaIter maxComp toxic possEnz) =
|
||||
do
|
||||
@ -138,16 +162,17 @@ printEnvironment (Environment soil pred metaIter maxComp toxic possEnz) =
|
||||
putStrLn $ "Compounds: " ++ show ((toEnum <$> [0..maxComp]) :: [Compound])
|
||||
putStrLn $ "Toxic: " ++ show toxic
|
||||
|
||||
printPopulation :: [Enzyme] -> [(Plant,Double)] -> IO ()
|
||||
printPopulation es ps = do
|
||||
printPopulation :: [Compound] -> [Enzyme] -> [(Plant,Double)] -> IO ()
|
||||
printPopulation toxins es ps = do
|
||||
let padded i str = take i $ str ++ repeat ' '
|
||||
putStr $ padded 40 "Population:"
|
||||
putStr $ padded 50 "Population:"
|
||||
forM_ ps $ \(_,f) -> putStr (printColor f '█')
|
||||
putStrLn colorOff
|
||||
forM_ es $ \e -> do
|
||||
putStr $ padded 40 (show (enzymeName e))
|
||||
putStr $ if (fst . snd . synthesis $ e) `elem` toxins then "\ESC[31m" ++ padded 50 (show (enzymeName e)) ++ "\ESC[0m"
|
||||
else padded 50 (show (enzymeName e))
|
||||
forM_ ps $ \(Plant g _,_) -> do
|
||||
let curE = sum $ map (\(_,q,a) -> fromIntegral q*a)
|
||||
let curE = sum $ map (\(_,q,a) -> fromIntegral q*a)
|
||||
. filter (\(e',_,_) -> e == e')
|
||||
$ g
|
||||
plot x
|
||||
|
Reference in New Issue
Block a user