purescript-0.5.2.4: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell98

Language.PureScript.TypeChecker.Monad

Description

Monads for type checking and type inference and associated data types

Synopsis

Documentation

bindNames :: MonadState CheckState m => Map (ModuleName, Ident) (Type, NameKind) -> m a -> m a Source

Temporarily bind a collection of names to values

bindTypes :: MonadState CheckState m => Map (Qualified ProperName) (Kind, TypeKind) -> m a -> m a Source

Temporarily bind a collection of names to types

withTypeClassDictionaries :: MonadState CheckState m => [TypeClassDictionaryInScope] -> m a -> m a Source

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 a Source

Temporarily bind a collection of names to local variables

bindLocalTypeVariables :: (Functor m, MonadState CheckState m) => ModuleName -> [(ProperName, Kind)] -> m a -> m a Source

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 Type Source

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 Kind Source

Lookup the kind of a type by name in the Environment

data CheckState Source

State required for type checking:

Constructors

CheckState 

Fields

checkEnv :: Environment

The current Environment

checkNextVar :: Int

The next fresh unification variable name

checkNextDictName :: Int

The next type class dictionary name

checkCurrentModule :: Maybe ModuleName

The current module

newtype Check a Source

The type checking monad, which provides the state of the type checker, and error reporting capabilities

Constructors

Check 

getEnv :: (Functor m, MonadState CheckState m) => m Environment Source

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 Int Source

Generate new type class dictionary name

liftCheck :: Check a -> UnifyT t Check a Source

Lift a computation in the Check monad into the substitution monad.

liftUnify :: Partial t => UnifyT t Check a -> Check (a, Substitution t) Source

Run a computation in the substitution monad, generating a return value and the final substitution.