Safe Haskell | None |
---|
Monads for type checking and type inference and associated data types
- bindNames :: MonadState CheckState m => Map (ModuleName, Ident) (Type, NameKind) -> m a -> m a
- bindTypes :: MonadState CheckState m => Map (Qualified ProperName) (Kind, TypeKind) -> m a -> m a
- withTypeClassDictionaries :: MonadState CheckState m => [TypeClassDictionaryInScope] -> m a -> m a
- getTypeClassDictionaries :: (Functor m, MonadState CheckState m) => m [TypeClassDictionaryInScope]
- bindLocalVariables :: (Functor m, MonadState CheckState m) => ModuleName -> [(Ident, Type)] -> m a -> m a
- bindLocalTypeVariables :: (Functor m, MonadState CheckState m) => ModuleName -> [(ProperName, Kind)] -> m a -> m a
- lookupVariable :: (Error e, Functor m, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified Ident -> m Type
- lookupTypeVariable :: (Error e, Functor m, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified ProperName -> m Kind
- data CheckState = CheckState {}
- newtype Check a = Check {
- unCheck :: StateT CheckState (Either ErrorStack) a
- getEnv :: (Functor m, MonadState CheckState m) => m Environment
- putEnv :: MonadState CheckState m => Environment -> m ()
- modifyEnv :: MonadState CheckState m => (Environment -> Environment) -> m ()
- runCheck :: Options -> Check a -> Either String (a, Environment)
- runCheck' :: Options -> Environment -> Check a -> Either String (a, Environment)
- guardWith :: MonadError e m => e -> Bool -> m ()
- freshDictionaryName :: Check Int
- liftCheck :: Check a -> UnifyT t Check a
- liftUnify :: Partial t => UnifyT t Check a -> Check (a, Substitution t)
Documentation
bindNames :: MonadState CheckState m => Map (ModuleName, Ident) (Type, NameKind) -> m a -> m aSource
Temporarily bind a collection of names to values
bindTypes :: MonadState CheckState m => Map (Qualified ProperName) (Kind, TypeKind) -> m a -> m aSource
Temporarily bind a collection of names to types
withTypeClassDictionaries :: MonadState CheckState m => [TypeClassDictionaryInScope] -> m a -> m aSource
Temporarily make a collection of type class dictionaries available
getTypeClassDictionaries :: (Functor m, MonadState CheckState m) => m [TypeClassDictionaryInScope]Source
Get the currently available list of type class dictionaries
bindLocalVariables :: (Functor m, MonadState CheckState m) => ModuleName -> [(Ident, Type)] -> m a -> m aSource
Temporarily bind a collection of names to local variables
bindLocalTypeVariables :: (Functor m, MonadState CheckState m) => ModuleName -> [(ProperName, Kind)] -> m a -> m aSource
Temporarily bind a collection of names to local type variables
lookupVariable :: (Error e, Functor m, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified Ident -> m TypeSource
Lookup the type of a value by name in the Environment
lookupTypeVariable :: (Error e, Functor m, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified ProperName -> m KindSource
Lookup the kind of a type by name in the Environment
data CheckState Source
State required for type checking:
CheckState | |
|
The type checking monad, which provides the state of the type checker, and error reporting capabilities
Check | |
|
getEnv :: (Functor m, MonadState CheckState m) => m EnvironmentSource
Get the current Environment
putEnv :: MonadState CheckState m => Environment -> m ()Source
Update the Environment
modifyEnv :: MonadState CheckState m => (Environment -> Environment) -> m ()Source
Modify the Environment
runCheck :: Options -> Check a -> Either String (a, Environment)Source
Run a computation in the Check monad, starting with an empty Environment
runCheck' :: Options -> Environment -> Check a -> Either String (a, Environment)Source
Run a computation in the Check monad, failing with an error, or succeeding with a return value and the final Environment
.
guardWith :: MonadError e m => e -> Bool -> m ()Source
Make an assertion, failing with an error message
freshDictionaryName :: Check IntSource
Generate new type class dictionary name