| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Ide.Plugin.Tactic.Judgements
Synopsis
- blacklistingDestruct :: Judgement -> Judgement
- unwhitelistingSplit :: Judgement -> Judgement
- introducingLambda :: Maybe OccName -> [(OccName, a)] -> Judgement' a -> Judgement' a
- introducingRecursively :: [(OccName, a)] -> Judgement' a -> Judgement' a
- introducingPat :: Maybe OccName -> DataCon -> [(OccName, a)] -> Judgement' a -> Judgement' a
- jGoal :: Judgement' a -> a
- jHypothesis :: Judgement' a -> Hypothesis a
- jEntireHypothesis :: Judgement' a -> Hypothesis a
- jPatHypothesis :: Judgement' a -> Map OccName PatVal
- substJdg :: TCvSubst -> Judgement -> Judgement
- unsetIsTopHole :: Judgement' a -> Judgement' a
- filterSameTypeFromOtherPositions :: DataCon -> Int -> Judgement -> Judgement
- isDestructBlacklisted :: Judgement -> Bool
- withNewGoal :: a -> Judgement' a -> Judgement' a
- jLocalHypothesis :: Judgement' a -> Hypothesis a
- isSplitWhitelisted :: Judgement -> Bool
- isPatternMatch :: Provenance -> Bool
- filterPosition :: OccName -> Int -> Judgement -> Judgement
- isTopHole :: Context -> Judgement' a -> Maybe OccName
- disallowing :: DisallowReason -> [OccName] -> Judgement' a -> Judgement' a
- mkFirstJudgement :: Hypothesis CType -> Bool -> Type -> Judgement' CType
- hypothesisFromBindings :: RealSrcSpan -> Bindings -> Hypothesis CType
- isTopLevel :: Provenance -> Bool
- hyNamesInScope :: Hypothesis a -> Set OccName
- hyByName :: Hypothesis a -> Map OccName (HyInfo a)
Documentation
Arguments
| :: Maybe OccName | The name of the top level function. For any other
 function, this should be  | 
| -> [(OccName, a)] | |
| -> Judgement' a | |
| -> Judgement' a | 
Introduce bindings in the context of a lamba.
introducingRecursively :: [(OccName, a)] -> Judgement' a -> Judgement' a Source #
Introduce a binding in a recursive context.
introducingPat :: Maybe OccName -> DataCon -> [(OccName, a)] -> Judgement' a -> Judgement' a Source #
Pattern vals are currently tracked in jHypothesis, with an extra piece of data sitting around in jPatternVals.
jGoal :: Judgement' a -> a Source #
jHypothesis :: Judgement' a -> Hypothesis a Source #
The hypothesis, consisting of local terms and the ambient environment (impors and class methods.) Hides disallowed values.
jEntireHypothesis :: Judgement' a -> Hypothesis a Source #
The whole hypothesis, including things disallowed.
jPatHypothesis :: Judgement' a -> Map OccName PatVal Source #
Only the hypothesis members which are pattern vals
unsetIsTopHole :: Judgement' a -> Judgement' a Source #
filterSameTypeFromOtherPositions :: DataCon -> Int -> Judgement -> Judgement Source #
Disallow any hypotheses who have the same type as anything bound by the
 given position for the datacon. Used to ensure recursive functions like
 fmap preserve the relative ordering of their arguments by eliminating any
 other term which might match.
withNewGoal :: a -> Judgement' a -> Judgement' a Source #
jLocalHypothesis :: Judgement' a -> Hypothesis a Source #
Just the local hypothesis.
isSplitWhitelisted :: Judgement -> Bool Source #
isPatternMatch :: Provenance -> Bool Source #
Is this a pattern match?
filterPosition :: OccName -> Int -> Judgement -> Judgement Source #
filter defn pos removes any hypotheses which are bound in defn to
 a position other than pos. Any terms whose ancestry doesn't include defn
 remain.
isTopHole :: Context -> Judgement' a -> Maybe OccName Source #
If we're in a top hole, the name of the defining function.
disallowing :: DisallowReason -> [OccName] -> Judgement' a -> Judgement' a Source #
Prevent some occnames from being used in the hypothesis. This will hide
 them from jHypothesis, but not from jEntireHypothesis.
Arguments
| :: Hypothesis CType | |
| -> Bool | are we in the top level rhs hole? | 
| -> Type | |
| -> Judgement' CType | 
isTopLevel :: Provenance -> Bool Source #
Is this a top level function binding?
hyNamesInScope :: Hypothesis a -> Set OccName Source #
What names are currently in scope in the hypothesis?