Copyright | (c) 2003 Wolfgang Lux 2016 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module implements substitutions on types.
Synopsis
- class ExpandAliasType a where
- expandAliasType :: [Type] -> a -> a
- class SubstType a where
- type TypeSubst = Subst Int Type
- bindVar :: Int -> Type -> TypeSubst -> TypeSubst
- substVar :: TypeSubst -> Int -> Type
- subst' :: TypeSubst -> Type -> [Type] -> Type
- expandAliasType' :: [Type] -> Type -> [Type] -> Type
- normalize :: Int -> PredType -> PredType
- instanceType :: ExpandAliasType a => Type -> a -> a
- idSubst :: Subst a b
- singleSubst :: Ord v => v -> e -> Subst v e
- bindSubst :: Ord v => v -> e -> Subst v e -> Subst v e
- compose :: Ord v => Subst v e -> Subst v e -> Subst v e
Documentation
class ExpandAliasType a where Source #
expandAliasType :: [Type] -> a -> a Source #
Instances
ExpandAliasType PredType Source # | |
Defined in Base.TypeSubst | |
ExpandAliasType Pred Source # | |
Defined in Base.TypeSubst | |
ExpandAliasType Type Source # | |
Defined in Base.TypeSubst | |
ExpandAliasType a => ExpandAliasType [a] Source # | |
Defined in Base.TypeSubst expandAliasType :: [Type] -> [a] -> [a] Source # | |
(Ord a, ExpandAliasType a) => ExpandAliasType (Set a) Source # | |
Defined in Base.TypeSubst |
class SubstType a where Source #
Instances
SubstType TypeScheme Source # | |
Defined in Base.TypeSubst subst :: TypeSubst -> TypeScheme -> TypeScheme Source # | |
SubstType PredType Source # | |
SubstType Pred Source # | |
SubstType Type Source # | |
SubstType ValueInfo Source # | |
SubstType a => SubstType [a] Source # | |
Defined in Base.TypeSubst | |
(Ord a, SubstType a) => SubstType (Set a) Source # | |
SubstType a => SubstType (TopEnv a) Source # | |
instanceType :: ExpandAliasType a => Type -> a -> a Source #
singleSubst :: Ord v => v -> e -> Subst v e Source #
Create a substitution for a single replacement