Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- sCHEMA_VERSION :: Integer
- dB_VERSION :: Integer
- checkVersion :: (HieDb -> IO a) -> HieDb -> IO a
- withHieDb :: FilePath -> (HieDb -> IO a) -> IO a
- withHieDbAndFlags :: LibDir -> FilePath -> (DynFlags -> HieDb -> IO a) -> IO a
- initConn :: HieDb -> IO ()
- addArr :: HieDb -> Array TypeIndex HieTypeFlat -> IO (Array TypeIndex (Maybe Int64))
- addTypeRefs :: HieDb -> FilePath -> HieFile -> Array TypeIndex (Maybe Int64) -> IO ()
- data SkipOptions = SkipOptions {
- skipRefs :: Bool
- skipDecls :: Bool
- skipDefs :: Bool
- skipExports :: Bool
- skipImports :: Bool
- skipTypes :: Bool
- skipTypeRefs :: Bool
- defaultSkipOptions :: SkipOptions
- addRefsFrom :: (MonadIO m, NameCacheMonad m) => HieDb -> Maybe FilePath -> SkipOptions -> FilePath -> m Bool
- addRefsFromLoaded :: MonadIO m => HieDb -> FilePath -> SourceFile -> Fingerprint -> HieFile -> m ()
- addRefsFromLoadedInternal :: MonadIO m => HieDb -> FilePath -> SourceFile -> Fingerprint -> SkipOptions -> HieFile -> m ()
- addRefsFromLoaded_unsafe :: MonadIO m => HieDb -> FilePath -> SourceFile -> Fingerprint -> SkipOptions -> HieFile -> m ()
- addSrcFile :: HieDb -> FilePath -> FilePath -> Bool -> IO ()
- removeDependencySrcFiles :: HieDb -> IO ()
- deleteFileFromIndex :: HieDb -> FilePath -> IO ()
- deleteMissingRealFiles :: HieDb -> IO ()
- garbageCollectTypeNames :: HieDb -> IO Int
- deleteInternalTables :: Connection -> FilePath -> IO ()
Documentation
dB_VERSION :: Integer Source #
checkVersion :: (HieDb -> IO a) -> HieDb -> IO a Source #
checkVersion f db
checks the schema version associated with given db
.
If that version is supported by hiedb, it runs the function f
with the db
.
Otherwise it throws IncompatibleSchemaVersion
exception.
withHieDb :: FilePath -> (HieDb -> IO a) -> IO a Source #
Given path to .hiedb
file, constructs HieDb
and passes it to given function.
withHieDbAndFlags :: LibDir -> FilePath -> (DynFlags -> HieDb -> IO a) -> IO a Source #
Given GHC LibDir and path to .hiedb
file,
constructs DynFlags (required for printing info from .hie
files)
and HieDb
and passes them to given function.
:: HieDb | |
-> FilePath | Path to |
-> HieFile | Data loaded from the |
-> Array TypeIndex (Maybe Int64) | Maps TypeIndex to database ID assigned to record in |
-> IO () |
Add references to types from given .hie
file to DB.
data SkipOptions Source #
Options to skip indexing phases
SkipOptions | |
|
Instances
Show SkipOptions Source # | |
Defined in HieDb.Create showsPrec :: Int -> SkipOptions -> ShowS # show :: SkipOptions -> String # showList :: [SkipOptions] -> ShowS # |
addRefsFrom :: (MonadIO m, NameCacheMonad m) => HieDb -> Maybe FilePath -> SkipOptions -> FilePath -> m Bool Source #
Adds all references from given .hie
file to HieDb
.
The indexing is skipped if the file was not modified since the last time it was indexed.
The boolean returned is true if the file was actually indexed
:: MonadIO m | |
=> HieDb | HieDb into which we're adding the file |
-> FilePath | Path to |
-> SourceFile | Path to .hs file from which |
-> Fingerprint | The hash of the |
-> HieFile | Data loaded from the |
-> m () |
addRefsFromLoadedInternal Source #
:: MonadIO m | |
=> HieDb | HieDb into which we're adding the file |
-> FilePath | Path to |
-> SourceFile | Path to .hs file from which |
-> Fingerprint | The hash of the |
-> SkipOptions | Skip indexing certain tables |
-> HieFile | Data loaded from the |
-> m () |
addRefsFromLoaded_unsafe Source #
:: MonadIO m | |
=> HieDb | HieDb into which we're adding the file |
-> FilePath | Path to |
-> SourceFile | Path to .hs file from which |
-> Fingerprint | The hash of the |
-> SkipOptions | Skip indexing certain tables |
-> HieFile | Data loaded from the |
-> m () |
Like addRefsFromLoaded
but without:
1) using a transaction
2) cleaning up previous versions of the file
Mostly useful to index a new database from scratch as fast as possible
:: HieDb | |
-> FilePath | Path to |
-> FilePath | Path to .hs file to be added to DB |
-> Bool | Is this a real source file? I.e. does it come from user's project (as opposed to from project's dependency)? |
-> IO () |
Add path to .hs source given path to .hie
file which has already been indexed.
No action is taken if the corresponding .hie
file has not been indexed yet.
removeDependencySrcFiles :: HieDb -> IO () Source #
Remove the path to .hs source for all dependency .hie
files. Useful for resetting
the indexed dependencies if the sources have been deleted for some reason.
deleteFileFromIndex :: HieDb -> FilePath -> IO () Source #
Delete all occurrences of given .hie
file from the database
deleteMissingRealFiles :: HieDb -> IO () Source #
Delete all entries associated with modules for which the modInfoSrcFile
doesn't exist
on the disk.
Doesn't delete it if there is no associated modInfoSrcFile
garbageCollectTypeNames :: HieDb -> IO Int Source #
Garbage collect typenames with no references - it is a good idea to call this function after a sequence of database updates (inserts or deletes)
deleteInternalTables :: Connection -> FilePath -> IO () Source #