| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Inference.AltInference
Synopsis
- showType :: Type -> String
- showTypeScheme :: TypeScheme -> String
- showConstraint :: TypeConstraint -> String
- type UnificationContext = Maybe String
- data SUnificationError
- sOccursIn :: Name -> Type -> Bool
- uUnify :: [TypeConstraint] -> Either SUnificationError SSubst
- uSubst :: Name -> Type -> Type -> Type
- uSubstInConstraint :: Name -> Type -> TypeConstraint -> TypeConstraint
- data SSubst = SSubst {}
- sEmptySubst :: SSubst
- sSubstituteTypeVariables :: SSubst -> Type -> Type
- sSubstituteTypeVariablesInScheme :: SSubst -> TypeScheme -> TypeScheme
- data SInferenceContext = SInferenceContext {}
- data SInferenceResult = SInferenceResult {}
- sInferType :: Term -> Flow SInferenceContext TypeScheme
- sInferTypeInternal :: Term -> Flow SInferenceContext SInferenceResult
- sInstantiate :: TypeScheme -> Flow SInferenceContext TypeScheme
- sInstantiateAndNormalize :: TypeScheme -> Flow SInferenceContext TypeScheme
- sFreeTypeVariables :: Type -> [Name]
- sNormalizeTypeVariables :: TypeScheme -> TypeScheme
- sNewVar :: Flow SInferenceContext Name
- sNewVars :: Int -> Flow SInferenceContext [Name]
- sVarScheme :: Name -> TypeScheme
- sWithTypeBinding :: Name -> TypeScheme -> Flow SInferenceContext a -> Flow SInferenceContext a
- _app :: Term -> Term -> Term
- _int :: Int -> Term
- _lambda :: String -> Term -> Term
- _list :: [Term] -> Term
- _map :: Map Term Term -> Term
- _pair :: Term -> Term -> Term
- _str :: String -> Term
- _var :: String -> Term
- (@@) :: Term -> Term -> Term
- (>:) :: String -> Term -> (Name, Term)
- int32 :: Int -> Term
- lambda :: String -> Term -> Term
- list :: [Term] -> Term
- map :: Map Term Term -> Term
- pair :: Term -> Term -> Term
- string :: String -> Term
- var :: String -> Term
- with :: Foldable t => Term -> t (Name, Term) -> Term
- (===) :: Type -> Type -> TypeConstraint
- _add :: Term
- primPred :: Term
- primSucc :: Term
- _unify :: Type -> Type -> Either SUnificationError SSubst
- sTestLexicon :: Map Name TypeScheme
- sInitialContext :: SInferenceContext
- _infer :: Term -> Maybe TypeScheme
- _inferRaw :: Term -> Maybe SInferenceResult
- _instantiate :: TypeScheme -> Maybe TypeScheme
- _con :: Type -> Type -> TypeConstraint
Documentation
showTypeScheme :: TypeScheme -> String Source #
type UnificationContext = Maybe String Source #
data SUnificationError Source #
Constructors
| SUnificationErrorCannotUnify Type Type UnificationContext | |
| SUnificationErrorOccursCheckFailed Name Type UnificationContext |
Instances
| Show SUnificationError Source # | |
Defined in Hydra.Inference.AltInference Methods showsPrec :: Int -> SUnificationError -> ShowS # show :: SUnificationError -> String # showList :: [SUnificationError] -> ShowS # | |
| Eq SUnificationError Source # | |
Defined in Hydra.Inference.AltInference Methods (==) :: SUnificationError -> SUnificationError -> Bool # (/=) :: SUnificationError -> SUnificationError -> Bool # | |
| Ord SUnificationError Source # | |
Defined in Hydra.Inference.AltInference Methods compare :: SUnificationError -> SUnificationError -> Ordering # (<) :: SUnificationError -> SUnificationError -> Bool # (<=) :: SUnificationError -> SUnificationError -> Bool # (>) :: SUnificationError -> SUnificationError -> Bool # (>=) :: SUnificationError -> SUnificationError -> Bool # max :: SUnificationError -> SUnificationError -> SUnificationError # min :: SUnificationError -> SUnificationError -> SUnificationError # | |
uUnify :: [TypeConstraint] -> Either SUnificationError SSubst Source #
uSubstInConstraint :: Name -> Type -> TypeConstraint -> TypeConstraint Source #
sEmptySubst :: SSubst Source #
data SInferenceContext Source #
Constructors
| SInferenceContext | |
Instances
| Show SInferenceContext Source # | |
Defined in Hydra.Inference.AltInference Methods showsPrec :: Int -> SInferenceContext -> ShowS # show :: SInferenceContext -> String # showList :: [SInferenceContext] -> ShowS # | |
| Eq SInferenceContext Source # | |
Defined in Hydra.Inference.AltInference Methods (==) :: SInferenceContext -> SInferenceContext -> Bool # (/=) :: SInferenceContext -> SInferenceContext -> Bool # | |
| Ord SInferenceContext Source # | |
Defined in Hydra.Inference.AltInference Methods compare :: SInferenceContext -> SInferenceContext -> Ordering # (<) :: SInferenceContext -> SInferenceContext -> Bool # (<=) :: SInferenceContext -> SInferenceContext -> Bool # (>) :: SInferenceContext -> SInferenceContext -> Bool # (>=) :: SInferenceContext -> SInferenceContext -> Bool # max :: SInferenceContext -> SInferenceContext -> SInferenceContext # min :: SInferenceContext -> SInferenceContext -> SInferenceContext # | |
data SInferenceResult Source #
Constructors
| SInferenceResult | |
Instances
| Show SInferenceResult Source # | |
Defined in Hydra.Inference.AltInference Methods showsPrec :: Int -> SInferenceResult -> ShowS # show :: SInferenceResult -> String # showList :: [SInferenceResult] -> ShowS # | |
| Eq SInferenceResult Source # | |
Defined in Hydra.Inference.AltInference Methods (==) :: SInferenceResult -> SInferenceResult -> Bool # (/=) :: SInferenceResult -> SInferenceResult -> Bool # | |
| Ord SInferenceResult Source # | |
Defined in Hydra.Inference.AltInference Methods compare :: SInferenceResult -> SInferenceResult -> Ordering # (<) :: SInferenceResult -> SInferenceResult -> Bool # (<=) :: SInferenceResult -> SInferenceResult -> Bool # (>) :: SInferenceResult -> SInferenceResult -> Bool # (>=) :: SInferenceResult -> SInferenceResult -> Bool # max :: SInferenceResult -> SInferenceResult -> SInferenceResult # min :: SInferenceResult -> SInferenceResult -> SInferenceResult # | |
sFreeTypeVariables :: Type -> [Name] Source #
sVarScheme :: Name -> TypeScheme Source #
sWithTypeBinding :: Name -> TypeScheme -> Flow SInferenceContext a -> Flow SInferenceContext a Source #
Temporarily add a (term variable, type scheme) to the typing environment
_instantiate :: TypeScheme -> Maybe TypeScheme Source #