plant-fitness can now depend on multiple plants
This commit is contained in:
parent
3dba2a478b
commit
2b7d0e6682
@ -86,7 +86,7 @@ loop loopAmount = loop' loopAmount 0
|
|||||||
putStrLn ""
|
putStrLn ""
|
||||||
putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":"
|
putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":"
|
||||||
newPlants <- flip runReaderT e $ do
|
newPlants <- flip runReaderT e $ do
|
||||||
! fs <- sequence (fitness <$> plants)
|
! fs <- fitness plants
|
||||||
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
|
||||||
pe <- asks possibleEnzymes
|
pe <- asks possibleEnzymes
|
||||||
@ -114,13 +114,13 @@ main :: IO ()
|
|||||||
main = do
|
main = do
|
||||||
hSetBuffering stdin NoBuffering
|
hSetBuffering stdin NoBuffering
|
||||||
hSetBuffering stdout NoBuffering
|
hSetBuffering stdout NoBuffering
|
||||||
randomCompounds <- makeHead (Substrate Photosynthesis) <$> generateTreeFromList 40 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly x compounds
|
randomCompounds <- makeHead (Substrate Photosynthesis) <$> generateTreeFromList 50 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly x compounds
|
||||||
ds <- randoms <$> newStdGen
|
ds <- randoms <$> newStdGen
|
||||||
probs <- randomRs (0.2,0.7) <$> newStdGen
|
probs <- randomRs (0.2,0.7) <$> newStdGen
|
||||||
let emptyPlants = replicate 100 emptyPlant
|
let emptyPlants = replicate 50 emptyPlant
|
||||||
poisonedTree = poisonTree ds randomCompounds
|
poisonedTree = poisonTree ds randomCompounds
|
||||||
poisonCompounds = foldMap (\(a,b) -> [(b,a) | a > 0.5]) poisonedTree
|
poisonCompounds = foldMap (\(a,b) -> [(b,a) | a > 0.5]) poisonedTree
|
||||||
predators <- generatePredators 0.5 poisonedTree
|
predators <- generatePredators 0.8 poisonedTree
|
||||||
let env = exampleEnvironment (getTreeSize randomCompounds) (generateEnzymeFromTree randomCompounds) (zip predators probs) poisonCompounds
|
let env = exampleEnvironment (getTreeSize randomCompounds) (generateEnzymeFromTree randomCompounds) (zip predators probs) poisonCompounds
|
||||||
printEnvironment env
|
printEnvironment env
|
||||||
writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 poisonedTree
|
writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 poisonedTree
|
||||||
|
@ -145,22 +145,27 @@ instance Eq Plant where
|
|||||||
|
|
||||||
type Fitness = Double
|
type Fitness = Double
|
||||||
|
|
||||||
fitness :: Plant -> World Fitness
|
fitness :: [Plant] -> World [Fitness]
|
||||||
fitness p = do
|
fitness ps = do
|
||||||
nutrients <- absorbNutrients p -- absorb soil
|
nutrients <- mapM absorbNutrients ps -- absorb soil
|
||||||
products <- produceCompounds p nutrients -- produce compounds
|
products <- sequenceA $ zipWith produceCompounds ps nutrients -- produce compounds
|
||||||
survivalRate <- deterPredators products -- defeat predators with produced compounds
|
ds <- liftIO $ randoms <$> newStdGen
|
||||||
let sumEnzymes = sum $ (\(_,q,a) -> fromIntegral q*a) <$> genome p -- amount of enzymes * activation = resources "wasted"
|
preds <- asks predators
|
||||||
staticCostOfEnzymes = 1 - 0.01*sumEnzymes -- static cost of creating enzymes
|
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
|
-- primaryEnzymes = filter (\(e,_,_) -> case (fst.fst.synthesis) e of -- select enzymes which use substrate
|
||||||
-- Substrate _ -> True
|
-- Substrate _ -> True
|
||||||
-- otherwise -> False)
|
-- otherwise -> False)
|
||||||
-- (genome p)
|
-- (genome p)
|
||||||
nutrientsAvailable <- fmap snd <$> asks soil
|
nutrientsAvailable <- fmap snd <$> asks soil
|
||||||
let nutrientsLeft = [products ! i | i <- [0..fromEnum (maxBound :: Nutrient)]]
|
let nutrientsLeft = (\p -> [p ! i | i <- [0..fromEnum (maxBound :: Nutrient)]]) <$> products
|
||||||
nutrientRatio = minimum $ zipWith (/) nutrientsLeft nutrientsAvailable
|
nutrientRatio = minimum . zipWith (flip (/)) nutrientsAvailable <$> nutrientsLeft
|
||||||
costOfEnzymes = max 0 $ staticCostOfEnzymes - nutrientRatio * 0.1 -- cost to keep enzymes are static costs + amount of nutrient sucked out of the primary cycle
|
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 $ survivalRate * costOfEnzymes
|
return $ zipWith (*) survivalRate costOfEnzymes
|
||||||
-- can also be written as, but above is more clear.
|
-- can also be written as, but above is more clear.
|
||||||
-- fitness p = absorbNutrients p >>= produceCompounds p >>= deterPredators
|
-- fitness p = absorbNutrients p >>= produceCompounds p >>= deterPredators
|
||||||
|
|
||||||
@ -183,21 +188,17 @@ produceCompounds (Plant genes _) substrate = do
|
|||||||
|
|
||||||
|
|
||||||
-- TODO:
|
-- 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.
|
-- - dampen full-force due to auto-mimicry-effect. => Fitness would not depend on single plant.
|
||||||
deterPredators :: Vector Amount -> World Probability
|
deterPredators :: [Vector Amount] -> [(Predator,Amount)] -> Vector Amount -> World Probability
|
||||||
deterPredators cs = do
|
deterPredators others appearingPredators cs = do
|
||||||
ps <- asks predators
|
-- ps <- asks predators
|
||||||
ts <- asks toxicCompounds
|
ts <- asks toxicCompounds
|
||||||
ds <- liftIO $ randoms <$> newStdGen
|
|
||||||
let
|
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
|
deter :: Predator -> Double
|
||||||
-- multiply (toxicity of t with 100% effectiveness at l| for all toxins t; and t in p's irresistance-list)
|
-- 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]
|
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)
|
-- 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
|
-- Mating & Creation of diversity
|
||||||
-- ------------------------------
|
-- ------------------------------
|
||||||
|
Loading…
Reference in New Issue
Block a user