module EmpFile where import Statistics readPdf :: FilePath -> IO [Distribution] readPdf f = do cs <- lines `fmap` readFile f return (parsePdf ("file '"++f++"'") cs) parsePdf :: String -> [String] -> [Distribution] parsePdf f cs = let (_:fs:vss) = transpose (map words cs) in if (or $ zipWith (/=) [(0::Int)..] (map read fs)) then error ("Flow index from "++f++" isn't [0..]!") else map (fromPdf 0 0.01 . map (P . read)) vss transpose :: [[a]] -> [[a]] transpose xs = let r0 = map head xs rest = map tail xs in if any null rest then [r0] else r0 : transpose rest -- currently this only works for a single model combine_models :: [Int -> Distribution] -> [Distribution] -> [Int -> Distribution] combine_models [f] ds = [\i -> if i < length ds then ds!!i else f i] combine_models _ _ = error "Can't combine multiple models"