Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Subst
- emptySubst :: Subst
- singleSubst :: TVar -> Type -> Subst
- (@@) :: Subst -> Subst -> Subst
- defaultingSubst :: Subst -> Subst
- listSubst :: [(TVar, Type)] -> Subst
- listParamSubst :: [(TParam, Type)] -> Subst
- isEmptySubst :: Subst -> Bool
- class FVS t where
- apSubstMaybe :: Subst -> Type -> Maybe Type
- class TVars t where
- apSubstTypeMapKeys :: Subst -> TypeMap a -> TypeMap a
- substBinds :: Subst -> Set TVar
- applySubstToVar :: Subst -> TVar -> Maybe Type
- substToList :: Subst -> [(TVar, Type)]
Documentation
A Subst
value represents a substitution that maps each Type
to a Type
.
Invariant: If there is a mapping from TVFree _ _ tps _
to a type
t
, then t
must not mention (directly or indirectly) any type
parameter that is not in tps
. In particular, if t
contains a
variable TVFree _ _ tps2 _
, then tps2
must be a subset of
tps
. This ensures that applying the substitution will not permit
any type parameter to escape from its scope.
emptySubst :: Subst Source #
defaultingSubst :: Subst -> Subst Source #
A defaulting substitution maps all otherwise-unmapped free
variables to a kind-appropriate default type (Bit
for value types
and 0
for numeric types).
listSubst :: [(TVar, Type)] -> Subst Source #
Makes a substitution out of a list. WARNING: We do not validate the list in any way, so the caller should ensure that we end up with a valid (e.g., idempotent) substitution.
listParamSubst :: [(TParam, Type)] -> Subst Source #
Makes a substitution out of a list. WARNING: We do not validate the list in any way, so the caller should ensure that we end up with a valid (e.g., idempotent) substitution.
isEmptySubst :: Subst -> Bool Source #
apSubstMaybe :: Subst -> Type -> Maybe Type Source #
Apply a substitution. Returns Nothing
if nothing changed.
Instances
TVars Type Source # | |
TVars Schema Source # | This instance does not need to worry about bound variable
capture, because we rely on the |
TVars DeclDef Source # | |
TVars Decl Source # | |
TVars DeclGroup Source # | |
TVars Match Source # | |
TVars Expr Source # | |
TVars Module Source # | |
TVars ConstraintSource Source # | |
Defined in Cryptol.TypeCheck.InferTypes apSubst :: Subst -> ConstraintSource -> ConstraintSource Source # | |
TVars DelayedCt Source # | |
TVars HasGoal Source # | |
TVars Goal Source # | |
TVars Goals Source # | |
TVars Error Source # | |
TVars Warning Source # | |
TVars t => TVars [t] Source # | |
Defined in Cryptol.TypeCheck.Subst | |
TVars t => TVars (Maybe t) Source # | |
TVars a => TVars (TypeMap a) Source # | |
(TVars s, TVars t) => TVars (s, t) Source # | |
Defined in Cryptol.TypeCheck.Subst | |
(Functor m, TVars a) => TVars (List m a) Source # | |