Safe Haskell | None |
---|---|
Language | Haskell2010 |
Development.IDE.Import.DependencyInformation
Synopsis
- data DependencyInformation = DependencyInformation {
- depErrorNodes :: !(FilePathIdMap (NonEmpty NodeError))
- depModuleNames :: !(FilePathIdMap ShowableModuleName)
- depModuleDeps :: !(FilePathIdMap FilePathIdSet)
- depReverseModuleDeps :: !(IntMap IntSet)
- depPathIdMap :: !PathIdMap
- depBootMap :: !BootIdMap
- newtype ModuleImports = ModuleImports {
- moduleImports :: [(Located ModuleName, Maybe FilePathId)]
- data RawDependencyInformation = RawDependencyInformation {
- rawImports :: !(FilePathIdMap (Either ModuleParseError ModuleImports))
- rawPathIdMap :: !PathIdMap
- rawBootMap :: !BootIdMap
- rawModuleNameMap :: !(FilePathIdMap ShowableModuleName)
- data NodeError
- data ModuleParseError = ModuleParseError
- newtype TransitiveDependencies = TransitiveDependencies {}
- newtype FilePathId = FilePathId {
- getFilePathId :: Int
- data NamedModuleDep = NamedModuleDep {}
- newtype ShowableModuleName = ShowableModuleName {}
- data PathIdMap
- emptyPathIdMap :: PathIdMap
- getPathId :: ArtifactsLocation -> PathIdMap -> (FilePathId, PathIdMap)
- lookupPathToId :: PathIdMap -> NormalizedFilePath -> Maybe FilePathId
- insertImport :: FilePathId -> Either ModuleParseError ModuleImports -> RawDependencyInformation -> RawDependencyInformation
- pathToId :: PathIdMap -> NormalizedFilePath -> FilePathId
- idToPath :: PathIdMap -> FilePathId -> NormalizedFilePath
- reachableModules :: DependencyInformation -> [NormalizedFilePath]
- processDependencyInformation :: RawDependencyInformation -> DependencyInformation
- transitiveDeps :: DependencyInformation -> NormalizedFilePath -> Maybe TransitiveDependencies
- transitiveReverseDependencies :: NormalizedFilePath -> DependencyInformation -> Maybe [NormalizedFilePath]
- immediateReverseDependencies :: NormalizedFilePath -> DependencyInformation -> Maybe [NormalizedFilePath]
- type BootIdMap = FilePathIdMap FilePathId
- insertBootId :: FilePathId -> FilePathId -> BootIdMap -> BootIdMap
Documentation
data DependencyInformation Source #
Constructors
DependencyInformation | |
Fields
|
Instances
Show DependencyInformation Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> DependencyInformation -> ShowS # show :: DependencyInformation -> String # showList :: [DependencyInformation] -> ShowS # | |
Generic DependencyInformation Source # | |
Defined in Development.IDE.Import.DependencyInformation Associated Types type Rep DependencyInformation :: Type -> Type # Methods from :: DependencyInformation -> Rep DependencyInformation x # to :: Rep DependencyInformation x -> DependencyInformation # | |
NFData DependencyInformation Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods rnf :: DependencyInformation -> () # | |
type Rep DependencyInformation Source # | |
Defined in Development.IDE.Import.DependencyInformation |
newtype ModuleImports Source #
The imports for a given module.
Constructors
ModuleImports | |
Fields
|
Instances
Show ModuleImports Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> ModuleImports -> ShowS # show :: ModuleImports -> String # showList :: [ModuleImports] -> ShowS # |
data RawDependencyInformation Source #
Unprocessed results that we find by following imports recursively.
Constructors
RawDependencyInformation | |
Fields
|
Instances
Show RawDependencyInformation Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> RawDependencyInformation -> ShowS # show :: RawDependencyInformation -> String # showList :: [RawDependencyInformation] -> ShowS # |
An error attached to a node in the dependency graph.
Constructors
PartOfCycle (Located ModuleName) [FilePathId] | This module is part of an import cycle. The module name corresponds to the import that enters the cycle starting from this module. The list of filepaths represents the elements in the cycle in unspecified order. |
FailedToLocateImport (Located ModuleName) | This module has an import that couldn’t be located. |
ParseError ModuleParseError | |
ParentOfErrorNode (Located ModuleName) | This module is the parent of a module that cannot be processed (either it cannot be parsed, is part of a cycle or the parent of another error node). |
Instances
data ModuleParseError Source #
This does not contain the actual parse error as that is already reported by GetParsedModule.
Constructors
ModuleParseError |
Instances
Show ModuleParseError Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> ModuleParseError -> ShowS # show :: ModuleParseError -> String # showList :: [ModuleParseError] -> ShowS # | |
Generic ModuleParseError Source # | |
Defined in Development.IDE.Import.DependencyInformation Associated Types type Rep ModuleParseError :: Type -> Type # Methods from :: ModuleParseError -> Rep ModuleParseError x # to :: Rep ModuleParseError x -> ModuleParseError # | |
NFData ModuleParseError Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods rnf :: ModuleParseError -> () # | |
type Rep ModuleParseError Source # | |
newtype TransitiveDependencies Source #
Constructors
TransitiveDependencies | |
Fields
|
Instances
newtype FilePathId Source #
For processing dependency information, we need lots of maps and sets of filepaths. Comparing Strings is really slow, so we work with IntMap/IntSet instead and only convert at the edges.
Constructors
FilePathId | |
Fields
|
Instances
Eq FilePathId Source # | |
Defined in Development.IDE.Import.DependencyInformation | |
Ord FilePathId Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods compare :: FilePathId -> FilePathId -> Ordering # (<) :: FilePathId -> FilePathId -> Bool # (<=) :: FilePathId -> FilePathId -> Bool # (>) :: FilePathId -> FilePathId -> Bool # (>=) :: FilePathId -> FilePathId -> Bool # max :: FilePathId -> FilePathId -> FilePathId # min :: FilePathId -> FilePathId -> FilePathId # | |
Show FilePathId Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> FilePathId -> ShowS # show :: FilePathId -> String # showList :: [FilePathId] -> ShowS # | |
NFData FilePathId Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods rnf :: FilePathId -> () # |
data NamedModuleDep Source #
Constructors
NamedModuleDep | |
Fields |
Instances
newtype ShowableModuleName Source #
Constructors
ShowableModuleName | |
Fields |
Instances
Show ShowableModuleName Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods showsPrec :: Int -> ShowableModuleName -> ShowS # show :: ShowableModuleName -> String # showList :: [ShowableModuleName] -> ShowS # | |
NFData ShowableModuleName Source # | |
Defined in Development.IDE.Import.DependencyInformation Methods rnf :: ShowableModuleName -> () # |
getPathId :: ArtifactsLocation -> PathIdMap -> (FilePathId, PathIdMap) Source #
insertImport :: FilePathId -> Either ModuleParseError ModuleImports -> RawDependencyInformation -> RawDependencyInformation Source #
pathToId :: PathIdMap -> NormalizedFilePath -> FilePathId Source #
idToPath :: PathIdMap -> FilePathId -> NormalizedFilePath Source #
transitiveDeps :: DependencyInformation -> NormalizedFilePath -> Maybe TransitiveDependencies Source #
returns all transitive dependencies in topological order.
transitiveReverseDependencies :: NormalizedFilePath -> DependencyInformation -> Maybe [NormalizedFilePath] Source #
Transitive reverse dependencies of a file
immediateReverseDependencies :: NormalizedFilePath -> DependencyInformation -> Maybe [NormalizedFilePath] Source #
Immediate reverse dependencies of a file
type BootIdMap = FilePathIdMap FilePathId Source #
insertBootId :: FilePathId -> FilePathId -> BootIdMap -> BootIdMap Source #