{-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE Rank2Types #-} -- | Unifies traversing all of the AST nodes. -- -- > import qualified ...Term as T module Descript.BasicInj.Traverse.Term ( TTerm (..) ) where import qualified Descript.BasicInj.Data.Value.Reg as Reg import qualified Descript.BasicInj.Data.Value.In as In import qualified Descript.BasicInj.Data.Value.Out as Out import Descript.BasicInj.Data import Descript.Misc -- | A type of AST node. Usually corresponds to a Haskell type but not -- necessarily. data TTerm (a :: * -> *) where Source :: TTerm Source Program :: TTerm Program BModule :: TTerm BModule AModule :: TTerm AModule ModuleDecl :: TTerm ModuleDecl ImportCtx :: TTerm ImportCtx RecordCtx :: TTerm RecordCtx ReduceCtx :: TTerm ReduceCtx PhaseCtx :: TTerm PhaseCtx Query :: TTerm Query ImportDecl :: TTerm ImportDecl RecordDecl :: TTerm RecordDecl Reducer :: TTerm Reducer ModulePath :: TTerm ModulePath ImportRecord :: TTerm ImportRecord RecordType :: TTerm RecordType RegValue :: TTerm (GenValue Reg.Part) Input :: TTerm (GenValue In.Part) Output :: TTerm (GenValue Out.Part) GenValue :: forall p. (GenPart p) => TTerm (GenValue p) RegPart :: TTerm Reg.Part InPart :: TTerm In.Part OutPart :: TTerm Out.Part Prim :: TTerm Prim PrimType :: TTerm PrimType RegRecord :: TTerm (GenRecord (GenValue Reg.Part)) InRecord :: TTerm (GenRecord In.OptValue) OutRecord :: TTerm (GenRecord (GenValue Out.Part)) GenRecord :: forall v. (FwdPrintable v, GenPropVal v) => TTerm (GenRecord v) RegProperty :: TTerm (GenProperty (GenValue Reg.Part)) InProperty :: TTerm (GenProperty In.OptValue) OutProperty :: TTerm (GenProperty (GenValue Out.Part)) GenProperty :: forall v. (FwdPrintable v, GenPropVal v) => TTerm (GenProperty v) PropPath :: TTerm PropPath PathElem :: TTerm PathElem InjApp :: TTerm Out.InjApp ModulePathElem :: TTerm Symbol RecordHead :: TTerm FSymbol PropertyKey :: TTerm Symbol