| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Development.IDE.Session
Description
The logic for setting up a ghcide session by tapping into hie-bios.
Synopsis
- data SessionLoadingOptions = SessionLoadingOptions {
- findCradle :: FilePath -> IO (Maybe FilePath)
 - loadCradle :: Recorder (WithPriority Log) -> Maybe FilePath -> FilePath -> IO (Cradle Void)
 - getCacheDirs :: String -> [String] -> IO CacheDirs
 - getInitialGhcLibDir :: Recorder (WithPriority Log) -> FilePath -> IO (Maybe LibDir)
 
 - data CacheDirs = CacheDirs {}
 - loadSession :: Recorder (WithPriority Log) -> FilePath -> IO (Action IdeGhcSession)
 - loadSessionWithOptions :: Recorder (WithPriority Log) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
 - setInitialDynFlags :: Recorder (WithPriority Log) -> FilePath -> SessionLoadingOptions -> IO (Maybe LibDir)
 - getHieDbLoc :: FilePath -> IO FilePath
 - runWithDb :: Recorder (WithPriority Log) -> FilePath -> (WithHieDb -> IndexQueue -> IO ()) -> IO ()
 - retryOnSqliteBusy :: (MonadIO m, MonadCatch m, RandomGen g) => Recorder (WithPriority Log) -> g -> m a -> m a
 - retryOnException :: (MonadIO m, MonadCatch m, RandomGen g, Exception e) => (e -> Maybe e) -> Recorder (WithPriority Log) -> Int -> Int -> Int -> g -> m a -> m a
 - data Log
- = LogSettingInitialDynFlags
 - | LogGetInitialGhcLibDirDefaultCradleFail !CradleError !FilePath !(Maybe FilePath) !(Cradle Void)
 - | LogGetInitialGhcLibDirDefaultCradleNone
 - | LogHieDbRetry !Int !Int !Int !SomeException
 - | LogHieDbRetriesExhausted !Int !Int !Int !SomeException
 - | LogHieDbWriterThreadSQLiteError !SQLError
 - | LogHieDbWriterThreadException !SomeException
 - | LogInterfaceFilesCacheDir !FilePath
 - | LogKnownFilesUpdated !(HashMap Target (HashSet NormalizedFilePath))
 - | LogMakingNewHscEnv ![UnitId]
 - | LogDLLLoadError !String
 - | LogCradlePath !FilePath
 - | LogCradleNotFound !FilePath
 - | LogSessionLoadingResult !(Either [CradleError] (ComponentOptions, FilePath))
 - | LogCradle !(Cradle Void)
 - | LogNoneCradleFound FilePath
 - | LogNewComponentCache !(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
 - | LogHieBios Log
 
 
Documentation
data SessionLoadingOptions Source #
Constructors
| SessionLoadingOptions | |
Fields 
  | |
Instances
| Default SessionLoadingOptions Source # | |
Defined in Development.IDE.Session Methods  | |
Constructors
| CacheDirs | |
Fields  | |
loadSession :: Recorder (WithPriority Log) -> FilePath -> IO (Action IdeGhcSession) Source #
Given a root directory, return a Shake Action which setups an
 IdeGhcSession given a file.
 Some of the many things this does:
- Find the cradle for the file
 - Get the session options,
 - Get the GHC lib directory
 - Make sure the GHC compiletime and runtime versions match
 - Restart the Shake session
 
This is the key function which implements multi-component support. All components mapping to the same hie.yaml file are mapped to the same HscEnv which is updated as new components are discovered.
loadSessionWithOptions :: Recorder (WithPriority Log) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession) Source #
setInitialDynFlags :: Recorder (WithPriority Log) -> FilePath -> SessionLoadingOptions -> IO (Maybe LibDir) Source #
Sets unsafeGlobalDynFlags on using the hie-bios cradle and returns the GHC libdir
runWithDb :: Recorder (WithPriority Log) -> FilePath -> (WithHieDb -> IndexQueue -> IO ()) -> IO () Source #
Wraps withHieDb to provide a database connection for reading, and a HieWriterChan for
 writing. Actions are picked off one by one from the HieWriterChan and executed in serial
 by a worker thread using a dedicated database connection.
 This is done in order to serialize writes to the database, or else SQLite becomes unhappy
retryOnSqliteBusy :: (MonadIO m, MonadCatch m, RandomGen g) => Recorder (WithPriority Log) -> g -> m a -> m a Source #
Arguments
| :: (MonadIO m, MonadCatch m, RandomGen g, Exception e) | |
| => (e -> Maybe e) | only retry on exception if this predicate returns Just  | 
| -> Recorder (WithPriority Log) | |
| -> Int | maximum backoff delay in microseconds  | 
| -> Int | base backoff delay in microseconds  | 
| -> Int | maximum number of times to retry  | 
| -> g | random number generator  | 
| -> m a | action that may throw exception  | 
| -> m a | 
If the action throws exception that satisfies predicate then we sleep for
 a duration determined by the random exponential backoff formula,
 `uniformRandom(0, min (maxDelay, (baseDelay * 2) ^ retryAttempt))`, and try
 the action again for a maximum of maxRetryCount times.
 MonadIO, MonadCatch are used as constraints because there are a few
 HieDb functions that don't return IO values.
Constructors