purescript-0.8.5.0: 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

data Substitution Source

A substitution of unification variables for types or kinds

Constructors

Substitution 

Fields

substType :: Map Int Type

Type substitution

substKind :: Map Int Kind

Kind substitution

emptySubstitution :: Substitution Source

An empty substitution

data CheckState Source

State required for type checking

Constructors

CheckState 

Fields

checkEnv :: Environment

The current Environment

checkNextType :: Int

The next type unification variable

checkNextKind :: Int

The next kind unification variable

checkNextSkolem :: Int

The next skolem variable

checkNextSkolemScope :: Int

The next skolem scope constant

checkCurrentModule :: Maybe ModuleName

The current module

checkSubstitution :: Substitution

The current substitution

emptyCheckState :: Environment -> CheckState Source

Create an empty CheckState

type Unknown = Int Source

Unification variables

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

Temporarily bind a collection of names to values

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

Temporarily bind a collection of names to types

withScopedTypeVars :: (MonadState CheckState m, MonadWriter MultipleErrors m) => ModuleName -> [(String, Kind)] -> 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 :: MonadState CheckState m => m (Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) TypeClassDictionaryInScope))) Source

Get the currently available map of type class dictionaries

bindLocalVariables :: MonadState CheckState m => ModuleName -> [(Ident, Type, NameVisibility)] -> m a -> m a Source

Temporarily bind a collection of names to local variables

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

Temporarily bind a collection of names to local type variables

makeBindingGroupVisible :: MonadState CheckState m => m () Source

Update the visibility of all names to Defined

withBindingGroupVisible :: MonadState CheckState m => m a -> m a Source

Update the visibility of all names to Defined in the scope of the provided action

preservingNames :: MonadState CheckState m => m a -> m a Source

Perform an action while preserving the names from the Environment.

lookupVariable :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified Ident -> m Type Source

Lookup the type of a value by name in the Environment

getVisibility :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified Ident -> m NameVisibility Source

Lookup the visibility of a value by name in the Environment

checkVisibility :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified Ident -> m () Source

Assert that a name is visible

lookupTypeVariable :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified (ProperName TypeName) -> m Kind Source

Lookup the kind of a type by name in the Environment

getEnv :: 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 :: Functor m => StateT CheckState m a -> m (a, Environment) Source

Run a computation in the typechecking monad, starting with an empty Environment

runCheck' :: Functor m => Environment -> StateT CheckState m a -> m (a, Environment) Source

Run a computation in the typechecking 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

liftUnify :: (MonadState CheckState m, MonadWriter MultipleErrors m, MonadError MultipleErrors m) => m a -> m (a, Substitution) Source

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

liftUnifyWarnings :: (MonadState CheckState m, MonadWriter MultipleErrors m, MonadError MultipleErrors m) => (Substitution -> ErrorMessage -> ErrorMessage) -> m a -> m (a, Substitution) Source

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