| Copyright | (c) 2013-2016 Galois Inc. |
|---|---|
| License | BSD3 |
| Maintainer | cryptol@galois.com |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Cryptol.TypeCheck.InferTypes
Description
This module contains types used during type inference.
Synopsis
- data SolverConfig = SolverConfig {}
- defaultSolverConfig :: [FilePath] -> SolverConfig
- data VarType
- data Goals = Goals {}
- type LitGoal = Goal
- litGoalToGoal :: (TVar, LitGoal) -> Goal
- goalToLitGoal :: Goal -> Maybe (TVar, LitGoal)
- litLessThanGoalToGoal :: (TVar, LitGoal) -> Goal
- goalToLitLessThanGoal :: Goal -> Maybe (TVar, LitGoal)
- emptyGoals :: Goals
- nullGoals :: Goals -> Bool
- fromGoals :: Goals -> [Goal]
- goalsFromList :: [Goal] -> Goals
- insertGoal :: Goal -> Goals -> Goals
- data Goal = Goal {
- goalSource :: ConstraintSource
- goalRange :: Range
- goal :: Prop
- data HasGoal = HasGoal {}
- data HasGoalSln = HasGoalSln {}
- data DelayedCt = DelayedCt {}
- data ConstraintSource
- selSrc :: Selector -> TypeSource
- cppKind :: Kind -> Doc
- addTVarsDescsAfter :: FVS t => NameMap -> t -> Doc -> Doc
- addTVarsDescsAfterFVS :: NameMap -> Set TVar -> Doc -> Doc
- addTVarsDescsBefore :: FVS t => NameMap -> t -> Doc -> Doc
- ppUse :: Expr -> Doc
- nameVariant :: Int -> String -> String
- computeModParamNames :: [TParam] -> NameMap -> NameMap
Documentation
data SolverConfig Source #
Constructors
| SolverConfig | |
Fields
| |
Instances
defaultSolverConfig :: [FilePath] -> SolverConfig Source #
A default configuration for using Z3, where the solver prelude is expected to be found in the given search path.
The types of variables in the environment.
Constructors
| Goals | |
Fields
| |
emptyGoals :: Goals Source #
goalsFromList :: [Goal] -> Goals Source #
Something that we need to find evidence for.
Constructors
| Goal | |
Fields
| |
Instances
| Generic Goal Source # | |
| Show Goal Source # | |
| TVars Goal Source # | |
| FVS Goal Source # | |
| NFData Goal Source # | |
Defined in Cryptol.TypeCheck.InferTypes | |
| Eq Goal Source # | |
| Ord Goal Source # | |
| PP (WithNames Goal) Source # | |
| type Rep Goal Source # | |
Defined in Cryptol.TypeCheck.InferTypes type Rep Goal = D1 ('MetaData "Goal" "Cryptol.TypeCheck.InferTypes" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "Goal" 'PrefixI 'True) (S1 ('MetaSel ('Just "goalSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstraintSource) :*: (S1 ('MetaSel ('Just "goalRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Just "goal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Prop)))) | |
Constructors
| HasGoal | |
Delayed implication constraints, arising from user-specified type sigs.
Constructors
| DelayedCt | |
Instances
| Generic DelayedCt Source # | |
| Show DelayedCt Source # | |
| TVars DelayedCt Source # | |
| FVS DelayedCt Source # | |
| NFData DelayedCt Source # | |
Defined in Cryptol.TypeCheck.InferTypes | |
| PP (WithNames DelayedCt) Source # | |
| type Rep DelayedCt Source # | |
Defined in Cryptol.TypeCheck.InferTypes type Rep DelayedCt = D1 ('MetaData "DelayedCt" "Cryptol.TypeCheck.InferTypes" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "DelayedCt" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dctSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)) :*: S1 ('MetaSel ('Just "dctForall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TParam])) :*: (S1 ('MetaSel ('Just "dctAsmps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Prop]) :*: S1 ('MetaSel ('Just "dctGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Goal])))) | |
data ConstraintSource Source #
Information about how a constraint came to be, used in error reporting.
Constructors
| CtComprehension | Computing shape of list comprehension |
| CtSplitPat | Use of a split pattern |
| CtTypeSig | A type signature in a pattern or expression |
| CtInst Expr | Instantiation of this expression |
| CtSelector | |
| CtExactType | |
| CtEnumeration | |
| CtDefaulting | Just defaulting on the command line |
| CtPartialTypeFun Name | Use of a partial type function. |
| CtImprovement | |
| CtPattern TypeSource | Constraints arising from type-checking patterns |
| CtModuleInstance Range | Instantiating a parametrized module |
| CtPropGuardsExhaustive Name | Checking that a use of prop guards is exhastive |
| CtFFI Name | Constraints on a foreign declaration required by the FFI (e.g. sequences must be finite) |
Instances
selSrc :: Selector -> TypeSource Source #