{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE OverloadedStrings #-} module Descript.Sugar.Data.Source ( Query (..) , AModule (..) , BModule (..) , Program (..) , Source (..) , mkSource , sourceToProgram , sourceBModule , sourceImportCtx ) where import Descript.Sugar.Data.Reducer import qualified Descript.Sugar.Data.Value.Reg as Reg import Descript.Sugar.Data.Type import Descript.Sugar.Data.Import import Descript.Misc import Data.Monoid import Data.List import Prelude hiding (mod) -- | The "main" value in a program. A program is interpreted by reducing -- its query - this reduced is the output of a program. data Query an = Query { queryAnn :: an , queryVal :: Reg.Value an } deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) -- | Anonymous module - no scope. Defines how a program is interpreted. -- When a module imports another, the other's 'AModule' is appended. data AModule an = AModule { amoduleAnn :: an , recordCtx :: RecordCtx an , reduceCtx :: ReduceCtx an } deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) -- | A module with a scope and imports, which allows it to import other -- modules. data BModule an = BModule { bmoduleAnn :: an , importCtx :: ImportCtx an , amodule :: AModule an } deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) -- | Parsed from a source file and interpreted. To interpret, the query -- is reduced using the module. data Program an = Program { programAnn :: an , module' :: BModule an , query :: Query an } deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) -- | Every source file gets parsed into one of these. data Source an = SourceModule (BModule an) | SourceProgram (Program an) deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) instance (Monoid an) => Monoid (AModule an) where mempty = AModule { amoduleAnn = mempty , recordCtx = mempty , reduceCtx = mempty } x `mappend` y = AModule { amoduleAnn = amoduleAnn x <> amoduleAnn y , recordCtx = recordCtx x <> recordCtx y , reduceCtx = reduceCtx x <> reduceCtx y } instance Ann Source where getAnn (SourceModule mod) = getAnn mod getAnn (SourceProgram prog) = getAnn prog instance Ann Program where getAnn = programAnn instance Ann BModule where getAnn = bmoduleAnn instance Ann AModule where getAnn = amoduleAnn instance Ann Query where getAnn = queryAnn instance Printable Source where aprintRec sub (SourceModule mod) = sub mod aprintRec sub (SourceProgram prog) = sub prog instance Printable Program where aprintRec sub prog = pintercal "\n\n" $ filter (/= mempty) [ sub $ module' prog , sub $ query prog ] instance Printable BModule where aprintRec sub mod = pintercal "\n\n" $ filter (/= mempty) [ sub $ importCtx mod , sub $ amodule mod ] instance Printable AModule where aprintRec sub mod = pintercal "\n\n" $ filter (/= mempty) [ sub $ recordCtx mod , sub $ reduceCtx mod ] instance Printable Query where aprintRec sub (Query _ val) = sub val <> "?" instance (Show an) => Summary (Source an) where summaryRec = pprintSummaryRec instance (Show an) => Summary (Program an) where summaryRec = pprintSummaryRec instance (Show an) => Summary (BModule an) where summaryRec = pprintSummaryRec instance (Show an) => Summary (AModule an) where summaryRec = pprintSummaryRec instance (Show an) => Summary (Query an) where summaryRec = pprintSummaryRec -- | Creates a source program if the query exists, or a source module if it doesn't. mkSource :: an -> BModule an -> Maybe (Query an) -> Source an mkSource _ mod Nothing = SourceModule mod mkSource ann mod (Just qry) = SourceProgram $ Program ann mod qry -- | If the source is a program, returns it. -- If it's a module, returns 'Nothing'. sourceToProgram :: Source an -> Maybe (Program an) sourceToProgram (SourceModule _) = Nothing sourceToProgram (SourceProgram prog) = Just prog -- | The source's bound module. sourceBModule :: Source an -> BModule an sourceBModule (SourceModule mod) = mod sourceBModule (SourceProgram prog) = module' prog -- | Contains the source's module declaration and imports. sourceImportCtx :: Source an -> ImportCtx an sourceImportCtx = importCtx . sourceBModule