Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data QCInst = QCI {
- qci_ev :: CtEvidence
- qci_tvs :: [TcTyVar]
- qci_pred :: TcPredType
- qci_pend_sc :: Bool
- isPendingScInst :: QCInst -> Maybe QCInst
- type Xi = Type
- data Ct
- = CDictCan {
- cc_ev :: CtEvidence
- cc_class :: Class
- cc_tyargs :: [Xi]
- cc_pend_sc :: Bool
- | CIrredCan {
- cc_ev :: CtEvidence
- cc_insol :: Bool
- | CTyEqCan { }
- | CFunEqCan { }
- | CNonCanonical {
- cc_ev :: CtEvidence
- | CHoleCan {
- cc_ev :: CtEvidence
- cc_hole :: Hole
- | CQuantCan QCInst
- = CDictCan {
- type Cts = Bag Ct
- emptyCts :: Cts
- andCts :: Cts -> Cts -> Cts
- andManyCts :: [Cts] -> Cts
- pprCts :: Cts -> SDoc
- singleCt :: Ct -> Cts
- listToCts :: [Ct] -> Cts
- ctsElts :: Cts -> [Ct]
- consCts :: Ct -> Cts -> Cts
- snocCts :: Cts -> Ct -> Cts
- extendCtsList :: Cts -> [Ct] -> Cts
- isEmptyCts :: Cts -> Bool
- isCTyEqCan :: Ct -> Bool
- isCFunEqCan :: Ct -> Bool
- isPendingScDict :: Ct -> Maybe Ct
- superClassesMightHelp :: WantedConstraints -> Bool
- getPendingWantedScs :: Cts -> ([Ct], Cts)
- isCDictCan_Maybe :: Ct -> Maybe Class
- isCFunEqCan_maybe :: Ct -> Maybe (TyCon, [Type])
- isCNonCanonical :: Ct -> Bool
- isWantedCt :: Ct -> Bool
- isDerivedCt :: Ct -> Bool
- isGivenCt :: Ct -> Bool
- isHoleCt :: Ct -> Bool
- isOutOfScopeCt :: Ct -> Bool
- isExprHoleCt :: Ct -> Bool
- isTypeHoleCt :: Ct -> Bool
- isUserTypeErrorCt :: Ct -> Bool
- getUserTypeErrorMsg :: Ct -> Maybe Type
- ctEvidence :: Ct -> CtEvidence
- ctLoc :: Ct -> CtLoc
- setCtLoc :: Ct -> CtLoc -> Ct
- ctPred :: Ct -> PredType
- ctFlavour :: Ct -> CtFlavour
- ctEqRel :: Ct -> EqRel
- ctOrigin :: Ct -> CtOrigin
- ctEvId :: Ct -> EvVar
- mkTcEqPredLikeEv :: CtEvidence -> TcType -> TcType -> TcType
- mkNonCanonical :: CtEvidence -> Ct
- mkNonCanonicalCt :: Ct -> Ct
- mkGivens :: CtLoc -> [EvId] -> [Ct]
- mkIrredCt :: CtEvidence -> Ct
- mkInsolubleCt :: CtEvidence -> Ct
- ctEvPred :: CtEvidence -> TcPredType
- ctEvLoc :: CtEvidence -> CtLoc
- ctEvOrigin :: CtEvidence -> CtOrigin
- ctEvEqRel :: CtEvidence -> EqRel
- ctEvExpr :: CtEvidence -> EvExpr
- ctEvTerm :: CtEvidence -> EvTerm
- ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion
- ctEvEvId :: CtEvidence -> EvVar
- tyCoVarsOfCt :: Ct -> TcTyCoVarSet
- tyCoVarsOfCts :: Cts -> TcTyCoVarSet
- tyCoVarsOfCtList :: Ct -> [TcTyCoVar]
- tyCoVarsOfCtsList :: Cts -> [TcTyCoVar]
- data WantedConstraints = WC {
- wc_simple :: Cts
- wc_impl :: Bag Implication
- insolubleWC :: WantedConstraints -> Bool
- emptyWC :: WantedConstraints
- isEmptyWC :: WantedConstraints -> Bool
- isSolvedWC :: WantedConstraints -> Bool
- andWC :: WantedConstraints -> WantedConstraints -> WantedConstraints
- unionsWC :: [WantedConstraints] -> WantedConstraints
- mkSimpleWC :: [CtEvidence] -> WantedConstraints
- mkImplicWC :: Bag Implication -> WantedConstraints
- addInsols :: WantedConstraints -> Bag Ct -> WantedConstraints
- insolublesOnly :: WantedConstraints -> WantedConstraints
- addSimples :: WantedConstraints -> Bag Ct -> WantedConstraints
- addImplics :: WantedConstraints -> Bag Implication -> WantedConstraints
- tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet
- dropDerivedWC :: WantedConstraints -> WantedConstraints
- dropDerivedSimples :: Cts -> Cts
- tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar]
- insolubleCt :: Ct -> Bool
- insolubleEqCt :: Ct -> Bool
- isDroppableCt :: Ct -> Bool
- insolubleImplic :: Implication -> Bool
- arisesFromGivens :: Ct -> Bool
- data Implication = Implic {}
- implicationPrototype :: Implication
- data ImplicStatus
- = IC_Solved { }
- | IC_Insoluble
- | IC_BadTelescope
- | IC_Unsolved
- isInsolubleStatus :: ImplicStatus -> Bool
- isSolvedStatus :: ImplicStatus -> Bool
- data SubGoalDepth
- initialSubGoalDepth :: SubGoalDepth
- maxSubGoalDepth :: SubGoalDepth -> SubGoalDepth -> SubGoalDepth
- bumpSubGoalDepth :: SubGoalDepth -> SubGoalDepth
- subGoalDepthExceeded :: DynFlags -> SubGoalDepth -> Bool
- data CtLoc = CtLoc {}
- ctLocSpan :: CtLoc -> RealSrcSpan
- ctLocEnv :: CtLoc -> TcLclEnv
- ctLocLevel :: CtLoc -> TcLevel
- ctLocOrigin :: CtLoc -> CtOrigin
- ctLocTypeOrKind_maybe :: CtLoc -> Maybe TypeOrKind
- ctLocDepth :: CtLoc -> SubGoalDepth
- bumpCtLocDepth :: CtLoc -> CtLoc
- isGivenLoc :: CtLoc -> Bool
- setCtLocOrigin :: CtLoc -> CtOrigin -> CtLoc
- updateCtLocOrigin :: CtLoc -> (CtOrigin -> CtOrigin) -> CtLoc
- setCtLocEnv :: CtLoc -> TcLclEnv -> CtLoc
- setCtLocSpan :: CtLoc -> RealSrcSpan -> CtLoc
- pprCtLoc :: CtLoc -> SDoc
- data CtEvidence
- data TcEvDest
- mkKindLoc :: TcType -> TcType -> CtLoc -> CtLoc
- toKindLoc :: CtLoc -> CtLoc
- mkGivenLoc :: TcLevel -> SkolemInfo -> TcLclEnv -> CtLoc
- isWanted :: CtEvidence -> Bool
- isGiven :: CtEvidence -> Bool
- isDerived :: CtEvidence -> Bool
- isGivenOrWDeriv :: CtFlavour -> Bool
- ctEvRole :: CtEvidence -> Role
- wrapType :: Type -> [TyVar] -> [PredType] -> Type
- wrapTypeWithImplication :: Type -> Implication -> Type
- data CtFlavour
- = Given
- | Wanted ShadowInfo
- | Derived
- data ShadowInfo
- ctEvFlavour :: CtEvidence -> CtFlavour
- type CtFlavourRole = (CtFlavour, EqRel)
- ctEvFlavourRole :: CtEvidence -> CtFlavourRole
- ctFlavourRole :: Ct -> CtFlavourRole
- eqCanRewrite :: EqRel -> EqRel -> Bool
- eqCanRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool
- eqMayRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool
- eqCanDischargeFR :: CtFlavourRole -> CtFlavourRole -> Bool
- funEqCanDischarge :: CtEvidence -> CtEvidence -> (SwapFlag, Bool)
- funEqCanDischargeF :: CtFlavour -> CtFlavour -> (SwapFlag, Bool)
- pprEvVarTheta :: [EvVar] -> SDoc
- pprEvVars :: [EvVar] -> SDoc
- pprEvVarWithType :: EvVar -> SDoc
- data Hole
- holeOcc :: Hole -> OccName
Documentation
QCI | |
|
CDictCan | |
| |
CIrredCan | |
| |
CTyEqCan | |
CFunEqCan | |
CNonCanonical | |
| |
CHoleCan | |
| |
CQuantCan QCInst |
andManyCts :: [Cts] -> Cts Source #
isEmptyCts :: Cts -> Bool Source #
isCTyEqCan :: Ct -> Bool Source #
isCFunEqCan :: Ct -> Bool Source #
superClassesMightHelp :: WantedConstraints -> Bool Source #
True if taking superclasses of givens, or of wanteds (to perhaps expose more equalities or functional dependencies) might help to solve this constraint. See Note [When superclasses help]
isCNonCanonical :: Ct -> Bool Source #
isWantedCt :: Ct -> Bool Source #
isDerivedCt :: Ct -> Bool Source #
isOutOfScopeCt :: Ct -> Bool Source #
isExprHoleCt :: Ct -> Bool Source #
isTypeHoleCt :: Ct -> Bool Source #
isUserTypeErrorCt :: Ct -> Bool Source #
getUserTypeErrorMsg :: Ct -> Maybe Type Source #
A constraint is considered to be a custom type error, if it contains custom type errors anywhere in it. See Note [Custom type errors in constraints]
ctEvidence :: Ct -> CtEvidence Source #
mkTcEqPredLikeEv :: CtEvidence -> TcType -> TcType -> TcType Source #
Makes a new equality predicate with the same role as the given evidence.
mkNonCanonical :: CtEvidence -> Ct Source #
mkNonCanonicalCt :: Ct -> Ct Source #
mkIrredCt :: CtEvidence -> Ct Source #
mkInsolubleCt :: CtEvidence -> Ct Source #
ctEvPred :: CtEvidence -> TcPredType Source #
ctEvLoc :: CtEvidence -> CtLoc Source #
ctEvOrigin :: CtEvidence -> CtOrigin Source #
ctEvEqRel :: CtEvidence -> EqRel Source #
Get the equality relation relevant for a CtEvidence
ctEvExpr :: CtEvidence -> EvExpr Source #
ctEvTerm :: CtEvidence -> EvTerm Source #
ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion Source #
ctEvEvId :: CtEvidence -> EvVar Source #
tyCoVarsOfCt :: Ct -> TcTyCoVarSet Source #
Returns free variables of constraints as a non-deterministic set
tyCoVarsOfCts :: Cts -> TcTyCoVarSet Source #
Returns free variables of a bag of constraints as a non-deterministic set. See Note [Deterministic FV] in FV.
tyCoVarsOfCtList :: Ct -> [TcTyCoVar] Source #
Returns free variables of constraints as a deterministically ordered. list. See Note [Deterministic FV] in FV.
tyCoVarsOfCtsList :: Cts -> [TcTyCoVar] Source #
Returns free variables of a bag of constraints as a deterministically odered list. See Note [Deterministic FV] in FV.
data WantedConstraints Source #
Instances
Outputable WantedConstraints # | |
Defined in Constraint |
insolubleWC :: WantedConstraints -> Bool Source #
isEmptyWC :: WantedConstraints -> Bool Source #
isSolvedWC :: WantedConstraints -> Bool Source #
Checks whether a the given wanted constraints are solved, i.e. that there are no simple constraints left and all the implications are solved.
mkSimpleWC :: [CtEvidence] -> WantedConstraints Source #
addInsols :: WantedConstraints -> Bag Ct -> WantedConstraints Source #
addSimples :: WantedConstraints -> Bag Ct -> WantedConstraints Source #
tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet Source #
Returns free variables of WantedConstraints as a non-deterministic set. See Note [Deterministic FV] in FV.
dropDerivedSimples :: Cts -> Cts Source #
tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] Source #
Returns free variables of WantedConstraints as a deterministically ordered list. See Note [Deterministic FV] in FV.
insolubleCt :: Ct -> Bool Source #
insolubleEqCt :: Ct -> Bool Source #
isDroppableCt :: Ct -> Bool Source #
insolubleImplic :: Implication -> Bool Source #
arisesFromGivens :: Ct -> Bool Source #
data Implication Source #
Implic | |
|
Instances
Outputable Implication # | |
Defined in Constraint |
data ImplicStatus Source #
Instances
Outputable ImplicStatus # | |
Defined in Constraint |
isInsolubleStatus :: ImplicStatus -> Bool Source #
isSolvedStatus :: ImplicStatus -> Bool Source #
data SubGoalDepth Source #
See Note [SubGoalDepth]
Instances
Eq SubGoalDepth # | |
Defined in Constraint (==) :: SubGoalDepth -> SubGoalDepth -> Bool # (/=) :: SubGoalDepth -> SubGoalDepth -> Bool # | |
Ord SubGoalDepth # | |
Defined in Constraint compare :: SubGoalDepth -> SubGoalDepth -> Ordering # (<) :: SubGoalDepth -> SubGoalDepth -> Bool # (<=) :: SubGoalDepth -> SubGoalDepth -> Bool # (>) :: SubGoalDepth -> SubGoalDepth -> Bool # (>=) :: SubGoalDepth -> SubGoalDepth -> Bool # max :: SubGoalDepth -> SubGoalDepth -> SubGoalDepth # min :: SubGoalDepth -> SubGoalDepth -> SubGoalDepth # | |
Outputable SubGoalDepth # | |
Defined in Constraint |
subGoalDepthExceeded :: DynFlags -> SubGoalDepth -> Bool Source #
CtLoc | |
|
ctLocSpan :: CtLoc -> RealSrcSpan Source #
ctLocLevel :: CtLoc -> TcLevel Source #
ctLocOrigin :: CtLoc -> CtOrigin Source #
ctLocDepth :: CtLoc -> SubGoalDepth Source #
bumpCtLocDepth :: CtLoc -> CtLoc Source #
isGivenLoc :: CtLoc -> Bool Source #
setCtLocSpan :: CtLoc -> RealSrcSpan -> CtLoc Source #
data CtEvidence Source #
CtGiven | |
CtWanted | |
| |
CtDerived | |
|
Instances
Outputable CtEvidence # | |
Defined in Constraint |
A place for type-checking evidence to go after it is generated. Wanted equalities are always HoleDest; other wanteds are always EvVarDest.
EvVarDest EvVar | bind this var to the evidence EvVarDest is always used for non-type-equalities e.g. class constraints |
HoleDest CoercionHole | fill in this hole with the evidence HoleDest is always used for type-equalities See Note [Coercion holes] in TyCoRep |
mkGivenLoc :: TcLevel -> SkolemInfo -> TcLclEnv -> CtLoc Source #
isWanted :: CtEvidence -> Bool Source #
isGiven :: CtEvidence -> Bool Source #
isDerived :: CtEvidence -> Bool Source #
isGivenOrWDeriv :: CtFlavour -> Bool Source #
ctEvRole :: CtEvidence -> Role Source #
Get the role relevant for a CtEvidence
wrapTypeWithImplication :: Type -> Implication -> Type Source #
Wraps the given type with the constraints (via ic_given) in the given implication, according to the variables mentioned (via ic_skols) in the implication, but taking care to only wrap those variables that are mentioned in the type or the implication.
data ShadowInfo Source #
Instances
Eq ShadowInfo # | |
Defined in Constraint (==) :: ShadowInfo -> ShadowInfo -> Bool # (/=) :: ShadowInfo -> ShadowInfo -> Bool # |
ctEvFlavour :: CtEvidence -> CtFlavour Source #
type CtFlavourRole = (CtFlavour, EqRel) Source #
Whether or not one Ct
can rewrite another is determined by its
flavour and its equality relation. See also
Note [Flavours with roles] in TcSMonad
ctEvFlavourRole :: CtEvidence -> CtFlavourRole Source #
Extract the flavour, role, and boxity from a CtEvidence
ctFlavourRole :: Ct -> CtFlavourRole Source #
Extract the flavour and role from a Ct
eqCanRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool Source #
eqMayRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool Source #
eqCanDischargeFR :: CtFlavourRole -> CtFlavourRole -> Bool Source #
funEqCanDischarge :: CtEvidence -> CtEvidence -> (SwapFlag, Bool) Source #
pprEvVarTheta :: [EvVar] -> SDoc Source #
pprEvVarWithType :: EvVar -> SDoc Source #
An expression or type hole
ExprHole UnboundVar | Either an out-of-scope variable or a "true" hole in an expression (TypedHoles) |
TypeHole OccName | A hole in a type (PartialTypeSignatures) |