added automimicry-effect
This commit is contained in:
@ -84,9 +84,19 @@ data Predator = Predator { irresistance :: [Compound]
|
||||
, fitnessImpact :: Amount
|
||||
-- ^ impact on the fitness of a plant
|
||||
-- (~ agressiveness of the herbivore)
|
||||
, numAttacks :: Amount
|
||||
-- ^ Avarage number of attacks in a generation of appearance
|
||||
-- (~ mean of poisson-distribution)
|
||||
} deriving (Show, Eq)
|
||||
|
||||
-- The environment itself is just the soil and the predators. Extensions would be possible.
|
||||
-- | Settings to enable/disable parts of the simulation
|
||||
data Settings = Settings { automimicry :: Bool -- ^ do we have automimicry-protection?
|
||||
, predatorsRandom :: Bool -- ^ do predators always appear or according to their random distribution?
|
||||
, numPlants :: Int -- ^ number of plants in starting population
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- | The environment itself.
|
||||
|
||||
data Environment =
|
||||
Environment
|
||||
@ -108,6 +118,7 @@ data Environment =
|
||||
-- Kills 100% of Predators above Amount.
|
||||
, possibleEnzymes :: [Enzyme]
|
||||
-- ^ All enzymes that can be created by genetic manipulation in this setting.
|
||||
, settings :: Settings
|
||||
} deriving (Show, Eq)
|
||||
|
||||
-- helper function. Allows for [0..maxCompoundWithoutGeneric] :: [Compound] with all non-generic Compounds
|
||||
@ -151,23 +162,28 @@ fitness ps = do
|
||||
products <- sequenceA $ zipWith produceCompounds ps nutrients -- produce compounds
|
||||
ds <- liftIO $ randoms <$> newStdGen
|
||||
preds <- asks predators
|
||||
randPred <- asks (predatorsRandom . settings)
|
||||
let
|
||||
appearingPredators = fmap 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 ps.
|
||||
survivalRate <- mapM (deterPredators products preds) products -- defeat predators with produced compounds
|
||||
appearingPredators = if randPred then
|
||||
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.
|
||||
else
|
||||
fst <$> preds -- else just forget about probabilities
|
||||
automimicry <- asks (automimicry . settings)
|
||||
popDefense <- if automimicry then
|
||||
forM appearingPredators $ \p -> do
|
||||
as <- mapM (deterPredator p) products -- how good can an individual deter p
|
||||
return $ sum as / fromIntegral (length as) -- how good can the population deter p on average
|
||||
else
|
||||
return $ repeat 1
|
||||
survivalRate <- mapM (deterPredators (zip appearingPredators popDefense)) products -- defeat predators with produced compounds
|
||||
let sumEnzymes = sum . fmap (\(_,q,a) -> fromIntegral q*a) . genome <$> ps -- amount of enzymes * activation = resources "wasted"
|
||||
staticCostOfEnzymes = (\x -> 1 - 0.01*x) <$> sumEnzymes -- static cost of creating enzymes
|
||||
-- primaryEnzymes = filter (\(e,_,_) -> case (fst.fst.synthesis) e of -- select enzymes which use substrate
|
||||
-- Substrate _ -> True
|
||||
-- otherwise -> False)
|
||||
-- (genome p)
|
||||
nutrientsAvailable <- fmap snd <$> asks soil
|
||||
let nutrientsLeft = (\p -> [p ! i | i <- [0..fromEnum (maxBound :: Nutrient)]]) <$> products
|
||||
nutrientRatio = minimum . zipWith (flip (/)) nutrientsAvailable <$> nutrientsLeft
|
||||
costOfEnzymes = max 0 <$> zipWith (\s n -> s-n*0.1) staticCostOfEnzymes nutrientRatio -- cost to keep enzymes are static costs + amount of nutrient sucked out of the primary cycle
|
||||
return $ zipWith (*) survivalRate costOfEnzymes
|
||||
-- can also be written as, but above is more clear.
|
||||
-- fitness p = absorbNutrients p >>= produceCompounds p >>= deterPredators
|
||||
|
||||
produceCompounds :: Plant -> [(Nutrient, Amount)] -> World (Vector Amount)
|
||||
produceCompounds (Plant genes _) substrate = do
|
||||
@ -186,19 +202,23 @@ produceCompounds (Plant genes _) substrate = do
|
||||
-- faster, because no inversions and optimized eig.
|
||||
return final
|
||||
|
||||
-- Automimicry: see https://www.ncbi.nlm.nih.gov/pmc/articles/PMC2275178/#__sec2title Formula 2.1
|
||||
-- Note: F(D) is "costOfEnzymes", but in 'fitness' we multiply "costOfEnzymes" already,
|
||||
-- so F(D) is omitted
|
||||
-- A(d_hat) is ahat * numAttacks p, because ahat is only deterrence of the population
|
||||
-- and does not incorporate the number of attacks, which A(d_hat) in the paper does.
|
||||
deterPredators :: [(Predator, Double)] -> Vector Amount -> World Probability
|
||||
deterPredators appearingPredators compounds = do
|
||||
deters <- forM appearingPredators $ \(p,ahat) -> do
|
||||
myDeter <- deterPredator p compounds
|
||||
return $ exp $ negate $ numAttacks p * ahat * myDeter -- exp due to assumption that number of attacks are poisson-distributed.
|
||||
return $ product deters
|
||||
|
||||
-- TODO:
|
||||
-- - dampen full-force due to auto-mimicry-effect. => Fitness would not depend on single plant.
|
||||
deterPredators :: [Vector Amount] -> [(Predator,Amount)] -> Vector Amount -> World Probability
|
||||
deterPredators others appearingPredators cs = do
|
||||
-- ps <- asks predators
|
||||
ts <- asks toxicCompounds
|
||||
let
|
||||
deter :: Predator -> Double
|
||||
-- multiply (toxicity of t with 100% effectiveness at l| for all toxins t; and t in p's irresistance-list)
|
||||
deter p = product [1 - min 1 (cs ! fromEnum t / l) | (t,l) <- ts, t `elem` irresistance p]
|
||||
-- multiply (probability of occurence * intensity of destruction / probability to deter predator | for all predators)
|
||||
return $ product [min 1 ((1-prob) * fitnessImpact p / deter p) | (p,prob) <- appearingPredators]
|
||||
|
||||
deterPredator :: Predator -> Vector Amount -> World Double
|
||||
deterPredator p comps = do
|
||||
toxins <- asks toxicCompounds
|
||||
return $ product [1 - min 1 (comps ! fromEnum t * l) | (t,l) <- toxins, t `elem` irresistance p]
|
||||
|
||||
-- Mating & Creation of diversity
|
||||
-- ------------------------------
|
||||
|
Reference in New Issue
Block a user