never executed always true always false
1 {-# LANGUAGE GADTs #-}
2 {-# LANGUAGE RankNTypes #-}
3
4 module GHC.Driver.Pipeline.Phases (TPhase(..), PhaseHook(..)) where
5
6 import GHC.Prelude
7 import GHC.Driver.Pipeline.Monad
8 import GHC.Driver.Env.Types
9 import GHC.Driver.Session
10 import GHC.Driver.CmdLine
11 import GHC.Types.SourceFile
12 import GHC.Unit.Module.ModSummary
13 import GHC.Unit.Module.Status
14 import GHC.Tc.Types ( FrontendResult )
15 import GHC.Types.Error
16 import GHC.Driver.Errors.Types
17 import GHC.Fingerprint.Type
18 import GHC.Unit.Module.Location ( ModLocation )
19 import GHC.Unit.Module.Name ( ModuleName )
20 import GHC.Unit.Module.ModIface
21 import GHC.Linker.Types
22 import GHC.Driver.Phases
23
24 -- Typed Pipeline Phases
25 -- MP: TODO: We need to refine the arguments to each of these phases so recompilation
26 -- can be smarter. For example, rather than passing a whole HscEnv, just pass the options
27 -- which each phase depends on, then recompilation checking can decide to only rerun each
28 -- phase if the inputs have been modified.
29 data TPhase res where
30 T_Unlit :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
31 T_FileArgs :: HscEnv -> FilePath -> TPhase (DynFlags, [Warn])
32 T_Cpp :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
33 T_HsPp :: PipeEnv -> HscEnv -> FilePath -> FilePath -> TPhase FilePath
34 T_HscRecomp :: PipeEnv -> HscEnv -> FilePath -> HscSource -> TPhase (HscEnv, ModSummary, HscRecompStatus)
35 T_Hsc :: HscEnv -> ModSummary -> TPhase (FrontendResult, Messages GhcMessage)
36 T_HscPostTc :: HscEnv -> ModSummary
37 -> FrontendResult
38 -> Messages GhcMessage
39 -> Maybe Fingerprint
40 -> TPhase HscBackendAction
41 T_HscBackend :: PipeEnv -> HscEnv -> ModuleName -> HscSource -> ModLocation -> HscBackendAction -> TPhase ([FilePath], ModIface, Maybe Linkable, FilePath)
42 T_CmmCpp :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
43 T_Cmm :: PipeEnv -> HscEnv -> FilePath -> TPhase ([FilePath], FilePath)
44 T_Cc :: Phase -> PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
45 T_As :: Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> TPhase FilePath
46 T_LlvmOpt :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
47 T_LlvmLlc :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
48 T_LlvmMangle :: PipeEnv -> HscEnv -> FilePath -> TPhase FilePath
49 T_MergeForeign :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> [FilePath] -> TPhase FilePath
50
51 -- | A wrapper around the interpretation function for phases.
52 data PhaseHook = PhaseHook (forall a . TPhase a -> IO a)