Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- type CG = State CGInfo
- data CGInfo = CGInfo {
- fEnv :: !(SEnv Sort)
- hsCs :: ![SubC]
- hsWfs :: ![WfC]
- fixCs :: ![FixSubC]
- fixWfs :: ![FixWfC]
- freshIndex :: !Integer
- binds :: !BindEnv
- ebinds :: ![BindId]
- annotMap :: !(AnnInfo (Annot SpecType))
- holesMap :: !(HashMap Var (HoleInfo (CGInfo, CGEnv) SpecType))
- tyConInfo :: !TyConMap
- specDecr :: ![(Var, [Int])]
- newTyEnv :: !(HashMap TyCon SpecType)
- termExprs :: !(HashMap Var [Located Expr])
- specLVars :: !(HashSet Var)
- specLazy :: !(HashSet Var)
- specTmVars :: !(HashSet Var)
- autoSize :: !(HashSet TyCon)
- tyConEmbed :: !(TCEmb TyCon)
- kuts :: !Kuts
- kvPacks :: ![HashSet KVar]
- cgLits :: !(SEnv Sort)
- cgConsts :: !(SEnv Sort)
- cgADTs :: ![DataDecl]
- tcheck :: !Bool
- pruneRefs :: !Bool
- logErrors :: ![Error]
- kvProf :: !KVProf
- recCount :: !Int
- bindSpans :: HashMap BindId SrcSpan
- allowHO :: !Bool
- ghcI :: !TargetInfo
- dataConTys :: ![(Var, SpecType)]
- unsorted :: !Templates
- data CGEnv = CGE {
- cgLoc :: !SpanStack
- renv :: !REnv
- syenv :: !(SEnv Var)
- denv :: !RDEnv
- litEnv :: !(SEnv Sort)
- constEnv :: !(SEnv Sort)
- fenv :: !FEnv
- recs :: !(HashSet Var)
- invs :: !RTyConInv
- rinvs :: !RTyConInv
- ial :: !RTyConIAl
- grtys :: !REnv
- assms :: !REnv
- intys :: !REnv
- emb :: TCEmb TyCon
- tgEnv :: !TagEnv
- tgKey :: !(Maybe TagKey)
- trec :: !(Maybe (HashMap Symbol SpecType))
- lcb :: !(HashMap Symbol CoreExpr)
- forallcb :: !(HashMap Var Expr)
- holes :: !HEnv
- lcs :: !LConstraint
- cerr :: !(Maybe (TError SpecType))
- cgInfo :: !TargetInfo
- cgVar :: !(Maybe Var)
- data LConstraint = LC [[(Symbol, SpecType)]]
- data FEnv = FE {}
- initFEnv :: [(Symbol, Sort)] -> FEnv
- insertsFEnv :: FEnv -> [((Symbol, Sort), BindId)] -> FEnv
- data HEnv
- fromListHEnv :: [Symbol] -> HEnv
- elemHEnv :: Symbol -> HEnv -> Bool
- data SubC
- type FixSubC = SubC Cinfo
- subVar :: FixSubC -> Maybe Var
- data WfC = WfC !CGEnv !SpecType
- type FixWfC = WfC Cinfo
- type RTyConInv = HashMap RTyCon [RInv]
- mkRTyConInv :: [(Maybe Var, Located SpecType)] -> RTyConInv
- addRTyConInv :: RTyConInv -> SpecType -> SpecType
- addRInv :: RTyConInv -> (Var, SpecType) -> (Var, SpecType)
- type RTyConIAl = HashMap RTyCon [RInv]
- mkRTyConIAl :: [(a, Located SpecType)] -> RTyConInv
- removeInvariant :: CGEnv -> CoreBind -> (CGEnv, RTyConInv)
- restoreInvariant :: CGEnv -> RTyConInv -> CGEnv
- makeRecInvariants :: CGEnv -> [Var] -> CGEnv
- getTemplates :: CG Templates
Constraint Generation Monad
Constraint information
Generation: Types ---------------------------------------------------------
CGInfo | |
|
Constraint Generation Environment
CGE | |
|
Logical constraints (FIXME: related to bounds?)
data LConstraint Source #
Instances
Semigroup LConstraint Source # | |
Defined in Language.Haskell.Liquid.Constraint.Types (<>) :: LConstraint -> LConstraint -> LConstraint # sconcat :: NonEmpty LConstraint -> LConstraint # stimes :: Integral b => b -> LConstraint -> LConstraint # | |
Monoid LConstraint Source # | |
Defined in Language.Haskell.Liquid.Constraint.Types mempty :: LConstraint # mappend :: LConstraint -> LConstraint -> LConstraint # mconcat :: [LConstraint] -> LConstraint # |
Fixpoint environment
Fixpoint Environment ------------------------------------------------------
Hole Environment
fromListHEnv :: [Symbol] -> HEnv Source #