Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides functionality to manage imports
- addImplicitImport :: (MonadIO m, MonadError IdeError m) => FilePath -> ModuleName -> m [Text]
- addQualifiedImport :: (MonadIO m, MonadError IdeError m) => FilePath -> ModuleName -> ModuleName -> m [Text]
- addImportForIdentifier :: (Ide m, MonadError IdeError m) => FilePath -> Text -> Maybe ModuleName -> [Filter] -> m (Either [Match IdeDeclaration] [Text])
- answerRequest :: MonadIO m => Maybe FilePath -> [Text] -> m Success
- parseImportsFromFile :: (MonadIO m, MonadError IdeError m) => FilePath -> m (ModuleName, [(ModuleName, ImportDeclarationType, Maybe ModuleName)])
- parseImport :: Text -> Maybe Import
- prettyPrintImportSection :: [Import] -> [Text]
- addImplicitImport' :: [Import] -> ModuleName -> [Text]
- addQualifiedImport' :: [Import] -> ModuleName -> ModuleName -> [Text]
- addExplicitImport' :: IdeDeclaration -> ModuleName -> Maybe ModuleName -> [Import] -> [Import]
- sliceImportSection :: [Text] -> Either Text (ModuleName, [Text], [Import], [Text])
- prettyPrintImport' :: Import -> Text
- data Import = Import ModuleName ImportDeclarationType (Maybe ModuleName)
Documentation
:: (MonadIO m, MonadError IdeError m) | |
=> FilePath | The source file read from |
-> ModuleName | The module to import |
-> m [Text] |
Adds an implicit import like import Prelude
to a Sourcefile.
:: (MonadIO m, MonadError IdeError m) | |
=> FilePath | The sourcefile read from |
-> ModuleName | The module to import |
-> ModuleName | The qualifier under which to import |
-> m [Text] |
Adds a qualified import like import Data.Map as Map
to a source file.
addImportForIdentifier Source #
:: (Ide m, MonadError IdeError m) | |
=> FilePath | The Sourcefile to read from |
-> Text | The identifier to import |
-> Maybe ModuleName | The optional qualifier under which to import |
-> [Filter] | Filters to apply before searching for the identifier |
-> m (Either [Match IdeDeclaration] [Text]) |
Looks up the given identifier in the currently loaded modules.
- Throws an error if the identifier cannot be found.
- If exactly one match is found, adds an explicit import to the importsection
- If more than one possible imports are found, reports the possibilities as a list of completions.
answerRequest :: MonadIO m => Maybe FilePath -> [Text] -> m Success Source #
Writes a list of lines to Just filepath
and responds with a TextResult
,
or returns the lines as a MultilineTextResult
if Nothing
was given as the
first argument.
parseImportsFromFile :: (MonadIO m, MonadError IdeError m) => FilePath -> m (ModuleName, [(ModuleName, ImportDeclarationType, Maybe ModuleName)]) Source #
Reads a file and returns the parsed module name as well as the parsed imports, while ignoring eventual parse errors that aren't relevant to the import section
prettyPrintImportSection :: [Import] -> [Text] Source #
addImplicitImport' :: [Import] -> ModuleName -> [Text] Source #
addQualifiedImport' :: [Import] -> ModuleName -> ModuleName -> [Text] Source #
addExplicitImport' :: IdeDeclaration -> ModuleName -> Maybe ModuleName -> [Import] -> [Import] Source #
sliceImportSection :: [Text] -> Either Text (ModuleName, [Text], [Import], [Text]) Source #
prettyPrintImport' :: Import -> Text Source #