Safe Haskell | None |
---|---|
Language | GHC2021 |
GHC.Driver.MakeAction
Synopsis
- data MakeAction = MakeAction !(RunMakeM a) !(MVar (Maybe a))
- data MakeEnv = MakeEnv {
- hsc_env :: !HscEnv
- compile_sem :: !AbstractSem
- withLogger :: forall a. Int -> ((Logger -> Logger) -> IO a) -> IO a
- env_messager :: !(Maybe Messager)
- diag_wrapper :: GhcMessage -> AnyGhcDiagnostic
- type RunMakeM a = ReaderT MakeEnv (MaybeT IO) a
- runAllPipelines :: WorkerLimit -> MakeEnv -> [MakeAction] -> IO ()
- runParPipelines :: WorkerLimit -> HscEnv -> (GhcMessage -> AnyGhcDiagnostic) -> Maybe Messager -> [MakeAction] -> IO ()
- runSeqPipelines :: HscEnv -> (GhcMessage -> AnyGhcDiagnostic) -> Maybe Messager -> [MakeAction] -> IO ()
- runPipelines :: WorkerLimit -> HscEnv -> (GhcMessage -> AnyGhcDiagnostic) -> Maybe Messager -> [MakeAction] -> IO ()
- data WorkerLimit
- mkWorkerLimit :: DynFlags -> IO WorkerLimit
- runWorkerLimit :: WorkerLimit -> (AbstractSem -> IO a) -> IO a
- withLoggerHsc :: Int -> MakeEnv -> (HscEnv -> IO a) -> IO a
- withParLog :: TVar LogQueueQueue -> Int -> ((Logger -> Logger) -> IO b) -> IO b
- withLocalTmpFS :: TmpFs -> (TmpFs -> IO a) -> IO a
- withLocalTmpFSMake :: MakeEnv -> (MakeEnv -> IO a) -> IO a
Documentation
data MakeAction Source #
Constructors
MakeAction !(RunMakeM a) !(MVar (Maybe a)) |
Environment used when compiling a module
Constructors
MakeEnv | |
Fields
|
Running the pipelines
runAllPipelines :: WorkerLimit -> MakeEnv -> [MakeAction] -> IO () Source #
Run the given actions and then wait for them all to finish.
Arguments
:: WorkerLimit | How to limit work parallelism |
-> HscEnv | The basic HscEnv which is augmented with specific info for each module |
-> (GhcMessage -> AnyGhcDiagnostic) | |
-> Maybe Messager | Optional custom messager to use to report progress |
-> [MakeAction] | The build plan for all the module nodes |
-> IO () |
Build and run a pipeline
runSeqPipelines :: HscEnv -> (GhcMessage -> AnyGhcDiagnostic) -> Maybe Messager -> [MakeAction] -> IO () Source #
runPipelines :: WorkerLimit -> HscEnv -> (GhcMessage -> AnyGhcDiagnostic) -> Maybe Messager -> [MakeAction] -> IO () Source #
Worker limit
data WorkerLimit Source #
This describes what we use to limit the number of jobs, either we limit it ourselves to a specific number or we have an external parallelism semaphore limit it for us.
Constructors
NumProcessorsLimit Int | |
JSemLimit SemaphoreName | Semaphore name to use |
Instances
Eq WorkerLimit Source # | |
Defined in GHC.Driver.MakeAction |
mkWorkerLimit :: DynFlags -> IO WorkerLimit Source #
runWorkerLimit :: WorkerLimit -> (AbstractSem -> IO a) -> IO a Source #
Utility
withParLog :: TVar LogQueueQueue -> Int -> ((Logger -> Logger) -> IO b) -> IO b Source #