Safe Haskell | Safe-Infered |
---|
This module contains a data type to represent (plain) types, some basic functionality for types, and an instance for Show.
- class Substitution s where
- class Substitutable a where
- (|->) :: Substitution s => s -> a -> a
- ftv :: a -> [Int]
- nextFTV :: Substitutable a => a -> Int
- type MapSubstitution = Map Int Tp
- emptySubst :: MapSubstitution
- (@@) :: MapSubstitution -> MapSubstitution -> MapSubstitution
- (@@@) :: MapSubstitution -> MapSubstitution -> MapSubstitution
- singleSubstitution :: Int -> Tp -> MapSubstitution
- listToSubstitution :: [(Int, Tp)] -> MapSubstitution
- newtype FixpointSubstitution = FixpointSubstitution (Map Int Tp)
- emptyFPS :: FixpointSubstitution
- disjointFPS :: FixpointSubstitution -> FixpointSubstitution -> FixpointSubstitution
- wrapSubstitution :: Substitution substitution => substitution -> WrappedSubstitution
- data WrappedSubstitution = forall a . Substitution a => WrappedSubstitution a (Int -> a -> Tp, [Int] -> a -> a, [Int] -> a -> a, a -> [Int], a -> Tps)
- freezeFTV :: Substitutable a => a -> a
- allTypeVariables :: HasTypes a => a -> [Int]
- allTypeConstants :: HasTypes a => a -> [String]
Substitutions and substitutables
class Substitution s whereSource
class Substitutable a whereSource
Substitutable Tp | |
Substitutable Predicate | |
Substitutable a => Substitutable [a] | |
Substitutable a => Substitutable (Maybe a) | |
Substitutable qs => Substitutable (Sigma qs) | |
Substitutable (Operation m) | |
Substitutable (Constraint m) | |
Substitutable (EqualityConstraint info) | |
Substitutable (PolymorphismConstraint info) | |
Substitutable (PredicateMap info) | |
Substitutable (ExtraConstraint info) | |
(Substitutable a, Substitutable b) => Substitutable (Either a b) | |
(Substitutable a, Substitutable b) => Substitutable (a, b) | |
(Substitutable q, Substitutable a) => Substitutable (Qualification q a) | |
Substitutable a => Substitutable (Quantification q a) | |
(Substitutable (f info), Substitutable (g info)) => Substitutable (ConstraintSum f g info) |
nextFTV :: Substitutable a => a -> IntSource
The next type variable that is not free (default is zero)
Substitution instances
type MapSubstitution = Map Int TpSource
A substitution represented by a finite map.
(@@) :: MapSubstitution -> MapSubstitution -> MapSubstitutionSource
Compose two finite map substitutions: safe.
Note for union
: bindings in right argument shadow those in the left
(@@@) :: MapSubstitution -> MapSubstitution -> MapSubstitutionSource
Compose two finite map substitutions: quick and dirty!
singleSubstitution :: Int -> Tp -> MapSubstitutionSource
listToSubstitution :: [(Int, Tp)] -> MapSubstitutionSource
newtype FixpointSubstitution Source
A fixpoint is computed when looking up the target of a type variable in this substitution. Combining two substitutions is cheap, whereas a lookup is more expensive than the normal finite map substitution.
emptyFPS :: FixpointSubstitutionSource
The empty fixpoint substitution
disjointFPS :: FixpointSubstitution -> FixpointSubstitution -> FixpointSubstitutionSource
Combine two fixpoint substitutions that are disjoint
Wrapper for substitutions
wrapSubstitution :: Substitution substitution => substitution -> WrappedSubstitutionSource
data WrappedSubstitution Source
forall a . Substitution a => WrappedSubstitution a (Int -> a -> Tp, [Int] -> a -> a, [Int] -> a -> a, a -> [Int], a -> Tps) |
Substitutables instances
freezeFTV :: Substitutable a => a -> aSource
allTypeVariables :: HasTypes a => a -> [Int]Source
allTypeConstants :: HasTypes a => a -> [String]Source