| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Language.PureScript.TypeChecker.Monad
Description
Monads for type checking and type inference and associated data types
Synopsis
- newtype UnkLevel = UnkLevel (NonEmpty Unknown)
- data Substitution = Substitution {- substType :: Map Int SourceType
- substUnsolved :: Map Int (UnkLevel, SourceType)
- substNames :: Map Int Text
 
- insertUnkName :: MonadState CheckState m => Unknown -> Text -> m ()
- lookupUnkName :: MonadState CheckState m => Unknown -> m (Maybe Text)
- emptySubstitution :: Substitution
- data CheckState = CheckState {- checkEnv :: Environment
- checkNextType :: Int
- checkNextSkolem :: Int
- checkNextSkolemScope :: Int
- checkCurrentModule :: Maybe ModuleName
- checkCurrentModuleImports :: [(SourceAnn, ModuleName, ImportDeclarationType, Maybe ModuleName, Map (ProperName 'TypeName) ([ProperName 'ConstructorName], ExportSource))]
- checkSubstitution :: Substitution
- checkHints :: [ErrorMessageHint]
- checkConstructorImportsForCoercible :: Set (ModuleName, Qualified (ProperName 'ConstructorName))
 
- emptyCheckState :: Environment -> CheckState
- type Unknown = Int
- bindNames :: MonadState CheckState m => Map (Qualified Ident) (SourceType, NameKind, NameVisibility) -> m a -> m a
- bindTypes :: MonadState CheckState m => Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) -> m a -> m a
- withScopedTypeVars :: (MonadState CheckState m, MonadWriter MultipleErrors m) => ModuleName -> [(Text, SourceType)] -> m a -> m a
- withErrorMessageHint :: (MonadState CheckState m, MonadError MultipleErrors m) => ErrorMessageHint -> m a -> m a
- getHints :: MonadState CheckState m => m [ErrorMessageHint]
- rethrowWithPositionTC :: (MonadState CheckState m, MonadError MultipleErrors m) => SourceSpan -> m a -> m a
- warnAndRethrowWithPositionTC :: (MonadState CheckState m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => SourceSpan -> m a -> m a
- withTypeClassDictionaries :: MonadState CheckState m => [NamedDict] -> m a -> m a
- getTypeClassDictionaries :: MonadState CheckState m => m (Map QualifiedBy (Map (Qualified (ProperName 'ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict))))
- lookupTypeClassDictionaries :: MonadState CheckState m => QualifiedBy -> m (Map (Qualified (ProperName 'ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict)))
- lookupTypeClassDictionariesForClass :: MonadState CheckState m => QualifiedBy -> Qualified (ProperName 'ClassName) -> m (Map (Qualified Ident) (NonEmpty NamedDict))
- bindLocalVariables :: MonadState CheckState m => [(SourceSpan, Ident, SourceType, NameVisibility)] -> m a -> m a
- bindLocalTypeVariables :: MonadState CheckState m => ModuleName -> [(ProperName 'TypeName, SourceType)] -> m a -> m a
- makeBindingGroupVisible :: MonadState CheckState m => m ()
- withBindingGroupVisible :: MonadState CheckState m => m a -> m a
- preservingNames :: MonadState CheckState m => m a -> m a
- lookupVariable :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => Qualified Ident -> m SourceType
- getVisibility :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => Qualified Ident -> m NameVisibility
- checkVisibility :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => Qualified Ident -> m ()
- lookupTypeVariable :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified (ProperName 'TypeName) -> m SourceType
- getEnv :: MonadState CheckState m => m Environment
- getLocalContext :: MonadState CheckState m => m Context
- putEnv :: MonadState CheckState m => Environment -> m ()
- modifyEnv :: MonadState CheckState m => (Environment -> Environment) -> m ()
- runCheck :: Functor m => CheckState -> StateT CheckState m a -> m (a, Environment)
- guardWith :: MonadError e m => e -> Bool -> m ()
- capturingSubstitution :: MonadState CheckState m => (a -> Substitution -> b) -> m a -> m b
- withFreshSubstitution :: MonadState CheckState m => m a -> m a
- withoutWarnings :: MonadWriter w m => m a -> m (a, w)
- unsafeCheckCurrentModule :: forall m. (MonadError MultipleErrors m, MonadState CheckState m) => m ModuleName
- debugEnv :: Environment -> [String]
- debugType :: Type a -> String
- debugConstraint :: Constraint a -> String
- debugTypes :: Environment -> [String]
- debugNames :: Environment -> [String]
- debugDataConstructors :: Environment -> [String]
- debugTypeSynonyms :: Environment -> [String]
- debugTypeClassDictionaries :: Environment -> [String]
- debugTypeClasses :: Environment -> [String]
- debugValue :: Expr -> String
- debugSubstitution :: Substitution -> [String]
Documentation
data Substitution Source #
A substitution of unification variables for types.
Constructors
| Substitution | |
| Fields 
 | |
insertUnkName :: MonadState CheckState m => Unknown -> Text -> m () Source #
lookupUnkName :: MonadState CheckState m => Unknown -> m (Maybe Text) Source #
emptySubstitution :: Substitution Source #
An empty substitution
data CheckState Source #
State required for type checking
Constructors
| CheckState | |
| Fields 
 | |
emptyCheckState :: Environment -> CheckState Source #
Create an empty CheckState
bindNames :: MonadState CheckState m => Map (Qualified Ident) (SourceType, NameKind, NameVisibility) -> m a -> m a Source #
Temporarily bind a collection of names to values
bindTypes :: MonadState CheckState m => Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) -> m a -> m a Source #
Temporarily bind a collection of names to types
withScopedTypeVars :: (MonadState CheckState m, MonadWriter MultipleErrors m) => ModuleName -> [(Text, SourceType)] -> m a -> m a Source #
Temporarily bind a collection of names to types
withErrorMessageHint :: (MonadState CheckState m, MonadError MultipleErrors m) => ErrorMessageHint -> m a -> m a Source #
getHints :: MonadState CheckState m => m [ErrorMessageHint] Source #
These hints are added at the front, so the most nested hint occurs at the front, but the simplifier assumes the reverse order.
rethrowWithPositionTC :: (MonadState CheckState m, MonadError MultipleErrors m) => SourceSpan -> m a -> m a Source #
warnAndRethrowWithPositionTC :: (MonadState CheckState m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => SourceSpan -> m a -> m a Source #
withTypeClassDictionaries :: MonadState CheckState m => [NamedDict] -> m a -> m a Source #
Temporarily make a collection of type class dictionaries available
getTypeClassDictionaries :: MonadState CheckState m => m (Map QualifiedBy (Map (Qualified (ProperName 'ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict)))) Source #
Get the currently available map of type class dictionaries
lookupTypeClassDictionaries :: MonadState CheckState m => QualifiedBy -> m (Map (Qualified (ProperName 'ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict))) Source #
Lookup type class dictionaries in a module.
lookupTypeClassDictionariesForClass :: MonadState CheckState m => QualifiedBy -> Qualified (ProperName 'ClassName) -> m (Map (Qualified Ident) (NonEmpty NamedDict)) Source #
Lookup type class dictionaries in a module.
bindLocalVariables :: MonadState CheckState m => [(SourceSpan, Ident, SourceType, NameVisibility)] -> m a -> m a Source #
Temporarily bind a collection of names to local variables
bindLocalTypeVariables :: MonadState CheckState m => ModuleName -> [(ProperName 'TypeName, SourceType)] -> 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) => Qualified Ident -> m SourceType Source #
Lookup the type of a value by name in the Environment
getVisibility :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => 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) => Qualified Ident -> m () Source #
Assert that a name is visible
lookupTypeVariable :: (e ~ MultipleErrors, MonadState CheckState m, MonadError e m) => ModuleName -> Qualified (ProperName 'TypeName) -> m SourceType Source #
Lookup the kind of a type by name in the Environment
getEnv :: MonadState CheckState m => m Environment Source #
Get the current Environment
getLocalContext :: MonadState CheckState m => m Context Source #
Get locally-bound names in context, to create an error message.
putEnv :: MonadState CheckState m => Environment -> m () Source #
Update the Environment
modifyEnv :: MonadState CheckState m => (Environment -> Environment) -> m () Source #
Modify the Environment
runCheck :: Functor m => CheckState -> 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
capturingSubstitution :: MonadState CheckState m => (a -> Substitution -> b) -> m a -> m b Source #
withFreshSubstitution :: MonadState CheckState m => m a -> m a Source #
withoutWarnings :: MonadWriter w m => m a -> m (a, w) Source #
unsafeCheckCurrentModule :: forall m. (MonadError MultipleErrors m, MonadState CheckState m) => m ModuleName Source #
debugEnv :: Environment -> [String] Source #
debugConstraint :: Constraint a -> String Source #
debugTypes :: Environment -> [String] Source #
debugNames :: Environment -> [String] Source #
debugDataConstructors :: Environment -> [String] Source #
debugTypeSynonyms :: Environment -> [String] Source #
debugTypeClasses :: Environment -> [String] Source #
debugValue :: Expr -> String Source #
debugSubstitution :: Substitution -> [String] Source #