liquidhaskell-0.3.1.0: Liquid Types for Haskell

Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.Constraint.Types

Documentation

data CGEnv Source

Constructors

CGE 

Fields

loc :: !SrcSpan

Location in original source file

renv :: !REnv

SpecTypes for Bindings in scope

syenv :: !(SEnv Var)

Map from free Symbols (e.g. datacons) to Var , penv :: !(F.SEnv PrType) -- ^ PrTypes for top-level bindings (merge with renv)

denv :: !RDEnv

Dictionary Environment

fenv :: !FEnv

Fixpoint Environment

recs :: !(HashSet Var)

recursive defs being processed (for annotations)

invs :: !RTyConInv

Datatype invariants

ial :: !RTyConIAl

Datatype checkable invariants

grtys :: !REnv

Top-level variables with (assert)-guarantees to verify

assms :: !REnv

Top-level variables with assumed types

emb :: TCEmb TyCon

How to embed GHC Tycons into fixpoint sorts

tgEnv :: !TagEnv

Map from top-level binders to fixpoint tag

tgKey :: !(Maybe TagKey)

Current top-level binder

trec :: !(Maybe (HashMap Symbol SpecType))

Type of recursive function with decreasing constraints

lcb :: !(HashMap Symbol CoreExpr)

Let binding that have not been checked

holes :: !HEnv

Types with holes, will need refreshing

lcs :: !LConstraint

Logical Constraints

data LConstraint Source

Constructors

LC [SpecType] 

Instances

data SubC Source

Constructors

SubC 

Fields

senv :: !CGEnv
 
lhs :: !SpecType
 
rhs :: !SpecType
 
SubR 

Fields

senv :: !CGEnv
 
oblig :: !Oblig
 
ref :: !RReft
 

data WfC Source

Constructors

WfC !CGEnv !SpecType 

Instances

data CGInfo Source

Constructors

CGInfo 

Fields

hsCs :: ![SubC]

subtyping constraints over RType

hsWfs :: ![WfC]

wellformedness constraints over RType

sCs :: ![SubC]

additional stratum constrains for let bindings

fixCs :: ![FixSubC]

subtyping over Sort (post-splitting)

isBind :: ![Bool]

tracks constraints that come from let-bindings

fixWfs :: ![FixWfC]

wellformedness constraints over Sort (post-splitting)

freshIndex :: !Integer

counter for generating fresh KVars

binds :: !BindEnv

set of environment binders

annotMap :: !(AnnInfo (Annot SpecType))

source-position annotation map

tyConInfo :: !(HashMap TyCon RTyCon)

information about type-constructors

specDecr :: ![(Var, [Int])]

? FIX THIS

termExprs :: !(HashMap Var [Expr])

Terminating Metrics for Recursive functions

specLVars :: !(HashSet Var)

Set of variables to ignore for termination checking

specLazy :: !(HashSet Var)

? FIX THIS

tyConEmbed :: !(TCEmb TyCon)

primitive Sorts into which TyCons should be embedded

kuts :: !Kuts

Fixpoint Kut variables (denoting "back-edges"/recursive KVars)

lits :: ![(Symbol, Sort)]

? FIX THIS

tcheck :: !Bool

Check Termination (?)

scheck :: !Bool

Check Strata (?)

trustghc :: !Bool

Trust ghc auto generated bindings

pruneRefs :: !Bool

prune unsorted refinements

logErrors :: ![TError SpecType]

Errors during coontraint generation

kvProf :: !KVProf

Profiling distribution of KVars

recCount :: !Int

number of recursive functions seen (for benchmarks)

newtype HEnv Source

Constructors

HEnv (HashSet Symbol) 

data FEnv Source

Constructors

FE 

Fields

fe_binds :: !IBindEnv

Integer Keys for Fixpoint Environment

fe_env :: !(SEnv Sort)

Fixpoint Environment

Instances