module FeedingRates where import System.Environment import System.Random import Control.Monad import System.Directory import System.Cmd import Data.Char import Data.Maybe import Data.List import Numeric import Types import System.FilePath getCommat :: Foodweb -> Matrix Double getCommat inputFW = functionToMatrix (alphaijElem inputFW res) (length (wij inputFW)) where res = fij (info inputFW) (wij inputFW) {- writeFile (x ++ ".alpha.txt") $ outputMatrix $ map (map show) alphaij -} --splits a txt file with matrices in, into lines, then drops any extra spaces, then drops empty lists from start of lists splitFile file = do src <- readFile file src <- return $ dropWhile null $ map (dropWhile isSpace) $ lines src let (s1,_:rest) = break null src -- breaks the first matrix from the rest (s2,_:s3) = break null $ dropWhile null rest -- separates out the last two matrices from each other return $ map (unlines . map tabify) [s1,s2,s3] putCM :: Foodweb -> Foodweb putCM fw = fw{cm=getCommat fw} tableTuple stabs1 = unlines $ [(show (map fst stabs1!!n)) ++ "\t" ++ (show $ map snd stabs1!!n)|n<-[0..(length stabs1)-1]] ------------change matrix type downwards sumT :: [Info] -> Matrix Double -> Int -> Double sumT info wij j= sum $ zipWith (*) (transpose wij !! j) (map biomass info) --checked fij :: [Info] -> Matrix Double -> Matrix Double fij info wij = res where is = [0..length wij-1] res = [[fijElem info wij res j i | i <- is] | j <- is] fijElem :: [Info] -> Matrix Double -> Matrix Double -> Int -> Int -> Double fijElem info wij fij i j = if sumT info wij j == 0 then 0 else ((wij!!i!!j) * biomass infoi * ((deathRate infoj * biomass infoj) + mi j)) / (aeff infoj * peff infoj * sumT info wij j) where infoi = info!!i infoj = info!!j mi j = sum [fij !! j !! i | i <- [0..j-1]] --fij checked and is correct and working alphaijElem :: Foodweb->Matrix Double-> Int -> Int -> Double alphaijElem (Foodweb names info wij _) res i j | i > j && i /= d = -resij/(biomassj) | i < j && i /= d = aeffi*peffi*resji/biomassj --error $ show (aeffj,peffj,resij,biomassi) -- | i == j && i /= d = -s*(deathRate infoi) -- will need to link up so we can insert real value of s in here | i == j && i == d = -(sumTdd)/(biomassd) -- need to check correct | i /= j && i == d = (deathRate infoj) + (1-aeffj)*(sumTdi1) + (sumTdi2)/(biomassj) - res!!d!!j/biomassj where s = 1 d = fromMaybe (-1) $ findIndex (== 0) (map deathRate info) infoi = info!!i infoj = info!!j infod = info!!d resij = res!!i!!j resji = res!!j!!i resdj = res!!d!!j biomassd = biomass infod biomassj = biomass infoj biomassi = biomass infoi peffi = peff infoi peffj = peff infoj aeffi = aeff infoi aeffj = aeff infoj sumTdd = sum [ (res!!d!!k)* ( (aeff (info!!k) ) * ( biomass (info!!k)))/(biomass (info!!k)) | k <-[0..length wij-1]] --need to check correct sumTdi1 = sum [(res!!k!!j)/(biomass (info!!j))| k <-[0..length wij-1]] sumTdi2 =sum [ (res!!j!!k)* ((1-(aeff (info!!k)))) | k <-[0..length wij-1] ] --perhaps create a sum over k function? {-wrap "table" . concatMap (wrap "tr" . concatMap (wrap "td" . unshow . showFFloat (Just 3))) where wrap tag str = "<" ++ tag ++ ">" ++ str ++ ""-} unshow f = f ""