2018-05-15 17:01:38 +00:00
{- # LANGUAGE BangPatterns # -}
2018-05-01 15:09:25 +00:00
module Main where
2018-05-02 21:39:22 +00:00
import Text.Printf
import Control.Monad.Reader
import Numeric.LinearAlgebra
import Data.List
import System.Random
import Control.Concurrent
2018-05-15 17:01:38 +00:00
import Control.Parallel.Strategies
2018-05-02 21:39:22 +00:00
import qualified Debug.Trace as Debug
import System.IO
2018-05-06 22:44:12 +00:00
import ArbitraryEnzymeTree
import Environment
2018-06-03 23:37:58 +00:00
import Evaluation
2018-05-02 21:39:22 +00:00
-- Example definitions
-- -------------------
-- Enzymes
2018-06-03 23:37:58 +00:00
-- pps :: Enzyme -- uses Phosphor from Substrate to produce PP
-- pps = Enzyme "PPS" [(Substrate Phosphor,1)] ((Substrate Phosphor,-1),(Produced PP,1)) Nothing
--
-- fpps :: Enzyme -- PP -> FPP
-- fpps = makeSimpleEnzyme (Produced PP) (Produced FPP)
2018-05-02 21:39:22 +00:00
-- Environment
2018-05-15 17:01:38 +00:00
exampleEnvironment :: Int -> [ Enzyme ] -> [ ( Predator , Probability ) ] -> [ ( Compound , Amount ) ] -> Environment
exampleEnvironment addedC es pred tox =
2018-05-02 21:39:22 +00:00
Environment
2018-06-03 23:37:58 +00:00
{ soil = [ ( PPM , 10 )
2018-05-02 21:39:22 +00:00
]
2018-05-15 17:01:38 +00:00
, predators = pred -- [ (greenfly, 0.1) ]
2018-05-02 21:39:22 +00:00
, metabolismIteration = 100
2018-05-06 22:44:12 +00:00
, maxCompound = maxCompoundWithoutGeneric + addedC
2018-05-15 17:01:38 +00:00
, toxicCompounds = tox --[(Produced FPP,0.1)] ++ tox
, possibleEnzymes = es -- [pps,fpps] ++ es
2018-06-03 23:37:58 +00:00
, settings = Settings { automimicry = False
2018-06-03 14:17:31 +00:00
, predatorsRandom = False
, numPlants = 150
}
2018-05-02 21:39:22 +00:00
}
-- Plants
2018-06-03 23:37:58 +00:00
-- examplePlants :: [Plant]
-- examplePlants = (\g -> Plant g defaultAbsorption) <$> genomes
-- where
-- enzymes = [pps, fpps]
-- quantity = [1,2] :: [Quantity]
-- activation = [0.7, 0.9, 1]
--
-- genomes = do
-- e <- permutations enzymes
-- e' <- subsequences e
-- q <- quantity
-- a <- activation
-- return $ (,,) <$> e' <*> [q] <*> [a]
--
-- defaultAbsorption = fmap ( limit Phosphor 2
-- . limit Nitrate 1
-- . limit Sulfur 0
-- ) <$> asks soil
-- -- custom absorbtion with helper-function:
-- limit :: Nutrient -> Amount -> (Nutrient, Amount) -> (Nutrient, Amount)
-- limit n a (n', a')
-- | n == n' = (n, min a a') -- if we should limit, then we do ;)
-- | otherwise = (n', a')
2018-05-02 21:39:22 +00:00
-- Running the simulation
-- ----------------------
loop :: Int -> [ Plant ] -> Environment -> IO ()
2018-06-03 14:17:31 +00:00
loop loopAmount ps env = loop' loopAmount 0 ps env
2018-05-02 21:39:22 +00:00
where
2018-06-03 14:17:31 +00:00
-- cache enzyme colorful-strings
stringe :: [ ( Enzyme , String ) ]
stringe = ( \ e -> case Data . List . find ( \ ( t , _ ) -> ( t == ) . fst . snd . synthesis $ e ) toxins of
Just ( _ , toxicity ) -> ( e , " \ 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 -> ( e , padded 50 ( show ( enzymeName e ) ) )
) <$> possibleEnzymes env
toxins :: [ ( Compound , Amount ) ]
toxins = toxicCompounds env
padded i str = take i $ str ++ repeat ' '
2018-06-03 23:37:58 +00:00
printEvery = 10
addedConstFitness = 0.1
2018-05-02 21:39:22 +00:00
loop' :: Int -> Int -> [ Plant ] -> Environment -> IO ()
2018-06-03 23:37:58 +00:00
loop' loopAmount curLoop plants e = unless ( loopAmount + 1 == curLoop ) $ do
2018-06-03 14:17:31 +00:00
when ( curLoop ` mod ` printEvery == 0 ) $ do
putStr " \ ESC [2J \ ESC [H "
printEnvironment e
putStrLn " "
putStrLn $ " Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ " : "
2018-05-04 22:23:40 +00:00
newPlants <- flip runReaderT e $ do
2018-06-03 23:37:58 +00:00
( ! fs , cs ) <- unzip . fmap ( \ ( f , c ) -> ( f , c ) ) <$> fitness plants
2018-05-02 21:39:22 +00:00
let fps = zip plants fs -- gives us plants & their fitness in a tuple
sumFitness = sum fs
2018-06-03 23:37:58 +00:00
when ( curLoop ` mod ` printEvery == 0 ) $ liftIO $ do
printPopulation stringe ( zip3 plants fs cs )
putStrLn $ " Population statistics: VarC = " ++ ( padded 50 . show . varianceOfProducedCompounds $ cs )
++ " DistC = " ++ ( padded 50 . show . meanOfDistinctCompounds $ cs )
hFlush stdout
threadDelay $ 100 * 1000 -- sleep x*1000ns (=x ~ ms)
2018-06-03 14:17:31 +00:00
-- generate x new plants.
np <- asks ( numPlants . settings )
sequence . flip fmap [ 1 .. np ] $ \ _ -> do
2018-05-02 21:39:22 +00:00
parent' <- liftIO $ randomRIO ( 0 , sumFitness )
let
-- if we only have one parent in our list, take it.
findParent :: Double -> [ ( Plant , Double ) ] -> Plant
findParent _ [ ( last , _ ) ] = last
-- otherwise count down x to find the parent in the list
findParent x ( ( p , f ) : ps )
| x < f = p
| otherwise = findParent ( x - f ) ps
parent = findParent parent' fps
haploMate parent
loop' loopAmount ( curLoop + 1 ) newPlants e
2018-05-01 15:09:25 +00:00
main :: IO ()
2018-05-02 21:39:22 +00:00
main = do
hSetBuffering stdin NoBuffering
2018-06-03 14:17:31 +00:00
--hSetBuffering stdout NoBuffering
2018-06-03 23:37:58 +00:00
randomCompounds <- makeHead ( Substrate PPM ) <$> generateTreeFromList 20 ( toEnum <$> [ ( maxCompoundWithoutGeneric + 1 ) .. ] :: [ Compound ] ) -- generate roughly x compounds
2018-05-15 17:01:38 +00:00
ds <- randoms <$> newStdGen
probs <- randomRs ( 0.2 , 0.7 ) <$> newStdGen
2018-06-03 14:17:31 +00:00
let poisonedTree = poisonTree ds randomCompounds
poisonCompounds = foldMap ( \ ( a , b ) -> [ ( b , a ) | a > 0.2 ] ) poisonedTree
predators <- generatePredators 0.5 poisonedTree
2018-05-15 17:01:38 +00:00
let env = exampleEnvironment ( getTreeSize randomCompounds ) ( generateEnzymeFromTree randomCompounds ) ( zip predators probs ) poisonCompounds
2018-06-03 14:17:31 +00:00
emptyPlants = replicate ( numPlants . settings $ env ) emptyPlant
2018-06-03 23:37:58 +00:00
enzs <- randomRs ( 0 , length ( possibleEnzymes env ) - 1 ) <$> newStdGen
let startPlants = randomGenome 10 enzs ( possibleEnzymes env ) emptyPlants
2018-05-06 22:44:12 +00:00
printEnvironment env
2018-05-23 11:13:20 +00:00
writeFile " poison.twopi " $ generateDotFromPoisonTree " poison " 0.5 poisonedTree
2018-05-02 21:39:22 +00:00
putStr " \ ESC [?1049h "
2018-06-03 23:37:58 +00:00
loop 2000 startPlants env
2018-05-02 21:39:22 +00:00
putStrLn " Simulation ended. Press key to exit. "
_ <- getChar
putStr " \ ESC [?1049l "
2018-06-03 23:37:58 +00:00
randomGenome :: Int -> [ Int ] -> [ Enzyme ] -> [ Plant ] -> [ Plant ]
randomGenome num inds enzs [] = []
randomGenome num inds enzs ( p : ps ) = p { genome = genes } : randomGenome num r enzs ps
where
i' = take num inds
r = drop num inds
enzymes = ( enzs !! ) <$> i'
genes = ( \ e -> ( e , 1 , 1 ) ) <$> enzymes
2018-05-15 17:01:38 +00:00
generatePredators :: Double -> EnzymeTree s ( Double , Compound ) -> IO [ Predator ]
generatePredators threshold t = do
ps <- mapM generatePredators' $ getSubTrees t
2018-05-23 11:07:34 +00:00
return $ filter ( ( /= [] ) . irresistance ) $ concat ps -- filter out predators that are resistant to everything because this does not make sense in our model.
2018-05-15 17:01:38 +00:00
where
2018-05-23 11:13:20 +00:00
generatePredators' :: EnzymeTree s ( Double , Compound ) -> IO [ Predator ]
2018-05-15 17:01:38 +00:00
generatePredators' t = do -- not fully resistant to t, but fully resistant to everything in ts
2018-05-23 11:13:20 +00:00
let comps = foldMap ( \ ( a , b ) -> [ ( a , b ) | a > threshold ] ) t
2018-05-15 17:01:38 +00:00
amount <- randomRIO ( 0 , length comps + 1 ) :: IO Int
forM [ 1 .. amount ] $ \ _ -> do
2018-06-03 23:37:58 +00:00
impact <- randomRIO ( 0.2 , 0.7 )
2018-05-15 17:01:38 +00:00
rands <- randoms <$> newStdGen
2018-05-23 11:13:20 +00:00
let unresists = foldMap ( \ ( ( a , b ) , r ) -> [ b | r * 2 < a ] ) $ zip comps rands
2018-06-03 14:17:31 +00:00
return $ Predator unresists impact 1
2018-05-15 17:01:38 +00:00
2018-05-02 21:39:22 +00:00
printEnvironment :: Environment -> IO ()
2018-06-03 14:17:31 +00:00
printEnvironment ( Environment soil pred metaIter maxComp toxic possEnz settings ) =
2018-05-02 21:39:22 +00:00
do
putStrLn " Environment: "
putStrLn $ " Soil: " ++ show soil
putStrLn $ " Predators: " ++ show pred
putStrLn $ " PSM Iters: " ++ show metaIter
putStrLn $ " Compounds: " ++ show ( ( toEnum <$> [ 0 .. maxComp ] ) :: [ Compound ] )
putStrLn $ " Toxic: " ++ show toxic
2018-06-03 14:17:31 +00:00
putStrLn $ " Settings: " ++ show settings
2018-05-02 21:39:22 +00:00
2018-06-03 23:37:58 +00:00
printPopulation :: [ ( Enzyme , String ) ] -> [ ( Plant , Double , Vector Amount ) ] -> IO ()
2018-06-03 14:17:31 +00:00
printPopulation es ps = do
2018-05-02 21:39:22 +00:00
let padded i str = take i $ str ++ repeat ' '
2018-05-15 17:01:38 +00:00
putStr $ padded 50 " Population: "
2018-06-03 23:37:58 +00:00
forM_ ps $ \ ( _ , f , _ ) -> putStr ( printColor f '█' )
2018-05-02 21:39:22 +00:00
putStrLn colorOff
2018-06-03 14:17:31 +00:00
forM_ es $ \ ( e , s ) -> do
putStr s
2018-06-03 23:37:58 +00:00
forM_ ps $ \ ( Plant g _ , _ , cs ) -> do
2018-05-15 17:01:38 +00:00
let curE = sum $ map ( \ ( _ , q , a ) -> fromIntegral q * a )
2018-05-02 21:39:22 +00:00
. filter ( \ ( e' , _ , _ ) -> e == e' )
$ g
plot x
2018-06-03 23:37:58 +00:00
| x > 2 = 'O'
| x > 1 = '+'
| x > 0.7 = 'ö'
| x > 0.5 = 'o'
| x > 0 = '.'
| otherwise = '_'
amount = min 2 $ cs ! fromEnum ( fst . snd . synthesis $ e )
putStr $ printColor ( amount / 2 ) ( plot curE )
putStrLn colorOff
2018-05-02 21:39:22 +00:00
printColor :: Double -> Char -> String
printColor x c
2018-05-04 22:23:40 +00:00
| x * x < 0.5 = " \ ESC [38;5; " ++ show ( 16 + 36 * 5 + 6 * floor ( 5 * 2 * x' ) + 0 ) ++ " m " ++ [ c ] ++ " "
| otherwise = " \ ESC [38;5; " ++ show ( 16 + 36 * floor ( 5 * 2 * ( 1 - x' ) ) + 6 * 5 + 0 ) ++ " m " ++ [ c ] ++ " "
2018-05-02 21:39:22 +00:00
-- 32 bit
-- | x*x < 0.5 = "\ESC[38;2;255;" ++ (show . floor $ 255*2*x') ++ ";0m" ++ [c] ++ ""
-- | otherwise = "\ESC[38;2;" ++ (show . floor $ 255*2*(1-x')) ++ ";255;0m" ++ [c] ++ ""
where x' = x * x
colorOff :: String
colorOff = " \ ESC [0m "
2018-05-06 22:44:12 +00:00
generateEnzymeFromTree :: EnzymeTree s Compound -> [ Enzyme ]
generateEnzymeFromTree t = ( makeSimpleEnzyme c . getElement <$> sts )
++ concatMap generateEnzymeFromTree sts
where
c = getElement t
sts = getSubTrees t