> module Imports where > import Control.Applicative > import System.IO.Error > import System.FilePath > import Data.Foldable > import Data.Monoid > import HaLay > import Parsley > tryReadFile :: FilePath -> IO String > tryReadFile s = catch (readFile s) $ \ e -> > if isDoesNotExistError e then return "" else ioError e > pImport :: P Tok [String] > pImport = teq (KW "import") *> spc *> pSep (teq (Sym ".")) uid <* pRest > grokImports :: [Tok] -> [[FilePath]] > grokImports cs = foldMap pure $ parse pImport cs > getHers :: [String] -> IO [[Tok]] > getHers p = ready <$> tryReadFile (joinPath p <.> "hers") > storySoFar :: [[Tok]] -> IO [[Tok]] > storySoFar hs = foldMap getHers (hs >>= grokImports) > instance Monoid x => Monoid (IO x) where > mempty = pure mempty > mappend x y = mappend <$> x <*> y