diff --git a/app/Main.hs b/app/Main.hs index 07a4e4b..f798183 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -38,7 +38,7 @@ exampleEnvironment addedC es pred tox = , maxCompound = maxCompoundWithoutGeneric + addedC , toxicCompounds = tox --[(Produced FPP,0.1)] ++ tox , possibleEnzymes = es -- [pps,fpps] ++ es - , settings = Settings { automimicry = False + , settings = Settings { automimicry = True , predatorsRandom = False , numPlants = 150 } @@ -88,7 +88,6 @@ loop loopAmount ps env = loop' loopAmount 0 ps env toxins = toxicCompounds env padded i str = take i $ str ++ repeat ' ' printEvery = 10 - addedConstFitness = 0.1 loop' :: Int -> Int -> [Plant] -> Environment -> IO () loop' loopAmount curLoop plants e = unless (loopAmount+1 == curLoop) $ do when (curLoop `mod` printEvery == 0) $ do @@ -97,7 +96,7 @@ loop loopAmount ps env = loop' loopAmount 0 ps env putStrLn "" putStrLn $ "Generation " ++ show curLoop ++ " of " ++ show loopAmount ++ ":" newPlants <- flip runReaderT e $ do - (!fs,cs) <- unzip . fmap (\(f,c) -> (f,c)) <$> fitness plants + (!fs,cs) <- unzip <$> fitness plants let fps = zip plants fs -- gives us plants & their fitness in a tuple sumFitness = sum fs when (curLoop `mod` printEvery == 0) $ liftIO $ do @@ -126,16 +125,16 @@ main :: IO () main = do hSetBuffering stdin NoBuffering --hSetBuffering stdout NoBuffering - randomCompounds <- makeHead (Substrate PPM) <$> generateTreeFromList 20 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly x compounds + randomCompounds <- makeHead (Substrate PPM) <$> generateTreeFromList 40 (toEnum <$> [(maxCompoundWithoutGeneric+1)..] :: [Compound]) -- generate roughly x compounds ds <- randoms <$> newStdGen probs <- randomRs (0.2,0.7) <$> newStdGen let poisonedTree = poisonTree ds randomCompounds - poisonCompounds = foldMap (\(a,b) -> [(b,a) | a > 0.2]) poisonedTree + poisonCompounds = foldMap (\(a,b) -> [(b,a) | a > 0.5]) poisonedTree predators <- generatePredators 0.5 poisonedTree let env = exampleEnvironment (getTreeSize randomCompounds) (generateEnzymeFromTree randomCompounds) (zip predators probs) poisonCompounds emptyPlants = replicate (numPlants . settings $ env) emptyPlant enzs <- randomRs (0,length (possibleEnzymes env) - 1) <$> newStdGen - let startPlants = randomGenome 10 enzs (possibleEnzymes env) emptyPlants + let startPlants = randomGenome 1 enzs (possibleEnzymes env) emptyPlants printEnvironment env writeFile "poison.twopi" $ generateDotFromPoisonTree "poison" 0.5 poisonedTree putStr "\ESC[?1049h" @@ -221,3 +220,6 @@ generateEnzymeFromTree t = (makeSimpleEnzyme c . getElement <$> sts) where c = getElement t sts = getSubTrees t + + +stepDebug a = liftIO $ print a >> void getChar diff --git a/src/Environment.hs b/src/Environment.hs index dceb9e1..10293a5 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -175,14 +175,14 @@ fitness ps = do return $ repeat 1 dieRate <- mapM (dieToPredators (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 + staticCostOfEnzymes = (\x -> 1 - 0.02*x) <$> sumEnzymes -- static cost of creating enzymes 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.01) staticCostOfEnzymes nutrientRatio -- 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 survivalRate = (1-) <$> dieRate - return $ (,) <$> zipWith (*) survivalRate costOfEnzymes - <*> products + return $ zip (zipWith (*) survivalRate costOfEnzymes) + (products) produceCompounds :: Plant -> [(Nutrient, Amount)] -> World (Vector Amount) produceCompounds (Plant genes _) substrate = do @@ -210,9 +210,10 @@ dieToPredators :: [(Predator, Double)] -> Vector Amount -> World Probability dieToPredators [] _ = return 0 -- if no predator, no dying. dieToPredators appearingPredators compounds = do deters <- forM appearingPredators $ \(p,ahat) -> do - myDeter <- dieToPredator p compounds - return $ ahat * myDeter -- exp due to assumption that number of attacks are poisson-distributed. - return $ product deters + myDieRate <- dieToPredator p compounds + return $ exp $ -(ahat*numAttacks p) * myDieRate -- exp due to assumption that number of attacks are poisson-distributed. + -- myDieRate = 1 - Survival = 1 - S(D) in the paper + return $ 1 - product deters dieToPredator :: Predator -> Vector Amount -> World Double