| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
HieDb.Query
Synopsis
- getAllIndexedMods :: HieDb -> IO [HieModuleRow]
- getAllIndexedExports :: HieDb -> IO [ExportRow]
- getExportsForModule :: HieDb -> ModuleName -> IO [ExportRow]
- findExporters :: HieDb -> OccName -> ModuleName -> Unit -> IO [ModuleName]
- resolveUnitId :: HieDb -> ModuleName -> IO (Either HieDbErr Unit)
- findReferences :: HieDb -> Bool -> OccName -> Maybe ModuleName -> Maybe Unit -> [FilePath] -> IO [Res RefRow]
- lookupHieFile :: HieDb -> ModuleName -> Unit -> IO (Maybe HieModuleRow)
- lookupHieFileFromSource :: HieDb -> FilePath -> IO (Maybe HieModuleRow)
- findTypeRefs :: HieDb -> Bool -> OccName -> Maybe ModuleName -> Maybe Unit -> [FilePath] -> IO [Res TypeRef]
- findDef :: HieDb -> OccName -> Maybe ModuleName -> Maybe Unit -> IO [Res DefRow]
- findOneDef :: HieDb -> OccName -> Maybe ModuleName -> Maybe Unit -> IO (Either HieDbErr (Res DefRow))
- searchDef :: HieDb -> String -> IO [Res DefRow]
- withTarget :: HieDb -> HieTarget -> (HieFile -> a) -> IO (Either HieDbErr a)
- type Vertex = (String, String, String, Int, Int, Int, Int)
- declRefs :: HieDb -> IO ()
- getGraph :: HieDb -> IO (AdjacencyMap Vertex)
- getVertices :: HieDb -> [Symbol] -> IO [Vertex]
- getReachable :: HieDb -> [Symbol] -> IO [Vertex]
- getUnreachable :: HieDb -> [Symbol] -> IO [Vertex]
- html :: (NameCacheMonad m, MonadIO m) => HieDb -> [Symbol] -> m ()
- getAnnotations :: HieDb -> [Symbol] -> IO (Map FilePath (ModuleName, Set Span))
- getReachableUnreachable :: HieDb -> [Symbol] -> IO ([Vertex], [Vertex])
- splitByReachability :: Ord a => AdjacencyMap a -> [a] -> (Set a, Set a)
Documentation
getAllIndexedMods :: HieDb -> IO [HieModuleRow] Source #
List all modules indexed in HieDb.
getExportsForModule :: HieDb -> ModuleName -> IO [ExportRow] Source #
List all exports of the given module
findExporters :: HieDb -> OccName -> ModuleName -> Unit -> IO [ModuleName] Source #
Find all the modules that export an identifier |
resolveUnitId :: HieDb -> ModuleName -> IO (Either HieDbErr Unit) Source #
Lookup Unit associated with given ModuleName. HieDbErr is returned if no module with given name has been indexed or if ModuleName is ambiguous (i.e. there are multiple packages containing module with given name)
findReferences :: HieDb -> Bool -> OccName -> Maybe ModuleName -> Maybe Unit -> [FilePath] -> IO [Res RefRow] Source #
lookupHieFile :: HieDb -> ModuleName -> Unit -> IO (Maybe HieModuleRow) Source #
Lookup HieModule row from HieDb given its ModuleName and Unit 
lookupHieFileFromSource :: HieDb -> FilePath -> IO (Maybe HieModuleRow) Source #
Lookup HieModule row from HieDb given the path to the Haskell source file 
findTypeRefs :: HieDb -> Bool -> OccName -> Maybe ModuleName -> Maybe Unit -> [FilePath] -> IO [Res TypeRef] Source #
findOneDef :: HieDb -> OccName -> Maybe ModuleName -> Maybe Unit -> IO (Either HieDbErr (Res DefRow)) Source #
withTarget :: HieDb -> HieTarget -> (HieFile -> a) -> IO (Either HieDbErr a) Source #
withTarget db t f runs function f with HieFile specified by HieTarget t.
In case the target is given by ModuleName (and optionally Unit) it is first resolved
from HieDb, which can lead to error if given file is not indexed/Module name is ambiguous.
splitByReachability :: Ord a => AdjacencyMap a -> [a] -> (Set a, Set a) Source #