plant-fitness can now depend on multiple plants

This commit is contained in:
Stefan Dresselhaus
2018-05-29 22:20:33 +02:00
parent 3dba2a478b
commit 2b7d0e6682
2 changed files with 24 additions and 23 deletions

View File

@ -145,22 +145,27 @@ instance Eq Plant where
type Fitness = Double
fitness :: Plant -> World Fitness
fitness p = do
nutrients <- absorbNutrients p -- absorb soil
products <- produceCompounds p nutrients -- produce compounds
survivalRate <- deterPredators products -- defeat predators with produced compounds
let sumEnzymes = sum $ (\(_,q,a) -> fromIntegral q*a) <$> genome p -- amount of enzymes * activation = resources "wasted"
staticCostOfEnzymes = 1 - 0.01*sumEnzymes -- static cost of creating enzymes
fitness :: [Plant] -> World [Fitness]
fitness ps = do
nutrients <- mapM absorbNutrients ps -- absorb soil
products <- sequenceA $ zipWith produceCompounds ps nutrients -- produce compounds
ds <- liftIO $ randoms <$> newStdGen
preds <- asks predators
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
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 = [products ! i | i <- [0..fromEnum (maxBound :: Nutrient)]]
nutrientRatio = minimum $ zipWith (/) nutrientsLeft nutrientsAvailable
costOfEnzymes = max 0 $ staticCostOfEnzymes - nutrientRatio * 0.1 -- cost to keep enzymes are static costs + amount of nutrient sucked out of the primary cycle
return $ survivalRate * costOfEnzymes
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
@ -183,21 +188,17 @@ produceCompounds (Plant genes _) substrate = do
-- TODO:
-- - choose predators beforehand, then only apply those who appear in full force.
-- - dampen full-force due to auto-mimicry-effect. => Fitness would not depend on single plant.
deterPredators :: Vector Amount -> World Probability
deterPredators cs = do
ps <- asks predators
deterPredators :: [Vector Amount] -> [(Predator,Amount)] -> Vector Amount -> World Probability
deterPredators others appearingPredators cs = do
-- ps <- asks predators
ts <- asks toxicCompounds
ds <- liftIO $ randoms <$> newStdGen
let
appearingPredators = fmap fst . filter (\((_,p),r) -> p > r) $ zip ps ds -- assign one probability to each predator, filter those who appear, throw random data away again.
-- appearingPredators is now a sublist of ps.
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])
return $ product [min 1 ((1-prob) * fitnessImpact p / deter p) | (p,prob) <- appearingPredators]
-- Mating & Creation of diversity
-- ------------------------------