Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- desugarImports :: forall m. (MonadError MultipleErrors m, MonadWriter MultipleErrors m) => [ExternsFile] -> [Module] -> m [Module]
- desugarImportsWithEnv :: forall m. (MonadError MultipleErrors m, MonadWriter MultipleErrors m) => [ExternsFile] -> [Module] -> m (Env, [Module])
- type Env = Map ModuleName (SourceSpan, Imports, Exports)
- primEnv :: Env
- data ImportRecord a = ImportRecord {}
- data ImportProvenance
- data Imports = Imports {
- importedTypes :: ImportMap (ProperName TypeName)
- importedTypeOps :: ImportMap (OpName TypeOpName)
- importedDataConstructors :: ImportMap (ProperName ConstructorName)
- importedTypeClasses :: ImportMap (ProperName ClassName)
- importedValues :: ImportMap Ident
- importedValueOps :: ImportMap (OpName ValueOpName)
- importedModules :: Set ModuleName
- importedQualModules :: Set ModuleName
- importedKinds :: ImportMap (ProperName KindName)
- data Exports = Exports {
- exportedTypes :: Map (ProperName TypeName) ([ProperName ConstructorName], ExportSource)
- exportedTypeOps :: Map (OpName TypeOpName) ExportSource
- exportedTypeClasses :: Map (ProperName ClassName) ExportSource
- exportedValues :: Map Ident ExportSource
- exportedValueOps :: Map (OpName ValueOpName) ExportSource
- exportedKinds :: Map (ProperName KindName) ExportSource
Documentation
desugarImports :: forall m. (MonadError MultipleErrors m, MonadWriter MultipleErrors m) => [ExternsFile] -> [Module] -> m [Module] Source #
Replaces all local names with qualified names within a list of modules. The modules should be topologically sorted beforehand.
desugarImportsWithEnv :: forall m. (MonadError MultipleErrors m, MonadWriter MultipleErrors m) => [ExternsFile] -> [Module] -> m (Env, [Module]) Source #
type Env = Map ModuleName (SourceSpan, Imports, Exports) Source #
The imports and exports for a collection of modules. The SourceSpan
is used
to store the source location of the module with a given name, used to provide
useful information when there is a duplicate module definition.
data ImportRecord a Source #
The details for an import: the name of the thing that is being imported
(x
if importing from A
), the module that the thing was originally
defined in (for re-export resolution), and the import provenance (see below).
Instances
Eq a => Eq (ImportRecord a) Source # | |
Defined in Language.PureScript.Sugar.Names.Env (==) :: ImportRecord a -> ImportRecord a -> Bool # (/=) :: ImportRecord a -> ImportRecord a -> Bool # | |
Ord a => Ord (ImportRecord a) Source # | |
Defined in Language.PureScript.Sugar.Names.Env compare :: ImportRecord a -> ImportRecord a -> Ordering # (<) :: ImportRecord a -> ImportRecord a -> Bool # (<=) :: ImportRecord a -> ImportRecord a -> Bool # (>) :: ImportRecord a -> ImportRecord a -> Bool # (>=) :: ImportRecord a -> ImportRecord a -> Bool # max :: ImportRecord a -> ImportRecord a -> ImportRecord a # min :: ImportRecord a -> ImportRecord a -> ImportRecord a # | |
Show a => Show (ImportRecord a) Source # | |
Defined in Language.PureScript.Sugar.Names.Env showsPrec :: Int -> ImportRecord a -> ShowS # show :: ImportRecord a -> String # showList :: [ImportRecord a] -> ShowS # |
data ImportProvenance Source #
Used to track how an import was introduced into scope. This allows us to handle the one-open-import special case that allows a name conflict to become a warning rather than being an unresolvable situation.
Instances
Eq ImportProvenance Source # | |
Defined in Language.PureScript.Sugar.Names.Env (==) :: ImportProvenance -> ImportProvenance -> Bool # (/=) :: ImportProvenance -> ImportProvenance -> Bool # | |
Ord ImportProvenance Source # | |
Defined in Language.PureScript.Sugar.Names.Env compare :: ImportProvenance -> ImportProvenance -> Ordering # (<) :: ImportProvenance -> ImportProvenance -> Bool # (<=) :: ImportProvenance -> ImportProvenance -> Bool # (>) :: ImportProvenance -> ImportProvenance -> Bool # (>=) :: ImportProvenance -> ImportProvenance -> Bool # max :: ImportProvenance -> ImportProvenance -> ImportProvenance # min :: ImportProvenance -> ImportProvenance -> ImportProvenance # | |
Show ImportProvenance Source # | |
Defined in Language.PureScript.Sugar.Names.Env showsPrec :: Int -> ImportProvenance -> ShowS # show :: ImportProvenance -> String # showList :: [ImportProvenance] -> ShowS # |
The imported declarations for a module, including the module's own members.
Imports | |
|
The exported declarations from a module.
Exports | |
|