{-# LANGUAGE RecordWildCards #-} module Environment where import Data.Functor ((<$>)) import Control.Applicative ((<*>)) import Control.Monad (forM_) import Control.Monad.Reader import Data.List (permutations, subsequences) import Numeric.LinearAlgebra type Probability = Double type Quantity = Int type Activation = Double type Amount = Double -- | Nutrients are the basis for any reaction and are found in the environment of the plant. data Nutrient = Sulfur | Phosphor | Nitrate | Photosynthesis deriving (Show, Enum, Bounded, Eq) -- | Fixed, non-generic Components data Component = PP | FPP deriving (Show, Enum, Bounded, Eq) -- | Compounds are either direct nutrients, already processed components or GenericEnzymes data Compound = Substrate Nutrient | Produced Component | GenericEnzyme Int deriving (Show, Eq) instance Enum Compound where toEnum x | x <= maxS = Substrate . toEnum $ x | x - (maxS+1) <= maxP = Produced . toEnum $ x - (maxS + 1) | otherwise = GenericEnzyme $ x - (maxS + 1) - (maxP + 1) where maxS = fromEnum (maxBound :: Nutrient) maxP = fromEnum (maxBound :: Component) fromEnum (Substrate x) = fromEnum x fromEnum (Produced x) = fromEnum x + maxS + 1 where maxS = fromEnum (maxBound :: Nutrient) fromEnum (GenericEnzyme x) = x + maxS + maxP + 2 where maxS = fromEnum (maxBound :: Nutrient) maxP = fromEnum (maxBound :: Component) -- | Enzymes are the main reaction-driver behind synthesis of intricate compounds. -- -- They are assumed to be reversible. data Enzyme = Enzyme { enzymeName :: String -- ^ Name of the Enzyme. , substrateRequirements :: [(Compound,Amount)] -- ^ needed for reaction to take place , synthesis :: ((Compound,Amount),(Compound,Amount)) -- ^ given x in amount -a, this will produce y in amount b , dominance :: Maybe Amount -- ^ in case of competition for nutrients this denotes the priority -- Nothing = max possible } deriving (Show, Eq) -- | conviniently make an Enzyme using 1 of the first compund to produce 1 of the second makeSimpleEnzyme :: Compound -> Compound -> Enzyme makeSimpleEnzyme a b = Enzyme (show a ++ " -> " ++ show b) [] ((a,-1),(b,1)) Nothing --Example "enzymes" could be: pps :: Enzyme -- uses Phosphor from Substrate to produce PP pps = Enzyme "PPS" [(Substrate Phosphor,1)] ((Substrate Phosphor,(-1)),(Produced PP,1)) Nothing fpps :: Enzyme -- PP -> FPP fpps = makeSimpleEnzyme (Produced PP) (Produced FPP) -- Evironment -- ---------- -- | In the environment we have predators that impact the fitness of our plants and -- may be resistant to some compounds the plant produces. They can also differ in -- their intensity. data Predator = Predator { resistance :: [Compound] -- ^ list of components this predator is resistant to , fitnessImpact :: Amount -- ^ impact on the fitness of a plant -- (~ agressiveness of the herbivore) } deriving (Show, Eq) -- Exemplatory: greenfly :: Predator -- 20% of plants die to greenfly, but the fly is greenfly = Predator [] 0.2 -- killed by any toxic Component -- The environment itself is just the soil and the predators. Extensions would be possible. data Environment = Environment { soil :: [(Nutrient, Amount)] -- ^ soil is a list of nutrients available to the plant. , predators :: [(Predator, Probability)] -- ^ Predators with the probability of appearance in this generation. , metabolismIteration :: Int -- ^ Number of iterations for producing compounds , maxCompound :: Int -- ^ Number of possible Compounds -- 'maxCompound' should be greater than #Nutrient + #Products. -- Rest will get filled up with 'GenericEnzyme i' -- -- To find the 'maxCompound' without 'GenericEnzyme' use -- 'maxComponent = fromEnum (maxBound :: Nutrient) + fromEnum (maxBound :: Component) + 1' , toxicCompounds :: [Compound] -- ^ Compounds considered to be toxic in this environment. } deriving (Show, Eq) -- helper function. Allows for [0..maxCompoundWithoutGeneric] :: [Compound] with all non-generic Compounds maxCompoundWithoutGeneric :: Int maxCompoundWithoutGeneric = fromEnum (maxBound :: Nutrient) + fromEnum (maxBound :: Component) + 1 -- Example: exampleEnvironment :: Environment exampleEnvironment = Environment { soil = [ (Nitrate, 2) , (Phosphor, 3) , (Photosynthesis, 10) ] , predators = [ (greenfly, 0.1) ] , metabolismIteration = 100 , maxCompound = maxCompoundWithoutGeneric , toxicCompounds = [Produced FPP] } type World a = ReaderT Environment IO a -- Plants -- ------ -- Plants consist of a Genome responsible for creation of the PSM and also an -- external state how many nutrients and compounds are currently inside the plant. type Genome = [(Enzyme, Quantity, Activation)] data Plant = Plant { genome :: Genome -- ^ the genetic characteristic of the plant , absorbNutrients :: World [(Nutrient,Amount)] -- ^ the capability to absorb nutrients given an environment } instance Show Plant where show p = "Plant with Genome " ++ show (genome p) instance Eq Plant where a == b = genome a == genome b -- | The following example yields in the example-environment this population: -- -- >>> printPopulation [pps, fpps] plants -- Population: -- PPS ______oöö+++______oöö+++____________oöö+++oöö+++ -- FPPS ____________oöö+++oöö+++______oöö+++______oöö+++ plants :: [Plant] plants = (\g -> Plant g defaultAbsorption) <$> genomes where enzymes = [pps, fpps] quantity = [1,2] :: [Quantity] activation = [0.7, 0.9, 1] genomes = do e <- permutations enzymes e' <- subsequences e q <- quantity a <- activation return $ (,,) <$> e' <*> [q] <*> [a] defaultAbsorption = soil <$> ask >>= return . fmap ( limit Phosphor 2 . limit Nitrate 1 . limit Sulfur 0 ) -- custom absorbtion with helper-function: limit :: Nutrient -> Amount -> (Nutrient, Amount) -> (Nutrient, Amount) limit n a (n', a') | n == n' = (n, min a a') -- if we should limit, then we do ;) | otherwise = (n', a') -- Fitness -- ------- -- The fitness-measure is central for the generation of offspring and the -- simulation. It evaluates the probability for passing on genes given a plant in -- an environment. 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 return survivalRate -- 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 numIter <- metabolismIteration <$> ask numCompounds <- maxCompound <$> ask let initialAmount = assoc (numCompounds+1) 0 ((\(n,a) -> (fromEnum $ Substrate n,a)) <$> substrate) enzymes = (\(e,q,a) -> (synthesis e,(fromIntegral q)*a)) <$> genes -- [(((Component,Amount),(Component,Amount)),q*a)], Amount got * by quantity & activation positions = concat $ (\(((i,ia),(o,oa)),f) -> [((fromEnum i,fromEnum i),2*f*ia),((fromEnum o,fromEnum i),oa),((fromEnum i,fromEnum o),f*oa)]) <$> enzymes -- [((row,column),amount)] mat = accum (konst 0 (numCompounds+1,numCompounds+1)) (+) positions --accumulate all entries into one matrix. -- mat is now the rate of change in u'(t) = A u(t) (l,v) = eig (ident (numCompounds+1) + ((*0.01) `cmap` mat)) -- use u(t+1) = u(t) + A u(t) = (E + A) u(t) for iteration final = (realPart `cmap` (v <> ((^numIter) `cmap` diag l) <> (tr v))) #> initialAmount -- (E + A)^numIter * t_0 for numIter iterations. return final deterPredators :: Vector Amount -> World Probability deterPredators cs = do ps <- predators <$> ask ts <- toxicCompounds <$> ask let deter :: Predator -> Bool -- if any (amount of toxin t > 0| for all toxins t | t not in p's resistance-list) deter p = or [cs ! (fromEnum t) > 0 | t <- ts, not (t `elem` resistance p)] -- multipy (probability of occurence * intensity of destruction| for all predators, if not deterred by toxins return . product $ [prob*fitnessImpact p | (p,prob) <- ps, not $ deter p] -- Mating & Creation of diversity -- ------------------------------ -- Running the simulation -- ---------------------- main = do putStrLn "Environment:" print exampleEnvironment putStrLn "Example population:" printPopulation [pps, fpps] plants fitness <- runReaderT (sequence $ (\a -> do p <- absorbNutrients a >>= produceCompounds a; (,) p <$> deterPredators p) <$> plants) exampleEnvironment mapM_ print fitness -- Utility Functions -- ----------------- getAmountOf :: Compound -> [(Compound, Amount)] -> Amount getAmountOf c = sum . fmap snd . filter ((== c) . fst) printPopulation :: [Enzyme] -> [Plant] -> IO () printPopulation es ps = do let padded i str = take i $ str ++ repeat ' ' putStrLn "Population:" forM_ es $ \e -> do putStr $ padded 8 (show e) forM_ ps $ \(Plant g _) -> do let curE = sum $ map (\(_,q,a) -> (fromIntegral q)*a) . filter (\(e',_,_) -> e == e') $ g plot x | x > 2 = "O" | x > 1 = "+" | x > 0.7 = "ö" | x > 0.5 = "o" | x > 0 = "." | otherwise = "_" putStr (plot curE) putStrLn ""