Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Debugger.Session
Description
Initialise the GHC session for one or more home units.
This code is inspired of HLS's session initialisation. It would be great to extract common functions in the future.
Synopsis
- parseHomeUnitArguments :: GhcMonad m => FilePath -> FilePath -> [String] -> [String] -> DynFlags -> FilePath -> m (NonEmpty (DynFlags, [Target]))
- setupHomeUnitGraph :: GhcMonad m => [(DynFlags, [Target])] -> m ()
- data TargetDetails = TargetDetails {}
- data Target
- toGhcTarget :: TargetDetails -> Target
- data CacheDirs = CacheDirs {}
- getCacheDirs :: String -> [String] -> IO CacheDirs
- interactiveGhcDebuggerUnitId :: UnitId
- getInteractiveDebuggerDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDebuggerDynFlags :: GhcMonad m => DynFlags -> m ()
- setWorkingDirectory :: FilePath -> DynFlags -> DynFlags
- setCacheDirs :: CacheDirs -> DynFlags -> DynFlags
- setBytecodeBackend :: DynFlags -> DynFlags
- enableByteCodeGeneration :: DynFlags -> DynFlags
Documentation
parseHomeUnitArguments Source #
Arguments
:: GhcMonad m | |
=> FilePath | Main entry point function |
-> FilePath | Component root. Important for multi-package cabal projects. |
-> [String] | |
-> [String] | |
-> DynFlags | |
-> FilePath | root dir, see Note [Root Directory] |
-> m (NonEmpty (DynFlags, [Target])) |
Throws if package flags are unsatisfiable
data TargetDetails Source #
Constructors
TargetDetails | |
Fields
|
Instances
Eq TargetDetails Source # | |
Defined in GHC.Debugger.Session Methods (==) :: TargetDetails -> TargetDetails -> Bool # (/=) :: TargetDetails -> TargetDetails -> Bool # | |
Ord TargetDetails Source # | |
Defined in GHC.Debugger.Session Methods compare :: TargetDetails -> TargetDetails -> Ordering # (<) :: TargetDetails -> TargetDetails -> Bool # (<=) :: TargetDetails -> TargetDetails -> Bool # (>) :: TargetDetails -> TargetDetails -> Bool # (>=) :: TargetDetails -> TargetDetails -> Bool # max :: TargetDetails -> TargetDetails -> TargetDetails # min :: TargetDetails -> TargetDetails -> TargetDetails # |
Constructors
TargetModule ModuleName | |
TargetFile FilePath |
toGhcTarget :: TargetDetails -> Target Source #
Turn a TargetDetails
into a Target
.
Constructors
CacheDirs | |
Fields |
Debugger's Interactive Home Unit
getInteractiveDebuggerDynFlags :: GhcMonad m => m DynFlags Source #
setInteractiveDebuggerDynFlags :: GhcMonad m => DynFlags -> m () Source #
Set the interactive DynFlags
for the haskell-debugger session.
We manage a separate home unit for the interactive DynFlags
.
The invariant is that DynFlags
found in InteractiveContext
*must* be
the same DynFlags
as the ones found in interactiveGhcDebuggerUnitId
in
the HomeUnitEnv
This function upholds this invariant.
Always prefer this, over setInteractiveDynFlags
.
DynFlags modifications
enableByteCodeGeneration :: DynFlags -> DynFlags Source #
If the compiler supports `.gbc` files (>= 9.14.2), then persist these artefacts to disk.