{-#LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} module Text.HPaco.Readers.Paco.ParserInternals ( PacoState (..) , defaultPacoState , Text.Parsec.Error.ParseError , Parser , addDef, resolveDef , fillExtension ) where import Control.Exception (Exception) import Control.Monad import Control.Monad.IO.Class import Data.Typeable import Text.HPaco.Reader import Text.HPaco.AST.AST import Text.HPaco.AST.Expression import Text.HPaco.AST.Statement import Text.Parsec.Error (ParseError) import Text.Parsec.Prim import Text.Parsec.Char import Text.Parsec.String hiding (Parser) import System.FilePath instance Exception ParseError deriving instance Typeable ParseError data PacoState = PacoState { psBasePath :: FilePath , psDefs :: [(String, Statement)] , psDeps :: [String] , psIncludeExtension :: Maybe String , psHandleInclude :: Reader } type Parser a = ParsecT String PacoState IO a defaultPacoState :: PacoState defaultPacoState = PacoState { psBasePath = "" , psDefs = [] , psDeps = [] , psIncludeExtension = Nothing , psHandleInclude = (\s t -> return defAST) } addDef :: String -> Statement -> Parser () addDef name value = modifyState (\s -> s { psDefs = ((name, value):psDefs s) }) resolveDef :: String -> Parser Statement resolveDef name = do defs <- psDefs `liftM` getState let val = lookup name defs maybe (unexpected $ name ++ " is not defined.") return val fillExtension :: FilePath -> String -> FilePath fillExtension fp ext = let ext0 = takeExtension fp in if null ext0 then replaceExtension fp ext else fp