| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
HieDb.Utils
Synopsis
- type TypeIndexing a = StateT (IntMap IntSet) IO a
- addTypeRef :: HieDb -> FilePath -> Array TypeIndex HieTypeFlat -> Array TypeIndex (Maybe Int64) -> RealSrcSpan -> TypeIndex -> TypeIndexing ()
- makeNc :: IO NameCache
- getHieFilesIn :: FilePath -> IO [FilePath]
- withHieFile :: (NameCacheMonad m, MonadIO m) => FilePath -> (HieFile -> m a) -> m a
- findDefInFile :: OccName -> Module -> FilePath -> IO (Either HieDbErr (RealSrcSpan, Module))
- pointCommand :: HieFile -> (Int, Int) -> Maybe (Int, Int) -> (HieAST TypeIndex -> a) -> [a]
- dynFlagsForPrinting :: LibDir -> IO DynFlags
- isCons :: String -> Bool
- data AstInfo = AstInfo {- astInfoRefs :: [RefRow]
- astInfoDecls :: [DeclRow]
- astInfoImports :: [ImportRow]
 
- genAstInfo :: FilePath -> Module -> Map Identifier [(Span, IdentifierDetails a)] -> AstInfo
- genDefRow :: FilePath -> Module -> Map Identifier [(Span, IdentifierDetails a)] -> [DefRow]
- identifierTree :: HieAST a -> Tree (HieAST a)
- generateExports :: FilePath -> [AvailInfo] -> [ExportRow]
Documentation
addTypeRef :: HieDb -> FilePath -> Array TypeIndex HieTypeFlat -> Array TypeIndex (Maybe Int64) -> RealSrcSpan -> TypeIndex -> TypeIndexing () Source #
getHieFilesIn :: FilePath -> IO [FilePath] Source #
Recursively search for .hie and .hie-boot  files in given directory
withHieFile :: (NameCacheMonad m, MonadIO m) => FilePath -> (HieFile -> m a) -> m a Source #
findDefInFile :: OccName -> Module -> FilePath -> IO (Either HieDbErr (RealSrcSpan, Module)) Source #
Given the path to a HieFile, it tries to find the SrcSpan of an External name in it by loading it and then looking for the name in NameCache
pointCommand :: HieFile -> (Int, Int) -> Maybe (Int, Int) -> (HieAST TypeIndex -> a) -> [a] Source #
Constructors
| AstInfo | |
| Fields 
 | |
genAstInfo :: FilePath -> Module -> Map Identifier [(Span, IdentifierDetails a)] -> AstInfo Source #
genDefRow :: FilePath -> Module -> Map Identifier [(Span, IdentifierDetails a)] -> [DefRow] Source #