Attackers in intervals now also work.

This commit is contained in:
Nicole Dresselhaus 2018-06-21 16:15:43 +02:00
parent 6dfc7e1ae0
commit f478f0ecb6
Signed by: Drezil
GPG Key ID: AC88BB432537313A
4 changed files with 57 additions and 33 deletions

View File

@ -20,13 +20,13 @@
- $\mathbf{E}[C_{plant} - C_#]$: Durchschnittliche Abweichung der produzierten - $\mathbf{E}[C_{plant} - C_#]$: Durchschnittliche Abweichung der produzierten
Stoffe gegenüber dem Schnitt der Gesamtpopulation Stoffe gegenüber dem Schnitt der Gesamtpopulation
- Anteile der Stoffe, die giftig sind - Anteile der Stoffe, die giftig sind
- $#Plants$ die Angreifer X abwehren könnten
## Messung ## Messung
- Ermitteln der Metriken für alle $x$ Generationen - Ermitteln der Metriken für alle $x$ Generationen
- Stabilisieren sich die Metriken bei identischem Aufbau konsistent? - Stabilisieren sich die Metriken bei identischem Aufbau konsistent?
- $#Plants$ die Angreifer X abwehren könnten - Ja, $\pm$ Random-Effekt
## Zu untersuchende Parameter ## Zu untersuchende Parameter

View File

@ -16,6 +16,7 @@ import System.IO
import System.Environment import System.Environment
import Data.Aeson import Data.Aeson
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import Options.Applicative import Options.Applicative
import Data.Semigroup ((<>)) import Data.Semigroup ((<>))
@ -47,10 +48,9 @@ exampleEnvironment addedC es pred tox =
, toxicCompounds = tox --[(Produced FPP,0.1)] ++ tox , toxicCompounds = tox --[(Produced FPP,0.1)] ++ tox
, possibleEnzymes = es -- [pps,fpps] ++ es , possibleEnzymes = es -- [pps,fpps] ++ es
, settings = Settings { automimicry = False , settings = Settings { automimicry = False
, predatorsRandom = False , predatorBehaviour = AttackInterval 10
, numPlants = 50 , numPlants = 50
, logEveryNIterations = 10 , logEveryNIterations = 10
, verbose = True
} }
} }
@ -83,8 +83,8 @@ exampleEnvironment addedC es pred tox =
-- Running the simulation -- Running the simulation
-- ---------------------- -- ----------------------
loop :: Int -> [Plant] -> Simulation -> IO () loop :: Int -> [Plant] -> Simulation -> CLIOptions -> IO ()
loop loopAmount ps env = loop' loopAmount 0 ps env loop loopAmount ps env opts = loop' loopAmount 0 ps env
where where
-- cache enzyme colorful-strings -- cache enzyme colorful-strings
@ -96,7 +96,7 @@ loop loopAmount ps env = loop' loopAmount 0 ps env
) <$> possibleEnzymes (snd env) ) <$> possibleEnzymes (snd env)
toxins :: [(Compound, Amount)] toxins :: [(Compound, Amount)]
toxins = toxicCompounds (snd env) toxins = toxicCompounds (snd env)
printEverything = verbose.settings.snd $ env printEverything = verbose opts
padded i str = take i $ str ++ repeat ' ' padded i str = take i $ str ++ repeat ' '
printEvery = 10 printEvery = 10
loop' :: Int -> Int -> [Plant] -> Simulation -> IO () loop' :: Int -> Int -> [Plant] -> Simulation -> IO ()
@ -107,15 +107,19 @@ loop loopAmount ps env = loop' loopAmount 0 ps env
putStrLn "" putStrLn ""
putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":" putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":"
newPlants <- simulate s $ do newPlants <- simulate s $ do
when (curLoop == 0) $ when (curLoop == 0) $ do
preds <- length <$> fromEnv predators
--- generates "pred1,pred2,pred3,.....predN"
let additionalHeader = intercalate "," $ ("pred"++).show <$> [1..preds]
tell $ "num_iter" tell $ "num_iter"
++ ",c_sum_mu,c_sum_sigma" ++ ",c_sum_mu,c_sum_sigma"
++ ",c_d_mu,c_d_sigma" ++ ",c_d_mu,c_d_sigma"
++ ",e_d_mu,e_d_sigma" ++ ",e_d_mu,e_d_sigma"
++ ",fitness_mean,fitness_sigma" ++ ",fitness_mean,fitness_sigma"
++ ",percent_toxic_mean,percent_toxic_sigma" ++ ",percent_toxic_mean,percent_toxic_sigma"
++ "," ++ additionalHeader
logIter <- fromEnv $ logEveryNIterations . settings logIter <- fromEnv $ logEveryNIterations . settings
(!fs,cs) <- unzip <$> fitness plants (!fs,cs) <- unzip <$> fitness curLoop plants
txns <- fmap (fromEnum . fst) <$> fromEnv toxicCompounds -- [Int] of id's of toxic compounds txns <- fmap (fromEnum . fst) <$> fromEnv toxicCompounds -- [Int] of id's of toxic compounds
let fps = zip plants fs -- gives us plants & their fitness in a tuple let fps = zip plants fs -- gives us plants & their fitness in a tuple
sumFitness = sum fs sumFitness = sum fs
@ -164,13 +168,17 @@ loop loopAmount ps env = loop' loopAmount 0 ps env
putStrLn $ "Percentage of toxins in Cmpnds= " ++ show toxs putStrLn $ "Percentage of toxins in Cmpnds= " ++ show toxs
hFlush stdout hFlush stdout
threadDelay $ 10*1000 -- sleep x*1000ns (=x ~ ms) threadDelay $ 10*1000 -- sleep x*1000ns (=x ~ ms)
when (curLoop `mod` logIter == 0) $ when (curLoop `mod` logIter == 0) $ do
preds <- fmap fst <$> fromEnv predators
let numPlantsCanRepel = (\ir -> sum $ (\p -> if sum ((p LA.!) <$> ir) > 0 then 1 else 0) <$> cs) . fmap fromEnum . irresistance <$> preds
addedData = intercalate "," $ show <$> numPlantsCanRepel
tell $ show curLoop tell $ show curLoop
++ "," ++ show c_sum_mu ++ "," ++ show c_sum_sigma ++ "," ++ show c_sum_mu ++ "," ++ show c_sum_sigma
++ "," ++ show c_d_mu ++ "," ++ show c_d_sigma ++ "," ++ show c_d_mu ++ "," ++ show c_d_sigma
++ "," ++ show e_d_mu ++ "," ++ show e_d_sigma ++ "," ++ show e_d_mu ++ "," ++ show e_d_sigma
++ "," ++ show (fst fns) ++ "," ++ show (snd fns) ++ "," ++ show (fst fns) ++ "," ++ show (snd fns)
++ "," ++ show (fst toxs) ++ "," ++ show (snd toxs) ++ "," ++ show (fst toxs) ++ "," ++ show (snd toxs)
++ "," ++ addedData
-- generate x new plants. -- generate x new plants.
np <- fromEnv (numPlants . settings) np <- fromEnv (numPlants . settings)
sequence . flip fmap [1..np] $ \_ -> do sequence . flip fmap [1..np] $ \_ -> do
@ -190,6 +198,7 @@ loop loopAmount ps env = loop' loopAmount 0 ps env
data CLIOptions = CLIOptions data CLIOptions = CLIOptions
{ environment :: Maybe FilePath { environment :: Maybe FilePath
, logfile :: FilePath , logfile :: FilePath
, verbose :: Bool
} }
cliOptParser :: Parser CLIOptions cliOptParser :: Parser CLIOptions
@ -208,6 +217,11 @@ cliOptParser = CLIOptions
<> value "simulation.log" <> value "simulation.log"
<> help "Name for the logfile" <> help "Name for the logfile"
) )
<*> switch
(long "verbose"
<> short 'v'
<> help "show 'gui' during process"
)
cliopts = info (cliOptParser <**> helper) cliopts = info (cliOptParser <**> helper)
(fullDesc (fullDesc
@ -236,15 +250,15 @@ main = do
putStrLn $ "reading environment: " ++ file putStrLn $ "reading environment: " ++ file
decodeStrict' <$> BS.readFile file decodeStrict' <$> BS.readFile file
let emptyPlants = replicate (numPlants . settings $ env) emptyPlant let emptyPlants = replicate (numPlants . settings $ env) emptyPlant
printEverything = verbose.settings $ env printEverything = verbose opts
enzs <- randomRs (0,length (possibleEnzymes env) - 1) <$> newStdGen enzs <- randomRs (0,length (possibleEnzymes env) - 1) <$> newStdGen
let startPlants = randomGenome 1 enzs (possibleEnzymes env) emptyPlants let startPlants = randomGenome 1 enzs (possibleEnzymes env) emptyPlants
--writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 poisonedTree --writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 poisonedTree
--writeFile "environment.json" . encode $ env LBS.writeFile "environment.json" . encode $ env
when printEverything $ putStr "\ESC[?1049h" when printEverything $ putStr "\ESC[?1049h"
loghandle <- openFile (logfile opts) WriteMode loghandle <- openFile (logfile opts) WriteMode
putStrLn $ "logging to: " ++ logfile opts putStrLn $ "logging to: " ++ logfile opts
loop 2000 startPlants (loghandle,env) loop 2000 startPlants (loghandle,env) opts
hClose loghandle hClose loghandle
when printEverything $ do when printEverything $ do
putStrLn "Simulation ended. Press key to exit." putStrLn "Simulation ended. Press key to exit."

View File

@ -429,7 +429,7 @@
"fitnessImpact": 0.4901681711436634, "fitnessImpact": 0.4901681711436634,
"irresistance": [ "irresistance": [
{ {
"contents": 27, "contents": 26,
"tag": "GenericCompound" "tag": "GenericCompound"
} }
], ],
@ -493,8 +493,10 @@
"automimicry": false, "automimicry": false,
"logEveryNIterations": 10, "logEveryNIterations": 10,
"numPlants": 100, "numPlants": 100,
"predatorsRandom": false, "predatorBehaviour": {
"verbose": false "contents": 10,
"tag": "AttackInterval"
}
}, },
"soil": [ "soil": [
[ [

View File

@ -111,12 +111,19 @@ data Predator = Predator { irresistance :: [Compound]
instance FromJSON Predator instance FromJSON Predator
instance ToJSON Predator instance ToJSON Predator
data PredatorBehaviour = AlwaysAttack
| AttackRandom
| AttackInterval Int
deriving (Show, Eq, Generic)
instance FromJSON PredatorBehaviour
instance ToJSON PredatorBehaviour
-- | Settings to enable/disable parts of the simulation -- | Settings to enable/disable parts of the simulation
data Settings = Settings { automimicry :: Bool -- ^ do we have automimicry-protection? data Settings = Settings { automimicry :: Bool -- ^ do we have automimicry-protection?
, predatorsRandom :: Bool -- ^ do predators always appear or according to their random distribution? , predatorBehaviour :: PredatorBehaviour -- ^ do predators always appear or according to their random distribution?
, numPlants :: Int -- ^ number of plants in starting population , numPlants :: Int -- ^ number of plants in starting population
, logEveryNIterations :: Int -- ^ log status every @loopNumber `mod` logEveryNIterations == 0@ , logEveryNIterations :: Int -- ^ log status every @loopNumber `mod` logEveryNIterations == 0@
, verbose :: Bool -- ^ print visual statistics instead of just logging
} }
deriving (Show, Eq, Generic) deriving (Show, Eq, Generic)
@ -199,19 +206,20 @@ instance Eq Plant where
type Fitness = Double type Fitness = Double
fitness :: [Plant] -> World [(Fitness, Vector Amount)] fitness :: Int -> [Plant] -> World [(Fitness, Vector Amount)]
fitness ps = do fitness iter ps = do
nutrients <- mapM absorbNutrients ps -- absorb soil nutrients <- mapM absorbNutrients ps -- absorb soil
products <- sequenceA $ zipWith produceCompounds ps nutrients -- produce compounds products <- sequenceA $ zipWith produceCompounds ps nutrients -- produce compounds
ds <- liftIO $ randoms <$> newStdGen ds <- liftIO $ randoms <$> newStdGen
preds <- fromEnv predators preds <- fromEnv predators
randPred <- fromEnv (predatorsRandom . settings) predB <- fromEnv (predatorBehaviour . settings)
let let
appearingPredators = if randPred then appearingPredators = case predB of
fmap (fst . fst) . filter (\((_,p),r) -> p > r) $ zip preds ds -- assign one probability to each predator, filter those who appear, throw random data away again. AttackRandom -> fmap (fst . fst) . filter (\((_,p),r) -> p > r) $ zip preds ds -- assign one probability to each predator, filter those who appear, throw random data away again.
-- appearingPredators is now a sublist of preds without the probability. -- appearingPredators is now a sublist of preds without the probability.
else AttackInterval lngth -> fmap fst . filter (\(_,p) -> iter `mod` floor (fromIntegral lngth / p) < lngth) $ preds
fst <$> preds -- else just forget about probabilities -- attacker appears for length lngth iterations averaging out at p over longer timespans.
AlwaysAttack -> fst <$> preds -- else just forget about probabilities
automimicry <- fromEnv (automimicry . settings) automimicry <- fromEnv (automimicry . settings)
popDefense <- if automimicry then popDefense <- if automimicry then
forM appearingPredators $ \p -> do forM appearingPredators $ \p -> do
@ -310,7 +318,7 @@ haploMate (Plant genes abs) = do
(stay, (e,q,a):stay') = splitAt (i `mod` length g - 2) g (stay, (e,q,a):stay') = splitAt (i `mod` length g - 2) g
addGene :: [Double] -> [Int] -> Genome -> Genome addGene :: [Double] -> [Int] -> Genome -> Genome
addGene (r:rs) (s:ss) g = if r < 0.005 then (enzymes !! s,1,1):g else g addGene (r:rs) (s:ss) g = if r < 0.005 then (enzymes !! s,1,0.5):g else g
noiseActivation :: [Double] -> Genome -> Genome noiseActivation :: [Double] -> Genome -> Genome
noiseActivation (r:rs) ((e,q,a):gs) = (e,q,max 0 $ min 1 $ a-0.01+0.02*r):noiseActivation rs gs noiseActivation (r:rs) ((e,q,a):gs) = (e,q,max 0 $ min 1 $ a-0.01+0.02*r):noiseActivation rs gs