{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
#include <ghcplatform.h>

{- Functions for providing the default interpretation of the 'TPhase' actions
-}
module GHC.Driver.Pipeline.Execute where

import GHC.Prelude
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Catch
import GHC.Driver.Hooks
import Control.Monad.Trans.Reader
import GHC.Driver.Pipeline.Monad
import GHC.Driver.Pipeline.Phases
import GHC.Driver.Env hiding (Hsc)
import GHC.Unit.Module.Location
import GHC.Driver.Phases
import GHC.Unit.Module.Name ( ModuleName )
import GHC.Unit.Types
import GHC.Types.SourceFile
import GHC.Unit.Module.Status
import GHC.Unit.Module.ModIface
import GHC.Linker.Types
import GHC.Driver.Backend
import GHC.Driver.Session
import GHC.Driver.CmdLine
import GHC.Unit.Module.ModSummary
import qualified GHC.LanguageExtensions as LangExt
import GHC.Types.SrcLoc
import GHC.Driver.Main
import GHC.Tc.Types
import GHC.Types.Error
import GHC.Driver.Errors.Types
import GHC.Fingerprint
import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Platform
import Data.List (intercalate, isInfixOf)
import GHC.Unit.Env
import GHC.SysTools.Info
import GHC.Utils.Error
import Data.Maybe
import GHC.CmmToLlvm.Mangler
import GHC.SysTools
import GHC.Utils.Panic.Plain
import System.Directory
import System.FilePath
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Unit.Info
import GHC.Unit.State
import GHC.Unit.Home
import GHC.Data.Maybe
import GHC.Iface.Make
import Data.Time
import GHC.Driver.Config.Parser
import GHC.Parser.Header
import GHC.Data.StringBuffer
import GHC.Types.SourceError
import GHC.Unit.Finder
import GHC.Runtime.Loader
import Data.IORef
import GHC.Types.Name.Env
import GHC.Platform.Ways
import GHC.Platform.ArchOS
import GHC.CmmToLlvm.Base ( llvmVersionList )
import {-# SOURCE #-} GHC.Driver.Pipeline (compileForeign, compileEmptyStub)
import GHC.Settings
import System.IO
import GHC.Linker.ExtraObj
import GHC.Linker.Dynamic
import Data.Version
import GHC.Utils.Panic
import GHC.Unit.Module.Env
import GHC.Driver.Env.KnotVars
import GHC.Driver.Config.Finder
import GHC.Rename.Names

newtype HookedUse a = HookedUse { forall a. HookedUse a -> (Hooks, PhaseHook) -> IO a
runHookedUse :: (Hooks, PhaseHook) -> IO a }
  deriving ((forall a b. (a -> b) -> HookedUse a -> HookedUse b)
-> (forall a b. a -> HookedUse b -> HookedUse a)
-> Functor HookedUse
forall a b. a -> HookedUse b -> HookedUse a
forall a b. (a -> b) -> HookedUse a -> HookedUse b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> HookedUse a -> HookedUse b
fmap :: forall a b. (a -> b) -> HookedUse a -> HookedUse b
$c<$ :: forall a b. a -> HookedUse b -> HookedUse a
<$ :: forall a b. a -> HookedUse b -> HookedUse a
Functor, Functor HookedUse
Functor HookedUse
-> (forall a. a -> HookedUse a)
-> (forall a b. HookedUse (a -> b) -> HookedUse a -> HookedUse b)
-> (forall a b c.
    (a -> b -> c) -> HookedUse a -> HookedUse b -> HookedUse c)
-> (forall a b. HookedUse a -> HookedUse b -> HookedUse b)
-> (forall a b. HookedUse a -> HookedUse b -> HookedUse a)
-> Applicative HookedUse
forall a. a -> HookedUse a
forall a b. HookedUse a -> HookedUse b -> HookedUse a
forall a b. HookedUse a -> HookedUse b -> HookedUse b
forall a b. HookedUse (a -> b) -> HookedUse a -> HookedUse b
forall a b c.
(a -> b -> c) -> HookedUse a -> HookedUse b -> HookedUse c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> HookedUse a
pure :: forall a. a -> HookedUse a
$c<*> :: forall a b. HookedUse (a -> b) -> HookedUse a -> HookedUse b
<*> :: forall a b. HookedUse (a -> b) -> HookedUse a -> HookedUse b
$cliftA2 :: forall a b c.
(a -> b -> c) -> HookedUse a -> HookedUse b -> HookedUse c
liftA2 :: forall a b c.
(a -> b -> c) -> HookedUse a -> HookedUse b -> HookedUse c
$c*> :: forall a b. HookedUse a -> HookedUse b -> HookedUse b
*> :: forall a b. HookedUse a -> HookedUse b -> HookedUse b
$c<* :: forall a b. HookedUse a -> HookedUse b -> HookedUse a
<* :: forall a b. HookedUse a -> HookedUse b -> HookedUse a
Applicative, Applicative HookedUse
Applicative HookedUse
-> (forall a b. HookedUse a -> (a -> HookedUse b) -> HookedUse b)
-> (forall a b. HookedUse a -> HookedUse b -> HookedUse b)
-> (forall a. a -> HookedUse a)
-> Monad HookedUse
forall a. a -> HookedUse a
forall a b. HookedUse a -> HookedUse b -> HookedUse b
forall a b. HookedUse a -> (a -> HookedUse b) -> HookedUse b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b. HookedUse a -> (a -> HookedUse b) -> HookedUse b
>>= :: forall a b. HookedUse a -> (a -> HookedUse b) -> HookedUse b
$c>> :: forall a b. HookedUse a -> HookedUse b -> HookedUse b
>> :: forall a b. HookedUse a -> HookedUse b -> HookedUse b
$creturn :: forall a. a -> HookedUse a
return :: forall a. a -> HookedUse a
Monad, Monad HookedUse
Monad HookedUse
-> (forall a. IO a -> HookedUse a) -> MonadIO HookedUse
forall a. IO a -> HookedUse a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
$cliftIO :: forall a. IO a -> HookedUse a
liftIO :: forall a. IO a -> HookedUse a
MonadIO, Monad HookedUse
Monad HookedUse
-> (forall e a. Exception e => e -> HookedUse a)
-> MonadThrow HookedUse
forall e a. Exception e => e -> HookedUse a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
$cthrowM :: forall e a. Exception e => e -> HookedUse a
throwM :: forall e a. Exception e => e -> HookedUse a
MonadThrow, MonadThrow HookedUse
MonadThrow HookedUse
-> (forall e a.
    Exception e =>
    HookedUse a -> (e -> HookedUse a) -> HookedUse a)
-> MonadCatch HookedUse
forall e a.
Exception e =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
$ccatch :: forall e a.
Exception e =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a
catch :: forall e a.
Exception e =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a
MonadCatch) via (ReaderT (Hooks, PhaseHook) IO)

instance MonadUse TPhase HookedUse where
  use :: forall a. TPhase a -> HookedUse a
use TPhase a
fa = ((Hooks, PhaseHook) -> IO a) -> HookedUse a
forall a. ((Hooks, PhaseHook) -> IO a) -> HookedUse a
HookedUse (((Hooks, PhaseHook) -> IO a) -> HookedUse a)
-> ((Hooks, PhaseHook) -> IO a) -> HookedUse a
forall a b. (a -> b) -> a -> b
$ \(Hooks
hooks, (PhaseHook forall a. TPhase a -> IO a
k)) ->
    case Hooks -> Maybe PhaseHook
runPhaseHook Hooks
hooks of
      Maybe PhaseHook
Nothing -> TPhase a -> IO a
forall a. TPhase a -> IO a
k TPhase a
fa
      Just (PhaseHook forall a. TPhase a -> IO a
h) -> TPhase a -> IO a
forall a. TPhase a -> IO a
h TPhase a
fa

-- | The default mechanism to run a pipeline, see Note [The Pipeline Monad]
runPipeline :: Hooks -> HookedUse a -> IO a
runPipeline :: forall a. Hooks -> HookedUse a -> IO a
runPipeline Hooks
hooks HookedUse a
pipeline = HookedUse a -> (Hooks, PhaseHook) -> IO a
forall a. HookedUse a -> (Hooks, PhaseHook) -> IO a
runHookedUse HookedUse a
pipeline (Hooks
hooks, (forall a. TPhase a -> IO a) -> PhaseHook
PhaseHook TPhase a -> IO a
forall a. TPhase a -> IO a
runPhase)

-- | Default interpretation of each phase, in terms of IO.
runPhase :: TPhase out -> IO out
runPhase :: forall a. TPhase a -> IO a
runPhase (T_Unlit PipeEnv
pipe_env HscEnv
hsc_env String
inp_path) = do
  String
out_path <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew (HscSource -> Phase
Cpp HscSource
HsSrcFile) PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
  HscEnv -> String -> String -> IO String
runUnlitPhase HscEnv
hsc_env String
inp_path String
out_path
runPhase (T_FileArgs HscEnv
hsc_env String
inp_path) = HscEnv -> String -> IO (DynFlags, Messages PsMessage, [Warn])
getFileArgs HscEnv
hsc_env String
inp_path
runPhase (T_Cpp PipeEnv
pipe_env HscEnv
hsc_env String
inp_path) = do
  String
out_path <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew (HscSource -> Phase
HsPp HscSource
HsSrcFile) PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
  HscEnv -> String -> String -> IO String
runCppPhase HscEnv
hsc_env String
inp_path String
out_path
runPhase (T_HsPp PipeEnv
pipe_env HscEnv
hsc_env String
origin_path String
inp_path) = do
  String
out_path <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew (HscSource -> Phase
Hsc HscSource
HsSrcFile) PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
  HscEnv -> String -> String -> String -> IO String
runHsPpPhase HscEnv
hsc_env String
origin_path String
inp_path String
out_path
runPhase (T_HscRecomp PipeEnv
pipe_env HscEnv
hsc_env String
fp HscSource
hsc_src) = do
  PipeEnv
-> HscEnv
-> String
-> HscSource
-> IO (HscEnv, ModSummary, HscRecompStatus)
runHscPhase PipeEnv
pipe_env HscEnv
hsc_env String
fp HscSource
hsc_src
runPhase (T_Hsc HscEnv
hsc_env ModSummary
mod_sum) = HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage)
runHscTcPhase HscEnv
hsc_env ModSummary
mod_sum
runPhase (T_HscPostTc HscEnv
hsc_env ModSummary
ms FrontendResult
fer Messages GhcMessage
m Maybe Fingerprint
mfi) =
  HscEnv
-> ModSummary
-> FrontendResult
-> Messages GhcMessage
-> Maybe Fingerprint
-> IO HscBackendAction
runHscPostTcPhase HscEnv
hsc_env ModSummary
ms FrontendResult
fer Messages GhcMessage
m Maybe Fingerprint
mfi
runPhase (T_HscBackend PipeEnv
pipe_env HscEnv
hsc_env ModuleName
mod_name HscSource
hsc_src ModLocation
location HscBackendAction
x) = do
  PipeEnv
-> HscEnv
-> ModuleName
-> HscSource
-> ModLocation
-> HscBackendAction
-> IO ([String], ModIface, Maybe Linkable, String)
runHscBackendPhase PipeEnv
pipe_env HscEnv
hsc_env ModuleName
mod_name HscSource
hsc_src ModLocation
location HscBackendAction
x
runPhase (T_CmmCpp PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) = do
  String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
Cmm PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
  Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> String
-> String
-> IO ()
doCpp (HscEnv -> Logger
hsc_logger HscEnv
hsc_env)
        (HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env)
        (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
        (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
        Bool
False{-not raw-}
        String
input_fn String
output_fn
  out -> IO out
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return out
String
output_fn
runPhase (T_Cmm PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) = do
  let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
  let next_phase :: Phase
next_phase = HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
HsSrcFile (DynFlags -> Backend
backend DynFlags
dflags)
  String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
  Maybe String
mstub <- HscEnv -> String -> String -> String -> IO (Maybe String)
hscCompileCmmFile HscEnv
hsc_env (PipeEnv -> String
src_filename PipeEnv
pipe_env) String
input_fn String
output_fn
  Maybe String
stub_o <- (String -> IO String) -> Maybe String -> IO (Maybe String)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM (HscEnv -> String -> IO String
compileStub HscEnv
hsc_env) Maybe String
mstub
  let foreign_os :: [String]
foreign_os = Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
stub_o
  out -> IO out
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
foreign_os, String
output_fn)

runPhase (T_Cc Phase
phase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) = Phase -> PipeEnv -> HscEnv -> String -> IO String
runCcPhase Phase
phase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn
runPhase (T_As Bool
cpp PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
input_fn) = do
  Bool
-> PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runAsPhase Bool
cpp PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
input_fn
runPhase (T_LlvmOpt PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) =
  PipeEnv -> HscEnv -> String -> IO String
runLlvmOptPhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn
runPhase (T_LlvmLlc PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) =
  PipeEnv -> HscEnv -> String -> IO String
runLlvmLlcPhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn
runPhase (T_LlvmMangle PipeEnv
pipe_env HscEnv
hsc_env String
input_fn) =
  PipeEnv -> HscEnv -> String -> IO String
runLlvmManglePhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn
runPhase (T_MergeForeign PipeEnv
pipe_env HscEnv
hsc_env String
input_fn [String]
fos) =
  PipeEnv -> HscEnv -> String -> [String] -> IO String
runMergeForeign PipeEnv
pipe_env HscEnv
hsc_env String
input_fn [String]
fos

runLlvmManglePhase :: PipeEnv -> HscEnv -> FilePath -> IO [Char]
runLlvmManglePhase :: PipeEnv -> HscEnv -> String -> IO String
runLlvmManglePhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn = do
      let next_phase :: Phase
next_phase = Bool -> Phase
As Bool
False
      String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
      let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
      Platform -> String -> String -> IO ()
llvmFixupAsm (DynFlags -> Platform
targetPlatform DynFlags
dflags) String
input_fn String
output_fn
      String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn

runMergeForeign :: PipeEnv -> HscEnv -> FilePath -> [FilePath] -> IO FilePath
runMergeForeign :: PipeEnv -> HscEnv -> String -> [String] -> IO String
runMergeForeign PipeEnv
_pipe_env HscEnv
hsc_env String
input_fn [String]
foreign_os = do
     if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
foreign_os
       then String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
input_fn
       else do
         -- Work around a binutil < 2.31 bug where you can't merge objects if the output file
         -- is one of the inputs
         String
new_o <- Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName (HscEnv -> Logger
hsc_logger HscEnv
hsc_env)
                              (HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env)
                              (DynFlags -> TempDir
tmpDir (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env))
                              TempFileLifetime
TFL_CurrentModule String
"o"
         String -> String -> IO ()
copyFile String
input_fn String
new_o
         HscEnv -> [String] -> String -> IO ()
joinObjectFiles HscEnv
hsc_env (String
new_o String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
foreign_os) String
input_fn
         String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
input_fn

runLlvmLlcPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
runLlvmLlcPhase :: PipeEnv -> HscEnv -> String -> IO String
runLlvmLlcPhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn = do
    -- Note [Clamping of llc optimizations]
    -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    -- See #13724
    --
    -- we clamp the llc optimization between [1,2]. This is because passing -O0
    -- to llc 3.9 or llc 4.0, the naive register allocator can fail with
    --
    --   Error while trying to spill R1 from class GPR: Cannot scavenge register
    --   without an emergency spill slot!
    --
    -- Observed at least with target 'arm-unknown-linux-gnueabihf'.
    --
    --
    -- With LLVM4, llc -O3 crashes when ghc-stage1 tries to compile
    --   rts/HeapStackCheck.cmm
    --
    -- llc -O3 '-mtriple=arm-unknown-linux-gnueabihf' -enable-tbaa /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc -o /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_7.lm_s
    -- 0  llc                      0x0000000102ae63e8 llvm::sys::PrintStackTrace(llvm::raw_ostream&) + 40
    -- 1  llc                      0x0000000102ae69a6 SignalHandler(int) + 358
    -- 2  libsystem_platform.dylib 0x00007fffc23f4b3a _sigtramp + 26
    -- 3  libsystem_c.dylib        0x00007fffc226498b __vfprintf + 17876
    -- 4  llc                      0x00000001029d5123 llvm::SelectionDAGISel::LowerArguments(llvm::Function const&) + 5699
    -- 5  llc                      0x0000000102a21a35 llvm::SelectionDAGISel::SelectAllBasicBlocks(llvm::Function const&) + 3381
    -- 6  llc                      0x0000000102a202b1 llvm::SelectionDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 1457
    -- 7  llc                      0x0000000101bdc474 (anonymous namespace)::ARMDAGToDAGISel::runOnMachineFunction(llvm::MachineFunction&) + 20
    -- 8  llc                      0x00000001025573a6 llvm::MachineFunctionPass::runOnFunction(llvm::Function&) + 134
    -- 9  llc                      0x000000010274fb12 llvm::FPPassManager::runOnFunction(llvm::Function&) + 498
    -- 10 llc                      0x000000010274fd23 llvm::FPPassManager::runOnModule(llvm::Module&) + 67
    -- 11 llc                      0x00000001027501b8 llvm::legacy::PassManagerImpl::run(llvm::Module&) + 920
    -- 12 llc                      0x000000010195f075 compileModule(char**, llvm::LLVMContext&) + 12133
    -- 13 llc                      0x000000010195bf0b main + 491
    -- 14 libdyld.dylib            0x00007fffc21e5235 start + 1
    -- Stack dump:
    -- 0.  Program arguments: llc -O3 -mtriple=arm-unknown-linux-gnueabihf -enable-tbaa /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc -o /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_7.lm_s
    -- 1.  Running pass 'Function Pass Manager' on module '/var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc33674_0/ghc_6.bc'.
    -- 2.  Running pass 'ARM Instruction Selection' on function '@"stg_gc_f1$def"'
    --
    -- Observed at least with -mtriple=arm-unknown-linux-gnueabihf -enable-tbaa
    --
    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
        logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
        llvmOpts :: String
llvmOpts = case DynFlags -> Int
llvmOptLevel DynFlags
dflags of
          Int
0 -> String
"-O1" -- required to get the non-naive reg allocator. Passing -regalloc=greedy is not sufficient.
          Int
1 -> String
"-O1"
          Int
_ -> String
"-O2"

        defaultOptions :: [Option]
defaultOptions = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option ([String] -> [Option])
-> (([String], [String]) -> [String])
-> ([String], [String])
-> [Option]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [String]) -> [String] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [String]
words ([String] -> [String])
-> (([String], [String]) -> [String])
-> ([String], [String])
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String], [String]) -> [String]
forall a b. (a, b) -> b
snd
                         (([String], [String]) -> [Option])
-> ([String], [String]) -> [Option]
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> ([String], [String])
forall a b. [(a, b)] -> ([a], [b])
unzip (DynFlags -> [(String, String)]
llvmOptions DynFlags
dflags)
        optFlag :: [Option]
optFlag = if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (DynFlags -> (DynFlags -> [String]) -> [String]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [String]
opt_lc)
                  then (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option ([String] -> [Option]) -> [String] -> [Option]
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
llvmOpts
                  else []

    Phase
next_phase <- if -- hidden debugging flag '-dno-llvm-mangler' to skip mangling
                     | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_NoLlvmMangler DynFlags
dflags -> Phase -> IO Phase
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Phase
As Bool
False)
                     | Bool
otherwise -> Phase -> IO Phase
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Phase
LlvmMangle

    String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing

    Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runLlvmLlc Logger
logger DynFlags
dflags
                (  [Option]
optFlag
                [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
defaultOptions
                [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> String -> Option
GHC.SysTools.FileOption String
"" String
input_fn
                   , String -> Option
GHC.SysTools.Option String
"-o"
                   , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn
                   ]
                )

    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn

runLlvmOptPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
runLlvmOptPhase :: PipeEnv -> HscEnv -> String -> IO String
runLlvmOptPhase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn = do
    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
        logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
    let -- we always (unless -optlo specified) run Opt since we rely on it to
        -- fix up some pretty big deficiencies in the code we generate
        optIdx :: Int
optIdx = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
2 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DynFlags -> Int
llvmOptLevel DynFlags
dflags  -- ensure we're in [0,2]
        llvmOpts :: String
llvmOpts = case Int -> [(Int, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
optIdx ([(Int, String)] -> Maybe String)
-> [(Int, String)] -> Maybe String
forall a b. (a -> b) -> a -> b
$ LlvmConfig -> [(Int, String)]
llvmPasses (LlvmConfig -> [(Int, String)]) -> LlvmConfig -> [(Int, String)]
forall a b. (a -> b) -> a -> b
$ DynFlags -> LlvmConfig
llvmConfig DynFlags
dflags of
                    Just String
passes -> String
passes
                    Maybe String
Nothing -> String -> String
forall a. String -> a
panic (String
"runPhase LlvmOpt: llvm-passes file "
                                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"is missing passes for level "
                                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
optIdx)
        defaultOptions :: [Option]
defaultOptions = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option ([String] -> [Option])
-> (([String], [String]) -> [String])
-> ([String], [String])
-> [Option]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String])
-> (([String], [String]) -> [[String]])
-> ([String], [String])
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [String]) -> [String] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> [String]
words ([String] -> [[String]])
-> (([String], [String]) -> [String])
-> ([String], [String])
-> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String], [String]) -> [String]
forall a b. (a, b) -> a
fst
                         (([String], [String]) -> [Option])
-> ([String], [String]) -> [Option]
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> ([String], [String])
forall a b. [(a, b)] -> ([a], [b])
unzip (DynFlags -> [(String, String)]
llvmOptions DynFlags
dflags)

        -- don't specify anything if user has specified commands. We do this
        -- for opt but not llc since opt is very specifically for optimisation
        -- passes only, so if the user is passing us extra options we assume
        -- they know what they are doing and don't get in the way.
        optFlag :: [Option]
optFlag = if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (DynFlags -> (DynFlags -> [String]) -> [String]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [String]
opt_lo)
                  then (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option ([String] -> [Option]) -> [String] -> [Option]
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
llvmOpts
                  else []

    String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
LlvmLlc PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing

    Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runLlvmOpt Logger
logger DynFlags
dflags
               (   [Option]
optFlag
                [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
defaultOptions [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++
                [ String -> String -> Option
GHC.SysTools.FileOption String
"" String
input_fn
                , String -> Option
GHC.SysTools.Option String
"-o"
                , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn]
                )

    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn


runAsPhase :: Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
runAsPhase :: Bool
-> PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runAsPhase Bool
with_cpp PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
input_fn = do
        let dflags :: DynFlags
dflags     = HscEnv -> DynFlags
hsc_dflags   HscEnv
hsc_env
        let logger :: Logger
logger     = HscEnv -> Logger
hsc_logger   HscEnv
hsc_env
        let unit_env :: UnitEnv
unit_env   = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
        let platform :: Platform
platform   = UnitEnv -> Platform
ue_platform UnitEnv
unit_env

        -- LLVM from version 3.0 onwards doesn't support the OS X system
        -- assembler, so we use clang as the assembler instead. (#5636)
        let (Logger -> DynFlags -> [Option] -> IO ()
as_prog, IO CompilerInfo
get_asm_info) | DynFlags -> Backend
backend DynFlags
dflags Backend -> Backend -> Bool
forall a. Eq a => a -> a -> Bool
== Backend
LLVM
                    , Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin
                    = (Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runClang, CompilerInfo -> IO CompilerInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CompilerInfo
Clang)
                    | Bool
otherwise
                    = (Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runAs, Logger -> DynFlags -> IO CompilerInfo
getAssemblerInfo Logger
logger DynFlags
dflags)

        CompilerInfo
asmInfo <- IO CompilerInfo
get_asm_info

        let cmdline_include_paths :: IncludeSpecs
cmdline_include_paths = DynFlags -> IncludeSpecs
includePaths DynFlags
dflags
        let pic_c_flags :: [String]
pic_c_flags = DynFlags -> [String]
picCCOpts DynFlags
dflags

        String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
StopLn PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location

        -- we create directories for the object file, because it
        -- might be a hierarchical module.
        Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
output_fn)

        let global_includes :: [Option]
global_includes = [ String -> Option
GHC.SysTools.Option (String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p)
                              | String
p <- IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
cmdline_include_paths ]
        let local_includes :: [Option]
local_includes = [ String -> Option
GHC.SysTools.Option (String
"-iquote" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p)
                             | String
p <- IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
                                IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
cmdline_include_paths]
        let runAssembler :: String -> String -> IO ()
runAssembler String
inputFilename String
outputFilename
              = String -> (String -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadIO m =>
String -> (String -> m a) -> m a
withAtomicRename String
outputFilename ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
temp_outputFilename ->
                    Logger -> DynFlags -> [Option] -> IO ()
as_prog
                       Logger
logger DynFlags
dflags
                       ([Option]
local_includes [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
global_includes
                       -- See Note [-fPIC for assembler]
                       [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
pic_c_flags
                       -- See Note [Produce big objects on Windows]
                       [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
GHC.SysTools.Option String
"-Wa,-mbig-obj"
                          | Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags) OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
                          , Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Platform -> Bool
target32Bit (DynFlags -> Platform
targetPlatform DynFlags
dflags)
                          ]

                       [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (if (CompilerInfo -> Bool) -> [CompilerInfo] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (CompilerInfo
asmInfo CompilerInfo -> CompilerInfo -> Bool
forall a. Eq a => a -> a -> Bool
==) [CompilerInfo
Clang, CompilerInfo
AppleClang, CompilerInfo
AppleClang51]
                            then [String -> Option
GHC.SysTools.Option String
"-Qunused-arguments"]
                            else [])
                       [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
GHC.SysTools.Option String
"-x"
                          , if Bool
with_cpp
                              then String -> Option
GHC.SysTools.Option String
"assembler-with-cpp"
                              else String -> Option
GHC.SysTools.Option String
"assembler"
                          , String -> Option
GHC.SysTools.Option String
"-c"
                          , String -> String -> Option
GHC.SysTools.FileOption String
"" String
inputFilename
                          , String -> Option
GHC.SysTools.Option String
"-o"
                          , String -> String -> Option
GHC.SysTools.FileOption String
"" String
temp_outputFilename
                          ])

        Logger -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger Int
4 (String -> SDoc
text String
"Running the assembler")
        String -> String -> IO ()
runAssembler String
input_fn String
output_fn

        String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn


runCcPhase :: Phase -> PipeEnv -> HscEnv -> FilePath -> IO FilePath
runCcPhase :: Phase -> PipeEnv -> HscEnv -> String -> IO String
runCcPhase Phase
cc_phase PipeEnv
pipe_env HscEnv
hsc_env String
input_fn = do
  let dflags :: DynFlags
dflags    = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
  let logger :: Logger
logger    = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
  let unit_env :: UnitEnv
unit_env  = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
  let home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
  let tmpfs :: TmpFs
tmpfs     = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
  let platform :: Platform
platform  = UnitEnv -> Platform
ue_platform UnitEnv
unit_env
  let hcc :: Bool
hcc       = Phase
cc_phase Phase -> Phase -> Bool
`eqPhase` Phase
HCc

  let cmdline_include_paths :: IncludeSpecs
cmdline_include_paths =  DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (DynFlags -> IncludeSpecs
includePaths DynFlags
dflags)

  -- HC files have the dependent packages stamped into them
  [UnitId]
pkgs <- if Bool
hcc then String -> IO [UnitId]
getHCFilePackages String
input_fn else [UnitId] -> IO [UnitId]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []

  -- add package include paths even if we're just compiling .c
  -- files; this is the Value Add(TM) that using ghc instead of
  -- gcc gives you :)
  [UnitInfo]
ps <- MaybeErr UnitErr [UnitInfo] -> IO [UnitInfo]
forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr (UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' UnitEnv
unit_env [UnitId]
pkgs)
  let pkg_include_dirs :: [String]
pkg_include_dirs     = [UnitInfo] -> [String]
collectIncludeDirs [UnitInfo]
ps
  let include_paths_global :: [String]
include_paths_global = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
        (IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_include_dirs)
  let include_paths_quote :: [String]
include_paths_quote = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-iquote" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
        (IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
         IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
cmdline_include_paths)
  let include_paths :: [String]
include_paths = [String]
include_paths_quote [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
include_paths_global

  -- pass -D or -optP to preprocessor when compiling foreign C files
  -- (#16737). Doing it in this way is simpler and also enable the C
  -- compiler to perform preprocessing and parsing in a single pass,
  -- but it may introduce inconsistency if a different pgm_P is specified.
  let opts :: [String]
opts = DynFlags -> (DynFlags -> [String]) -> [String]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [String]
opt_P
      aug_imports :: [String]
aug_imports = DynFlags -> [String] -> [String]
augmentImports DynFlags
dflags [String]
opts

      more_preprocessor_opts :: [String]
more_preprocessor_opts = [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [String
"-Xpreprocessor", String
i]
        | Bool -> Bool
not Bool
hcc
        , String
i <- [String]
aug_imports
        ]

  let gcc_extra_viac_flags :: [String]
gcc_extra_viac_flags = DynFlags -> [String]
extraGccViaCFlags DynFlags
dflags
  let pic_c_flags :: [String]
pic_c_flags = DynFlags -> [String]
picCCOpts DynFlags
dflags

  let verbFlags :: [String]
verbFlags = DynFlags -> [String]
getVerbFlags DynFlags
dflags

  -- cc-options are not passed when compiling .hc files.  Our
  -- hc code doesn't not #include any header files anyway, so these
  -- options aren't necessary.
  let pkg_extra_cc_opts :: [String]
pkg_extra_cc_opts
          | Bool
hcc       = []
          | Bool
otherwise = [UnitInfo] -> [String]
collectExtraCcOpts [UnitInfo]
ps

  let framework_paths :: [String]
framework_paths
          | Platform -> Bool
platformUsesFrameworks Platform
platform
          = let pkgFrameworkPaths :: [String]
pkgFrameworkPaths     = [UnitInfo] -> [String]
collectFrameworksDirs [UnitInfo]
ps
                cmdlineFrameworkPaths :: [String]
cmdlineFrameworkPaths = DynFlags -> [String]
frameworkPaths DynFlags
dflags
            in (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"-F"String -> String -> String
forall a. [a] -> [a] -> [a]
++) ([String]
cmdlineFrameworkPaths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkgFrameworkPaths)
          | Bool
otherwise
          = []

  let cc_opt :: [String]
cc_opt | DynFlags -> Int
llvmOptLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 = [ String
"-O2" ]
             | DynFlags -> Int
llvmOptLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 = [ String
"-O" ]
             | Bool
otherwise            = []

  -- Decide next phase
  let next_phase :: Phase
next_phase = Bool -> Phase
As Bool
False
  String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing

  let
    more_hcc_opts :: [String]
more_hcc_opts =
          -- on x86 the floating point regs have greater precision
          -- than a double, which leads to unpredictable results.
          -- By default, we turn this off with -ffloat-store unless
          -- the user specified -fexcess-precision.
          (if Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchX86 Bool -> Bool -> Bool
&&
              Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExcessPrecision DynFlags
dflags)
                  then [ String
"-ffloat-store" ]
                  else []) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++

          -- gcc's -fstrict-aliasing allows two accesses to memory
          -- to be considered non-aliasing if they have different types.
          -- This interacts badly with the C code we generate, which is
          -- very weakly typed, being derived from C--.
          [String
"-fno-strict-aliasing"]

  String
ghcVersionH <- DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env

  Maybe ForeignSrcLang
-> Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runCc (Phase -> Maybe ForeignSrcLang
phaseForeignLanguage Phase
cc_phase) Logger
logger TmpFs
tmpfs DynFlags
dflags (
                  [ String -> String -> Option
GHC.SysTools.FileOption String
"" String
input_fn
                  , String -> Option
GHC.SysTools.Option String
"-o"
                  , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn
                  ]
                 [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option (
                    [String]
pic_c_flags

          -- Stub files generated for foreign exports references the runIO_closure
          -- and runNonIO_closure symbols, which are defined in the base package.
          -- These symbols are imported into the stub.c file via RtsAPI.h, and the
          -- way we do the import depends on whether we're currently compiling
          -- the base package or not.
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32 Bool -> Bool -> Bool
&&
                        HomeUnit -> UnitId -> Bool
forall u. GenHomeUnit u -> UnitId -> Bool
isHomeUnitId HomeUnit
home_unit UnitId
baseUnitId
                          then [ String
"-DCOMPILING_BASE_PACKAGE" ]
                          else [])

                 -- GCC 4.6+ doesn't like -Wimplicit when compiling C++.
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (if (Phase
cc_phase Phase -> Phase -> Bool
forall a. Eq a => a -> a -> Bool
/= Phase
Ccxx Bool -> Bool -> Bool
&& Phase
cc_phase Phase -> Phase -> Bool
forall a. Eq a => a -> a -> Bool
/= Phase
Cobjcxx)
                       then [String
"-Wimplicit"]
                       else [])

                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (if Bool
hcc
                       then [String]
gcc_extra_viac_flags [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
more_hcc_opts
                       else [])
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
verbFlags
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"-S" ]
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
cc_opt
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"-include", String
ghcVersionH ]
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
framework_paths
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
include_paths
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
more_preprocessor_opts
                 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_extra_cc_opts
                 ))

  String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn

-- This is where all object files get written from, for hs-boot and hsig files as well.
runHscBackendPhase :: PipeEnv
                   -> HscEnv
                   -> ModuleName
                   -> HscSource
                   -> ModLocation
                   -> HscBackendAction
                   -> IO ([FilePath], ModIface, Maybe Linkable, FilePath)
runHscBackendPhase :: PipeEnv
-> HscEnv
-> ModuleName
-> HscSource
-> ModLocation
-> HscBackendAction
-> IO ([String], ModIface, Maybe Linkable, String)
runHscBackendPhase PipeEnv
pipe_env HscEnv
hsc_env ModuleName
mod_name HscSource
src_flavour ModLocation
location HscBackendAction
result = do
  let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
      logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
      o_file :: String
o_file = if DynFlags -> Bool
dynamicNow DynFlags
dflags then ModLocation -> String
ml_dyn_obj_file ModLocation
location else ModLocation -> String
ml_obj_file ModLocation
location -- The real object file
      next_phase :: Phase
next_phase = HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
src_flavour (DynFlags -> Backend
backend DynFlags
dflags)
  case HscBackendAction
result of
      HscUpdate ModIface
iface ->
          do
             case HscSource
src_flavour of
               HscSource
HsigFile -> do
                 -- We need to create a REAL but empty .o file
                 -- because we are going to attempt to put it in a library
                 let input_fn :: String
input_fn = String -> Maybe String -> String
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"runPhase" (ModLocation -> Maybe String
ml_hs_file ModLocation
location)
                     basename :: String
basename = String -> String
dropExtension String
input_fn
                 DynFlags -> HscEnv -> String -> ModLocation -> ModuleName -> IO ()
compileEmptyStub DynFlags
dflags HscEnv
hsc_env String
basename ModLocation
location ModuleName
mod_name

               -- In the case of hs-boot files, generate a dummy .o-boot
               -- stamp file for the benefit of Make
               HscSource
HsBootFile -> Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
o_file
               HscSource
HsSrcFile -> String -> IO ()
forall a. String -> a
panic String
"HscUpdate not relevant for HscSrcFile"

             ([String], ModIface, Maybe Linkable, String)
-> IO ([String], ModIface, Maybe Linkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], ModIface
iface, Maybe Linkable
forall a. Maybe a
Nothing, String
o_file)
      HscRecomp { hscs_guts :: HscBackendAction -> CgGuts
hscs_guts = CgGuts
cgguts,
                  hscs_mod_location :: HscBackendAction -> ModLocation
hscs_mod_location = ModLocation
mod_location,
                  hscs_partial_iface :: HscBackendAction -> PartialModIface
hscs_partial_iface = PartialModIface
partial_iface,
                  hscs_old_iface_hash :: HscBackendAction -> Maybe Fingerprint
hscs_old_iface_hash = Maybe Fingerprint
mb_old_iface_hash
                }
        -> case DynFlags -> Backend
backend DynFlags
dflags of
          Backend
NoBackend -> String -> IO ([String], ModIface, Maybe Linkable, String)
forall a. String -> a
panic String
"HscRecomp not relevant for NoBackend"
          Backend
Interpreter -> do
              -- In interpreted mode the regular codeGen backend is not run so we
              -- generate a interface without codeGen info.
              ModIface
final_iface <- HscEnv
-> PartialModIface
-> Maybe StgCgInfos
-> Maybe CmmCgInfos
-> IO ModIface
mkFullIface HscEnv
hsc_env PartialModIface
partial_iface Maybe StgCgInfos
forall a. Maybe a
Nothing Maybe CmmCgInfos
forall a. Maybe a
Nothing
              Logger
-> DynFlags
-> Bool
-> ModIface
-> Maybe Fingerprint
-> ModLocation
-> IO ()
hscMaybeWriteIface Logger
logger DynFlags
dflags Bool
True ModIface
final_iface Maybe Fingerprint
mb_old_iface_hash ModLocation
location

              (Maybe String
hasStub, CompiledByteCode
comp_bc, [SptEntry]
spt_entries) <- HscEnv
-> CgGuts
-> ModLocation
-> IO (Maybe String, CompiledByteCode, [SptEntry])
hscInteractive HscEnv
hsc_env CgGuts
cgguts ModLocation
mod_location

              [Unlinked]
stub_o <- case Maybe String
hasStub of
                        Maybe String
Nothing -> [Unlinked] -> IO [Unlinked]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
                        Just String
stub_c -> do
                            String
stub_o <- HscEnv -> String -> IO String
compileStub HscEnv
hsc_env String
stub_c
                            [Unlinked] -> IO [Unlinked]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String -> Unlinked
DotO String
stub_o]

              let hs_unlinked :: [Unlinked]
hs_unlinked = [CompiledByteCode -> [SptEntry] -> Unlinked
BCOs CompiledByteCode
comp_bc [SptEntry]
spt_entries]
              UTCTime
unlinked_time <- IO UTCTime
getCurrentTime
              let !linkable :: Linkable
linkable = UTCTime -> Module -> [Unlinked] -> Linkable
LM UTCTime
unlinked_time (HomeUnit -> ModuleName -> Module
mkHomeModule (HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env) ModuleName
mod_name)
                             ([Unlinked]
hs_unlinked [Unlinked] -> [Unlinked] -> [Unlinked]
forall a. [a] -> [a] -> [a]
++ [Unlinked]
stub_o)
              ([String], ModIface, Maybe Linkable, String)
-> IO ([String], ModIface, Maybe Linkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], ModIface
final_iface, Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
linkable, String -> String
forall a. String -> a
panic String
"interpreter")
          Backend
_ -> do
              String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env (ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
              (String
outputFilename, Maybe String
mStub, [(ForeignSrcLang, String)]
foreign_files, Maybe StgCgInfos
mb_stg_infos, Maybe CmmCgInfos
mb_cg_infos) <-
                HscEnv
-> CgGuts
-> ModLocation
-> String
-> IO
     (String, Maybe String, [(ForeignSrcLang, String)],
      Maybe StgCgInfos, Maybe CmmCgInfos)
hscGenHardCode HscEnv
hsc_env CgGuts
cgguts ModLocation
mod_location String
output_fn
              ModIface
final_iface <- HscEnv
-> PartialModIface
-> Maybe StgCgInfos
-> Maybe CmmCgInfos
-> IO ModIface
mkFullIface HscEnv
hsc_env PartialModIface
partial_iface Maybe StgCgInfos
mb_stg_infos Maybe CmmCgInfos
mb_cg_infos

              -- See Note [Writing interface files]
              Logger
-> DynFlags
-> Bool
-> ModIface
-> Maybe Fingerprint
-> ModLocation
-> IO ()
hscMaybeWriteIface Logger
logger DynFlags
dflags Bool
False ModIface
final_iface Maybe Fingerprint
mb_old_iface_hash ModLocation
mod_location

              Maybe String
stub_o <- (String -> IO String) -> Maybe String -> IO (Maybe String)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM (HscEnv -> String -> IO String
compileStub HscEnv
hsc_env) Maybe String
mStub
              [String]
foreign_os <-
                ((ForeignSrcLang, String) -> IO String)
-> [(ForeignSrcLang, String)] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignSrcLang -> String -> IO String)
-> (ForeignSrcLang, String) -> IO String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (HscEnv -> ForeignSrcLang -> String -> IO String
compileForeign HscEnv
hsc_env)) [(ForeignSrcLang, String)]
foreign_files
              let fos :: [String]
fos = ([String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
stub_o [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
foreign_os)

              -- This is awkward, no linkable is produced here because we still
              -- have some way to do before the object file is produced
              -- In future we can split up the driver logic more so that this function
              -- is in TPipeline and in this branch we can invoke the rest of the backend phase.
              ([String], ModIface, Maybe Linkable, String)
-> IO ([String], ModIface, Maybe Linkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
fos, ModIface
final_iface, Maybe Linkable
forall a. Maybe a
Nothing, String
outputFilename)


runUnlitPhase :: HscEnv -> FilePath -> FilePath -> IO FilePath
runUnlitPhase :: HscEnv -> String -> String -> IO String
runUnlitPhase HscEnv
hsc_env String
input_fn String
output_fn = do
    let
       -- escape the characters \, ", and ', but don't try to escape
       -- Unicode or anything else (so we don't use Util.charToC
       -- here).  If we get this wrong, then in
       -- GHC.HsToCore.Coverage.isGoodTickSrcSpan where we check that the filename in
       -- a SrcLoc is the same as the source filenaame, the two will
       -- look bogusly different. See test:
       -- libraries/hpc/tests/function/subdir/tough2.hs
       escape :: String -> String
escape (Char
'\\':String
cs) = Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escape String
cs
       escape (Char
'\"':String
cs) = Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'\"'Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escape String
cs
       escape (Char
'\'':String
cs) = Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'\''Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escape String
cs
       escape (Char
c:String
cs)    = Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escape String
cs
       escape []        = []

    let flags :: [Option]
flags = [ -- The -h option passes the file name for unlit to
                  -- put in a #line directive
                  String -> Option
GHC.SysTools.Option     String
"-h"
                  -- See Note [Don't normalise input filenames].
                , String -> Option
GHC.SysTools.Option (String -> Option) -> String -> Option
forall a b. (a -> b) -> a -> b
$ String -> String
escape String
input_fn
                , String -> String -> Option
GHC.SysTools.FileOption String
"" String
input_fn
                , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn
                ]

    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
        logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
    Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runUnlit Logger
logger DynFlags
dflags [Option]
flags

    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn

getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, [Warn]))
getFileArgs :: HscEnv -> String -> IO (DynFlags, Messages PsMessage, [Warn])
getFileArgs HscEnv
hsc_env String
input_fn = do
  let dflags0 :: DynFlags
dflags0 = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
      parser_opts :: ParserOpts
parser_opts = DynFlags -> ParserOpts
initParserOpts DynFlags
dflags0
  (Messages PsMessage
warns0, [Located String]
src_opts) <- ParserOpts -> String -> IO (Messages PsMessage, [Located String])
getOptionsFromFile ParserOpts
parser_opts String
input_fn
  (DynFlags
dflags1, [Located String]
unhandled_flags, [Warn]
warns)
    <- DynFlags
-> [Located String] -> IO (DynFlags, [Located String], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located String] -> m (DynFlags, [Located String], [Warn])
parseDynamicFilePragma DynFlags
dflags0 [Located String]
src_opts
  [Located String] -> IO ()
forall (m :: * -> *). MonadIO m => [Located String] -> m ()
checkProcessArgsResult [Located String]
unhandled_flags
  (DynFlags, Messages PsMessage, [Warn])
-> IO (DynFlags, Messages PsMessage, [Warn])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
dflags1, Messages PsMessage
warns0, [Warn]
warns)

runCppPhase :: HscEnv -> FilePath -> FilePath -> IO FilePath
runCppPhase :: HscEnv -> String -> String -> IO String
runCppPhase HscEnv
hsc_env String
input_fn String
output_fn = do
  Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> String
-> String
-> IO ()
doCpp (HscEnv -> Logger
hsc_logger HscEnv
hsc_env)
           (HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env)
           (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
           (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
           Bool
True{-raw-}
           String
input_fn String
output_fn
  String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn


runHscPhase :: PipeEnv
  -> HscEnv
  -> FilePath
  -> HscSource
  -> IO (HscEnv, ModSummary, HscRecompStatus)
runHscPhase :: PipeEnv
-> HscEnv
-> String
-> HscSource
-> IO (HscEnv, ModSummary, HscRecompStatus)
runHscPhase PipeEnv
pipe_env HscEnv
hsc_env0 String
input_fn HscSource
src_flavour = do
  let dflags0 :: DynFlags
dflags0 = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env0
      PipeEnv{ src_basename :: PipeEnv -> String
src_basename=String
basename,
               src_suffix :: PipeEnv -> String
src_suffix=String
suff } = PipeEnv
pipe_env

  -- we add the current directory (i.e. the directory in which
  -- the .hs files resides) to the include path, since this is
  -- what gcc does, and it's probably what you want.
  let current_dir :: String
current_dir = String -> String
takeDirectory String
basename
      new_includes :: IncludeSpecs
new_includes = IncludeSpecs -> [String] -> IncludeSpecs
addImplicitQuoteInclude IncludeSpecs
paths [String
current_dir]
      paths :: IncludeSpecs
paths = DynFlags -> IncludeSpecs
includePaths DynFlags
dflags0
      dflags :: DynFlags
dflags = DynFlags
dflags0 { includePaths :: IncludeSpecs
includePaths = IncludeSpecs
new_includes }
      hsc_env :: HscEnv
hsc_env = (() :: Constraint) => DynFlags -> HscEnv -> HscEnv
DynFlags -> HscEnv -> HscEnv
hscSetFlags DynFlags
dflags HscEnv
hsc_env0



  -- gather the imports and module name
  (Maybe StringBuffer
hspp_buf,ModuleName
mod_name,[(PkgQual, GenLocated SrcSpan ModuleName)]
imps,[(PkgQual, GenLocated SrcSpan ModuleName)]
src_imps, Bool
ghc_prim_imp) <- do
    StringBuffer
buf <- String -> IO StringBuffer
hGetStringBuffer String
input_fn
    let imp_prelude :: Bool
imp_prelude = Extension -> DynFlags -> Bool
xopt Extension
LangExt.ImplicitPrelude DynFlags
dflags
        popts :: ParserOpts
popts = DynFlags -> ParserOpts
initParserOpts DynFlags
dflags
        rn_pkg_qual :: ModuleName -> RawPkgQual -> PkgQual
rn_pkg_qual = UnitEnv -> ModuleName -> RawPkgQual -> PkgQual
renameRawPkgQual (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
        rn_imps :: [(RawPkgQual, GenLocated SrcSpan ModuleName)]
-> [(PkgQual, GenLocated SrcSpan ModuleName)]
rn_imps = ((RawPkgQual, GenLocated SrcSpan ModuleName)
 -> (PkgQual, GenLocated SrcSpan ModuleName))
-> [(RawPkgQual, GenLocated SrcSpan ModuleName)]
-> [(PkgQual, GenLocated SrcSpan ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(RawPkgQual
rpk, lmn :: GenLocated SrcSpan ModuleName
lmn@(L SrcSpan
_ ModuleName
mn)) -> (ModuleName -> RawPkgQual -> PkgQual
rn_pkg_qual ModuleName
mn RawPkgQual
rpk, GenLocated SrcSpan ModuleName
lmn))
    Either
  (Messages PsMessage)
  ([(RawPkgQual, GenLocated SrcSpan ModuleName)],
   [(RawPkgQual, GenLocated SrcSpan ModuleName)], Bool,
   GenLocated SrcSpan ModuleName)
eimps <- ParserOpts
-> Bool
-> StringBuffer
-> String
-> String
-> IO
     (Either
        (Messages PsMessage)
        ([(RawPkgQual, GenLocated SrcSpan ModuleName)],
         [(RawPkgQual, GenLocated SrcSpan ModuleName)], Bool,
         GenLocated SrcSpan ModuleName))
getImports ParserOpts
popts Bool
imp_prelude StringBuffer
buf String
input_fn (String
basename String -> String -> String
<.> String
suff)
    case Either
  (Messages PsMessage)
  ([(RawPkgQual, GenLocated SrcSpan ModuleName)],
   [(RawPkgQual, GenLocated SrcSpan ModuleName)], Bool,
   GenLocated SrcSpan ModuleName)
eimps of
        Left Messages PsMessage
errs -> Messages GhcMessage
-> IO
     (Maybe StringBuffer, ModuleName,
      [(PkgQual, GenLocated SrcSpan ModuleName)],
      [(PkgQual, GenLocated SrcSpan ModuleName)], Bool)
forall (io :: * -> *) a. MonadIO io => Messages GhcMessage -> io a
throwErrors (PsMessage -> GhcMessage
GhcPsMessage (PsMessage -> GhcMessage)
-> Messages PsMessage -> Messages GhcMessage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Messages PsMessage
errs)
        Right ([(RawPkgQual, GenLocated SrcSpan ModuleName)]
src_imps,[(RawPkgQual, GenLocated SrcSpan ModuleName)]
imps, Bool
ghc_prim_imp, L SrcSpan
_ ModuleName
mod_name) -> (Maybe StringBuffer, ModuleName,
 [(PkgQual, GenLocated SrcSpan ModuleName)],
 [(PkgQual, GenLocated SrcSpan ModuleName)], Bool)
-> IO
     (Maybe StringBuffer, ModuleName,
      [(PkgQual, GenLocated SrcSpan ModuleName)],
      [(PkgQual, GenLocated SrcSpan ModuleName)], Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
              (StringBuffer -> Maybe StringBuffer
forall a. a -> Maybe a
Just StringBuffer
buf, ModuleName
mod_name, [(RawPkgQual, GenLocated SrcSpan ModuleName)]
-> [(PkgQual, GenLocated SrcSpan ModuleName)]
rn_imps [(RawPkgQual, GenLocated SrcSpan ModuleName)]
imps, [(RawPkgQual, GenLocated SrcSpan ModuleName)]
-> [(PkgQual, GenLocated SrcSpan ModuleName)]
rn_imps [(RawPkgQual, GenLocated SrcSpan ModuleName)]
src_imps, Bool
ghc_prim_imp)

  -- Take -o into account if present
  -- Very like -ohi, but we must *only* do this if we aren't linking
  -- (If we're linking then the -o applies to the linked thing, not to
  -- the object file for one module.)
  -- Note the nasty duplication with the same computation in compileFile above
  ModLocation
location <- PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO ModLocation
mkOneShotModLocation PipeEnv
pipe_env DynFlags
dflags HscSource
src_flavour ModuleName
mod_name
  let o_file :: String
o_file = ModLocation -> String
ml_obj_file ModLocation
location -- The real object file
      hi_file :: String
hi_file = ModLocation -> String
ml_hi_file ModLocation
location
      hie_file :: String
hie_file = ModLocation -> String
ml_hie_file ModLocation
location
      dyn_o_file :: String
dyn_o_file = ModLocation -> String
ml_dyn_obj_file ModLocation
location

  Fingerprint
src_hash <- String -> IO Fingerprint
getFileHash (String
basename String -> String -> String
<.> String
suff)
  Maybe UTCTime
hi_date <- String -> IO (Maybe UTCTime)
modificationTimeIfExists String
hi_file
  Maybe UTCTime
hie_date <- String -> IO (Maybe UTCTime)
modificationTimeIfExists String
hie_file
  Maybe UTCTime
o_mod <- String -> IO (Maybe UTCTime)
modificationTimeIfExists String
o_file
  Maybe UTCTime
dyn_o_mod <- String -> IO (Maybe UTCTime)
modificationTimeIfExists String
dyn_o_file

  -- Tell the finder cache about this module
  Module
mod <- do
    let home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
    let fc :: FinderCache
fc        = HscEnv -> FinderCache
hsc_FC HscEnv
hsc_env
    FinderCache -> HomeUnit -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder FinderCache
fc HomeUnit
home_unit ModuleName
mod_name ModLocation
location

  -- Make the ModSummary to hand to hscMain
  let
    mod_summary :: ModSummary
mod_summary = ModSummary {  ms_mod :: Module
ms_mod       = Module
mod,
                                ms_hsc_src :: HscSource
ms_hsc_src   = HscSource
src_flavour,
                                ms_hspp_file :: String
ms_hspp_file = String
input_fn,
                                ms_hspp_opts :: DynFlags
ms_hspp_opts = DynFlags
dflags,
                                ms_hspp_buf :: Maybe StringBuffer
ms_hspp_buf  = Maybe StringBuffer
hspp_buf,
                                ms_location :: ModLocation
ms_location  = ModLocation
location,
                                ms_hs_hash :: Fingerprint
ms_hs_hash   = Fingerprint
src_hash,
                                ms_obj_date :: Maybe UTCTime
ms_obj_date  = Maybe UTCTime
o_mod,
                                ms_dyn_obj_date :: Maybe UTCTime
ms_dyn_obj_date = Maybe UTCTime
dyn_o_mod,
                                ms_parsed_mod :: Maybe HsParsedModule
ms_parsed_mod   = Maybe HsParsedModule
forall a. Maybe a
Nothing,
                                ms_iface_date :: Maybe UTCTime
ms_iface_date   = Maybe UTCTime
hi_date,
                                ms_hie_date :: Maybe UTCTime
ms_hie_date     = Maybe UTCTime
hie_date,
                                ms_ghc_prim_import :: Bool
ms_ghc_prim_import = Bool
ghc_prim_imp,
                                ms_textual_imps :: [(PkgQual, GenLocated SrcSpan ModuleName)]
ms_textual_imps = [(PkgQual, GenLocated SrcSpan ModuleName)]
imps,
                                ms_srcimps :: [(PkgQual, GenLocated SrcSpan ModuleName)]
ms_srcimps      = [(PkgQual, GenLocated SrcSpan ModuleName)]
src_imps }


  -- run the compiler!
  let msg :: Messager
      msg :: Messager
msg HscEnv
hsc_env (Int, Int)
_ RecompileRequired
what ModuleGraphNode
_ = Logger -> RecompileRequired -> IO ()
oneShotMsg (HscEnv -> Logger
hsc_logger HscEnv
hsc_env) RecompileRequired
what
  HscEnv
plugin_hsc_env' <- HscEnv -> IO HscEnv
initializePlugins HscEnv
hsc_env

  -- Need to set the knot-tying mutable variable for interface
  -- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var.
  -- See also Note [hsc_type_env_var hack]
  IORef (NameEnv TyThing)
type_env_var <- NameEnv TyThing -> IO (IORef (NameEnv TyThing))
forall a. a -> IO (IORef a)
newIORef NameEnv TyThing
forall a. NameEnv a
emptyNameEnv
  let plugin_hsc_env :: HscEnv
plugin_hsc_env = HscEnv
plugin_hsc_env' { hsc_type_env_vars :: KnotVars (IORef (NameEnv TyThing))
hsc_type_env_vars = ModuleEnv (IORef (NameEnv TyThing))
-> KnotVars (IORef (NameEnv TyThing))
forall a. ModuleEnv a -> KnotVars a
knotVarsFromModuleEnv ([(Module, IORef (NameEnv TyThing))]
-> ModuleEnv (IORef (NameEnv TyThing))
forall a. [(Module, a)] -> ModuleEnv a
mkModuleEnv [(Module
mod, IORef (NameEnv TyThing)
type_env_var)]) }

  HscRecompStatus
status <- Maybe Messager
-> HscEnv
-> ModSummary
-> Maybe ModIface
-> Maybe Linkable
-> (Int, Int)
-> IO HscRecompStatus
hscRecompStatus (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
msg) HscEnv
plugin_hsc_env ModSummary
mod_summary
                        Maybe ModIface
forall a. Maybe a
Nothing Maybe Linkable
forall a. Maybe a
Nothing (Int
1, Int
1)

  (HscEnv, ModSummary, HscRecompStatus)
-> IO (HscEnv, ModSummary, HscRecompStatus)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv
plugin_hsc_env, ModSummary
mod_summary, HscRecompStatus
status)

-- | Calculate the ModLocation from the provided DynFlags. This function is only used
-- in one-shot mode and therefore takes into account the effect of -o/-ohi flags
-- (which do nothing in --make mode)
mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO ModLocation
mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO ModLocation
mkOneShotModLocation PipeEnv
pipe_env DynFlags
dflags HscSource
src_flavour ModuleName
mod_name = do
    let PipeEnv{ src_basename :: PipeEnv -> String
src_basename=String
basename,
             src_suffix :: PipeEnv -> String
src_suffix=String
suff } = PipeEnv
pipe_env
    let location1 :: ModLocation
location1 = FinderOpts -> ModuleName -> String -> String -> ModLocation
mkHomeModLocation2 FinderOpts
fopts ModuleName
mod_name String
basename String
suff

    -- Boot-ify it if necessary
    let location2 :: ModLocation
location2
          | HscSource
HsBootFile <- HscSource
src_flavour = ModLocation -> ModLocation
addBootSuffixLocnOut ModLocation
location1
          | Bool
otherwise                 = ModLocation
location1


    -- Take -ohi into account if present
    -- This can't be done in mkHomeModuleLocation because
    -- it only applies to the module being compiles
    let ohi :: Maybe String
ohi = DynFlags -> Maybe String
outputHi DynFlags
dflags
        location3 :: ModLocation
location3 | Just String
fn <- Maybe String
ohi = ModLocation
location2{ ml_hi_file :: String
ml_hi_file = String
fn }
                  | Bool
otherwise      = ModLocation
location2

    let dynohi :: Maybe String
dynohi = DynFlags -> Maybe String
dynOutputHi DynFlags
dflags
        location4 :: ModLocation
location4 | Just String
fn <- Maybe String
dynohi = ModLocation
location3{ ml_dyn_hi_file :: String
ml_dyn_hi_file = String
fn }
                  | Bool
otherwise         = ModLocation
location3

    -- Take -o into account if present
    -- Very like -ohi, but we must *only* do this if we aren't linking
    -- (If we're linking then the -o applies to the linked thing, not to
    -- the object file for one module.)
    -- Note the nasty duplication with the same computation in compileFile
    -- above
    let expl_o_file :: Maybe String
expl_o_file = DynFlags -> Maybe String
outputFile_ DynFlags
dflags
        expl_dyn_o_file :: Maybe String
expl_dyn_o_file  = DynFlags -> Maybe String
dynOutputFile_ DynFlags
dflags
        location5 :: ModLocation
location5 | Just String
ofile <- Maybe String
expl_o_file
                  , let dyn_ofile :: String
dyn_ofile = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (String
ofile String -> String -> String
-<.> DynFlags -> String
dynObjectSuf_ DynFlags
dflags) Maybe String
expl_dyn_o_file
                  , GhcLink -> Bool
isNoLink (DynFlags -> GhcLink
ghcLink DynFlags
dflags)
                  = ModLocation
location4 { ml_obj_file :: String
ml_obj_file = String
ofile
                              , ml_dyn_obj_file :: String
ml_dyn_obj_file = String
dyn_ofile }
                  | Just String
dyn_ofile <- Maybe String
expl_dyn_o_file
                  = ModLocation
location4 { ml_dyn_obj_file :: String
ml_dyn_obj_file = String
dyn_ofile }
                  | Bool
otherwise = ModLocation
location4
    ModLocation -> IO ModLocation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ModLocation
location5
    where
      fopts :: FinderOpts
fopts = DynFlags -> FinderOpts
initFinderOpts DynFlags
dflags

runHscTcPhase :: HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage)
runHscTcPhase :: HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage)
runHscTcPhase = HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage)
hscTypecheckAndGetWarnings

runHscPostTcPhase ::
    HscEnv
  -> ModSummary
  -> FrontendResult
  -> Messages GhcMessage
  -> Maybe Fingerprint
  -> IO HscBackendAction
runHscPostTcPhase :: HscEnv
-> ModSummary
-> FrontendResult
-> Messages GhcMessage
-> Maybe Fingerprint
-> IO HscBackendAction
runHscPostTcPhase HscEnv
hsc_env ModSummary
mod_summary FrontendResult
tc_result Messages GhcMessage
tc_warnings Maybe Fingerprint
mb_old_hash = do
        HscEnv -> Hsc HscBackendAction -> IO HscBackendAction
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc HscBackendAction -> IO HscBackendAction)
-> Hsc HscBackendAction -> IO HscBackendAction
forall a b. (a -> b) -> a -> b
$ do
            ModSummary
-> FrontendResult
-> Messages GhcMessage
-> Maybe Fingerprint
-> Hsc HscBackendAction
hscDesugarAndSimplify ModSummary
mod_summary FrontendResult
tc_result Messages GhcMessage
tc_warnings Maybe Fingerprint
mb_old_hash


runHsPpPhase :: HscEnv -> FilePath -> FilePath -> FilePath -> IO FilePath
runHsPpPhase :: HscEnv -> String -> String -> String -> IO String
runHsPpPhase HscEnv
hsc_env String
orig_fn String
input_fn String
output_fn = do
    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
    let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
    Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runPp Logger
logger DynFlags
dflags
      ( [ String -> Option
GHC.SysTools.Option     String
orig_fn
      , String -> Option
GHC.SysTools.Option     String
input_fn
      , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn
      ] )
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
output_fn

phaseOutputFilenameNew :: Phase -- ^ The next phase
                       -> PipeEnv
                       -> HscEnv
                       -> Maybe ModLocation -- ^ A ModLocation, if we are compiling a Haskell source file
                       -> IO FilePath
phaseOutputFilenameNew :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
next_phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
maybe_loc = do
  let PipeEnv{StopPhase
stop_phase :: StopPhase
stop_phase :: PipeEnv -> StopPhase
stop_phase, String
src_basename :: PipeEnv -> String
src_basename :: String
src_basename, PipelineOutput
output_spec :: PipelineOutput
output_spec :: PipeEnv -> PipelineOutput
output_spec} = PipeEnv
pipe_env
  let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
      logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
      tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
  Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs (StopPhase -> Phase
stopPhaseToPhase StopPhase
stop_phase) PipelineOutput
output_spec
                    String
src_basename DynFlags
dflags Phase
next_phase Maybe ModLocation
maybe_loc


-- | Computes the next output filename for something in the compilation
-- pipeline.  This is controlled by several variables:
--
--      1. 'Phase': the last phase to be run (e.g. 'stopPhase').  This
--         is used to tell if we're in the last phase or not, because
--         in that case flags like @-o@ may be important.
--      2. 'PipelineOutput': is this intended to be a 'Temporary' or
--         'Persistent' build output?  Temporary files just go in
--         a fresh temporary name.
--      3. 'String': what was the basename of the original input file?
--      4. 'DynFlags': the obvious thing
--      5. 'Phase': the phase we want to determine the output filename of.
--      6. @Maybe ModLocation@: the 'ModLocation' of the module we're
--         compiling; this can be used to override the default output
--         of an object file.  (TODO: do we actually need this?)
getOutputFilename
  :: Logger
  -> TmpFs
  -> Phase
  -> PipelineOutput
  -> String
  -> DynFlags
  -> Phase -- next phase
  -> Maybe ModLocation
  -> IO FilePath
getOutputFilename :: Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs Phase
stop_phase PipelineOutput
output String
basename DynFlags
dflags Phase
next_phase Maybe ModLocation
maybe_location
  -- 1. If we are generating object files for a .hs file, then return the odir as the ModLocation
  -- will have been modified to point to the accurate locations
 | Phase
StopLn <- Phase
next_phase, Just ModLocation
loc <- Maybe ModLocation
maybe_location  =
      String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ if DynFlags -> Bool
dynamicNow DynFlags
dflags then ModLocation -> String
ml_dyn_obj_file ModLocation
loc
                                    else ModLocation -> String
ml_obj_file ModLocation
loc
 -- 2. If output style is persistant then
 | Bool
is_last_phase, PipelineOutput
Persistent   <- PipelineOutput
output = IO String
persistent_fn
 -- 3. Specific file is only set when outputFile is set by -o
 -- If we are in dynamic mode but -dyno is not set then write to the same path as
 -- -o with a .dyn_* extension. This case is not triggered for object files which
 -- are always handled by the ModLocation.
 | Bool
is_last_phase, PipelineOutput
SpecificFile <- PipelineOutput
output =
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$
      if DynFlags -> Bool
dynamicNow DynFlags
dflags
        then case DynFlags -> Maybe String
dynOutputFile_ DynFlags
dflags of
                Maybe String
Nothing -> let ofile :: String
ofile = DynFlags -> String
getOutputFile_ DynFlags
dflags
                               new_ext :: String
new_ext = case String -> String
takeExtension String
ofile of
                                            String
"" -> String
"dyn"
                                            String
ext -> String
"dyn_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. HasCallStack => [a] -> [a]
tail String
ext
                           in String -> String -> String
replaceExtension String
ofile String
new_ext
                Just String
fn -> String
fn
        else DynFlags -> String
getOutputFile_ DynFlags
dflags
 | Bool
keep_this_output                      = IO String
persistent_fn
 | Temporary TempFileLifetime
lifetime <- PipelineOutput
output          = Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
lifetime String
suffix
 | Bool
otherwise                             = Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule
   String
suffix
    where
          getOutputFile_ :: DynFlags -> String
getOutputFile_ DynFlags
dflags = case DynFlags -> Maybe String
outputFile_ DynFlags
dflags of
                                    Maybe String
Nothing -> String -> SDoc -> String
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"SpecificFile: No filename" ((Bool, Maybe String, Maybe String) -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((Bool, Maybe String, Maybe String) -> SDoc)
-> (Bool, Maybe String, Maybe String) -> SDoc
forall a b. (a -> b) -> a -> b
$ (DynFlags -> Bool
dynamicNow DynFlags
dflags, DynFlags -> Maybe String
outputFile_ DynFlags
dflags, DynFlags -> Maybe String
dynOutputFile_ DynFlags
dflags))
                                    Just String
fn -> String
fn

          hcsuf :: String
hcsuf      = DynFlags -> String
hcSuf DynFlags
dflags
          odir :: Maybe String
odir       = DynFlags -> Maybe String
objectDir DynFlags
dflags
          osuf :: String
osuf       = DynFlags -> String
objectSuf DynFlags
dflags
          keep_hc :: Bool
keep_hc    = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepHcFiles DynFlags
dflags
          keep_hscpp :: Bool
keep_hscpp = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepHscppFiles DynFlags
dflags
          keep_s :: Bool
keep_s     = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepSFiles DynFlags
dflags
          keep_bc :: Bool
keep_bc    = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepLlvmFiles DynFlags
dflags

          myPhaseInputExt :: Phase -> String
myPhaseInputExt Phase
HCc       = String
hcsuf
          myPhaseInputExt Phase
MergeForeign = String
osuf
          myPhaseInputExt Phase
StopLn    = String
osuf
          myPhaseInputExt Phase
other     = Phase -> String
phaseInputExt Phase
other

          is_last_phase :: Bool
is_last_phase = Phase
next_phase Phase -> Phase -> Bool
`eqPhase` Phase
stop_phase

          -- sometimes, we keep output from intermediate stages
          keep_this_output :: Bool
keep_this_output =
               case Phase
next_phase of
                       As Bool
_    | Bool
keep_s     -> Bool
True
                       Phase
LlvmOpt | Bool
keep_bc    -> Bool
True
                       Phase
HCc     | Bool
keep_hc    -> Bool
True
                       HsPp HscSource
_  | Bool
keep_hscpp -> Bool
True   -- See #10869
                       Phase
_other               -> Bool
False

          suffix :: String
suffix = Phase -> String
myPhaseInputExt Phase
next_phase

          -- persistent object files get put in odir
          persistent_fn :: IO String
persistent_fn
             | Phase
StopLn <- Phase
next_phase = String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
odir_persistent
             | Bool
otherwise            = String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
persistent

          persistent :: String
persistent = String
basename String -> String -> String
<.> String
suffix

          odir_persistent :: String
odir_persistent
             | Just String
d <- Maybe String
odir = (String
d String -> String -> String
</> String
persistent)
             | Bool
otherwise      = String
persistent


-- | LLVM Options. These are flags to be passed to opt and llc, to ensure
-- consistency we list them in pairs, so that they form groups.
llvmOptions :: DynFlags
            -> [(String, String)]  -- ^ pairs of (opt, llc) arguments
llvmOptions :: DynFlags -> [(String, String)]
llvmOptions DynFlags
dflags =
       [(String
"-enable-tbaa -tbaa",  String
"-enable-tbaa") | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_LlvmTBAA DynFlags
dflags ]
    [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String
"-relocation-model=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
rmodel
        ,String
"-relocation-model=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
rmodel) | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
rmodel)]
    [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String
"-stack-alignment=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show Int
align)
        ,String
"-stack-alignment=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show Int
align)) | Int
align Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 ]

    -- Additional llc flags
    [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String
"", String
"-mcpu=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
mcpu)   | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
mcpu)
                                 , Bool -> Bool
not ((String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isInfixOf String
"-mcpu") (DynFlags -> (DynFlags -> [String]) -> [String]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [String]
opt_lc)) ]
    [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String
"", String
"-mattr=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
attrs) | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
attrs) ]
    [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String
"", String
"-target-abi=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
abi) | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
abi) ]

  where target :: String
target = PlatformMisc -> String
platformMisc_llvmTarget (PlatformMisc -> String) -> PlatformMisc -> String
forall a b. (a -> b) -> a -> b
$ DynFlags -> PlatformMisc
platformMisc DynFlags
dflags
        Just (LlvmTarget String
_ String
mcpu [String]
mattr) = String -> [(String, LlvmTarget)] -> Maybe LlvmTarget
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
target (LlvmConfig -> [(String, LlvmTarget)]
llvmTargets (LlvmConfig -> [(String, LlvmTarget)])
-> LlvmConfig -> [(String, LlvmTarget)]
forall a b. (a -> b) -> a -> b
$ DynFlags -> LlvmConfig
llvmConfig DynFlags
dflags)

        -- Relocation models
        rmodel :: String
rmodel | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PIC DynFlags
dflags         = String
"pic"
               | DynFlags -> Bool
positionIndependent DynFlags
dflags  = String
"pic"
               | DynFlags -> Ways
ways DynFlags
dflags Ways -> Way -> Bool
`hasWay` Way
WayDyn = String
"dynamic-no-pic"
               | Bool
otherwise                   = String
"static"

        platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags

        align :: Int
        align :: Int
align = case Platform -> Arch
platformArch Platform
platform of
                  Arch
ArchX86_64 | DynFlags -> Bool
isAvxEnabled DynFlags
dflags -> Int
32
                  Arch
_                                -> Int
0

        attrs :: String
        attrs :: String
attrs = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
mattr
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+sse42"   | DynFlags -> Bool
isSse4_2Enabled DynFlags
dflags   ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+sse2"    | Platform -> Bool
isSse2Enabled Platform
platform   ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+sse"     | Platform -> Bool
isSseEnabled Platform
platform    ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx512f" | DynFlags -> Bool
isAvx512fEnabled DynFlags
dflags  ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx2"    | DynFlags -> Bool
isAvx2Enabled DynFlags
dflags     ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx"     | DynFlags -> Bool
isAvxEnabled DynFlags
dflags      ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx512cd"| DynFlags -> Bool
isAvx512cdEnabled DynFlags
dflags ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx512er"| DynFlags -> Bool
isAvx512erEnabled DynFlags
dflags ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+avx512pf"| DynFlags -> Bool
isAvx512pfEnabled DynFlags
dflags ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+bmi"     | DynFlags -> Bool
isBmiEnabled DynFlags
dflags      ]
              [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"+bmi2"    | DynFlags -> Bool
isBmi2Enabled DynFlags
dflags     ]

        abi :: String
        abi :: String
abi = case Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) of
                Arch
ArchRISCV64 -> String
"lp64d"
                Arch
_           -> String
""


-- Note [Filepaths and Multiple Home Units]
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (IncludeSpecs [String]
incs [String]
quotes [String]
impl) =
     let go :: [String] -> [String]
go = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (DynFlags -> String -> String
augmentByWorkingDirectory DynFlags
dflags)
     in [String] -> [String] -> [String] -> IncludeSpecs
IncludeSpecs ([String] -> [String]
go [String]
incs) ([String] -> [String]
go [String]
quotes) ([String] -> [String]
go [String]
impl)
-- -----------------------------------------------------------------------------
-- Running CPP

-- | Run CPP
--
-- UnitEnv is needed to compute MIN_VERSION macros
doCpp :: Logger -> TmpFs -> DynFlags -> UnitEnv -> Bool -> FilePath -> FilePath -> IO ()
doCpp :: Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> String
-> String
-> IO ()
doCpp Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env Bool
raw String
input_fn String
output_fn = do
    let hscpp_opts :: [String]
hscpp_opts = DynFlags -> [String]
picPOpts DynFlags
dflags
    let cmdline_include_paths :: IncludeSpecs
cmdline_include_paths = DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (DynFlags -> IncludeSpecs
includePaths DynFlags
dflags)
    let unit_state :: UnitState
unit_state = (() :: Constraint) => UnitEnv -> UnitState
UnitEnv -> UnitState
ue_units UnitEnv
unit_env
    [String]
pkg_include_dirs <- MaybeErr UnitErr [String] -> IO [String]
forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
                        ([UnitInfo] -> [String]
collectIncludeDirs ([UnitInfo] -> [String])
-> MaybeErr UnitErr [UnitInfo] -> MaybeErr UnitErr [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UnitEnv -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo UnitEnv
unit_env)
    -- MP: This is not quite right, the headers which are supposed to be installed in
    -- the package might not be the same as the provided include paths, but it's a close
    -- enough approximation for things to work. A proper solution would be to have to declare which paths should
    -- be propagated to dependent packages.
    let home_pkg_deps :: [DynFlags]
home_pkg_deps =
         [HomeUnitEnv -> DynFlags
homeUnitEnv_dflags (HomeUnitEnv -> DynFlags)
-> (UnitEnv -> HomeUnitEnv) -> UnitEnv -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (() :: Constraint) => UnitId -> UnitEnv -> HomeUnitEnv
UnitId -> UnitEnv -> HomeUnitEnv
ue_findHomeUnitEnv UnitId
uid (UnitEnv -> DynFlags) -> UnitEnv -> DynFlags
forall a b. (a -> b) -> a -> b
$ UnitEnv
unit_env | UnitId
uid <- UnitId -> UnitEnv -> [UnitId]
ue_transitiveHomeDeps (UnitEnv -> UnitId
ue_currentUnit UnitEnv
unit_env) UnitEnv
unit_env]
        dep_pkg_extra_inputs :: [IncludeSpecs]
dep_pkg_extra_inputs = [DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
fs (DynFlags -> IncludeSpecs
includePaths DynFlags
fs) | DynFlags
fs <- [DynFlags]
home_pkg_deps]

    let include_paths_global :: [String]
include_paths_global = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
          (IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_include_dirs
                                                    [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (IncludeSpecs -> [String]) -> [IncludeSpecs] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IncludeSpecs -> [String]
includePathsGlobal [IncludeSpecs]
dep_pkg_extra_inputs)
    let include_paths_quote :: [String]
include_paths_quote = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-iquote" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
          (IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
           IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
cmdline_include_paths)
    let include_paths :: [String]
include_paths = [String]
include_paths_quote [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
include_paths_global

    let verbFlags :: [String]
verbFlags = DynFlags -> [String]
getVerbFlags DynFlags
dflags

    let cpp_prog :: [Option] -> IO ()
cpp_prog [Option]
args | Bool
raw       = Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runCpp Logger
logger DynFlags
dflags [Option]
args
                      | Bool
otherwise = Maybe ForeignSrcLang
-> Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runCc Maybe ForeignSrcLang
forall a. Maybe a
Nothing Logger
logger TmpFs
tmpfs DynFlags
dflags
                                        (String -> Option
GHC.SysTools.Option String
"-E" Option -> [Option] -> [Option]
forall a. a -> [a] -> [a]
: [Option]
args)

    let platform :: Platform
platform   = DynFlags -> Platform
targetPlatform DynFlags
dflags
        targetArch :: String
targetArch = Arch -> String
stringEncodeArch (Arch -> String) -> Arch -> String
forall a b. (a -> b) -> a -> b
$ Platform -> Arch
platformArch Platform
platform
        targetOS :: String
targetOS = OS -> String
stringEncodeOS (OS -> String) -> OS -> String
forall a b. (a -> b) -> a -> b
$ Platform -> OS
platformOS Platform
platform
        isWindows :: Bool
isWindows = Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
    let target_defs :: [String]
target_defs =
          [ String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
HOST_OS     String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_BUILD_OS",
            String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ HOST_ARCH   ++ "_BUILD_ARCH",
            String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
targetOS    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_OS",
            String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
targetArch  String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_ARCH" ]
        -- remember, in code we *compile*, the HOST is the same our TARGET,
        -- and BUILD is the same as our HOST.

    let io_manager_defs :: [String]
io_manager_defs =
          [ String
"-D__IO_MANAGER_WINIO__=1" | Bool
isWindows ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__IO_MANAGER_MIO__=1"               ]

    let sse_defs :: [String]
sse_defs =
          [ String
"-D__SSE__"      | Platform -> Bool
isSseEnabled      Platform
platform ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__SSE2__"     | Platform -> Bool
isSse2Enabled     Platform
platform ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__SSE4_2__"   | DynFlags -> Bool
isSse4_2Enabled   DynFlags
dflags ]

    let avx_defs :: [String]
avx_defs =
          [ String
"-D__AVX__"      | DynFlags -> Bool
isAvxEnabled      DynFlags
dflags ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX2__"     | DynFlags -> Bool
isAvx2Enabled     DynFlags
dflags ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512CD__" | DynFlags -> Bool
isAvx512cdEnabled DynFlags
dflags ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512ER__" | DynFlags -> Bool
isAvx512erEnabled DynFlags
dflags ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512F__"  | DynFlags -> Bool
isAvx512fEnabled  DynFlags
dflags ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512PF__" | DynFlags -> Bool
isAvx512pfEnabled DynFlags
dflags ]

    [String]
backend_defs <- Logger -> DynFlags -> IO [String]
getBackendDefs Logger
logger DynFlags
dflags

    let th_defs :: [String]
th_defs = [ String
"-D__GLASGOW_HASKELL_TH__" ]
    -- Default CPP defines in Haskell source
    String
ghcVersionH <- DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env
    let hsSourceCppOpts :: [String]
hsSourceCppOpts = [ String
"-include", String
ghcVersionH ]

    -- MIN_VERSION macros
    let uids :: [(Unit, Maybe PackageArg)]
uids = UnitState -> [(Unit, Maybe PackageArg)]
explicitUnits UnitState
unit_state
        pkgs :: [UnitInfo]
pkgs = ((Unit, Maybe PackageArg) -> Maybe UnitInfo)
-> [(Unit, Maybe PackageArg)] -> [UnitInfo]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (UnitState -> Unit -> Maybe UnitInfo
lookupUnit UnitState
unit_state (Unit -> Maybe UnitInfo)
-> ((Unit, Maybe PackageArg) -> Unit)
-> (Unit, Maybe PackageArg)
-> Maybe UnitInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Unit, Maybe PackageArg) -> Unit
forall a b. (a, b) -> a
fst) [(Unit, Maybe PackageArg)]
uids
    [Option]
mb_macro_include <-
        if Bool -> Bool
not ([UnitInfo] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
pkgs) Bool -> Bool -> Bool
&& GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_VersionMacros DynFlags
dflags
            then do String
macro_stub <- Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule String
"h"
                    String -> String -> IO ()
writeFile String
macro_stub ([UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs)
                    -- Include version macros for every *exposed* package.
                    -- Without -hide-all-packages and with a package database
                    -- size of 1000 packages, it takes cpp an estimated 2
                    -- milliseconds to process this file. See #10970
                    -- comment 8.
                    [Option] -> IO [Option]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String -> String -> Option
GHC.SysTools.FileOption String
"-include" String
macro_stub]
            else [Option] -> IO [Option]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []

    [Option] -> IO ()
cpp_prog       (   (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
verbFlags
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
include_paths
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
hsSourceCppOpts
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
target_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
backend_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
th_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
hscpp_opts
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
sse_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
avx_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
io_manager_defs
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
mb_macro_include
        -- Set the language mode to assembler-with-cpp when preprocessing. This
        -- alleviates some of the C99 macro rules relating to whitespace and the hash
        -- operator, which we tend to abuse. Clang in particular is not very happy
        -- about this.
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
GHC.SysTools.Option     String
"-x"
                       , String -> Option
GHC.SysTools.Option     String
"assembler-with-cpp"
                       , String -> Option
GHC.SysTools.Option     String
input_fn
        -- We hackily use Option instead of FileOption here, so that the file
        -- name is not back-slashed on Windows.  cpp is capable of
        -- dealing with / in filenames, so it works fine.  Furthermore
        -- if we put in backslashes, cpp outputs #line directives
        -- with *double* backslashes.   And that in turn means that
        -- our error messages get double backslashes in them.
        -- In due course we should arrange that the lexer deals
        -- with these \\ escapes properly.
                       , String -> Option
GHC.SysTools.Option     String
"-o"
                       , String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn
                       ])

getBackendDefs :: Logger -> DynFlags -> IO [String]
getBackendDefs :: Logger -> DynFlags -> IO [String]
getBackendDefs Logger
logger DynFlags
dflags | DynFlags -> Backend
backend DynFlags
dflags Backend -> Backend -> Bool
forall a. Eq a => a -> a -> Bool
== Backend
LLVM = do
    Maybe LlvmVersion
llvmVer <- Logger -> DynFlags -> IO (Maybe LlvmVersion)
figureLlvmVersion Logger
logger DynFlags
dflags
    [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ case (LlvmVersion -> [Int]) -> Maybe LlvmVersion -> Maybe [Int]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LlvmVersion -> [Int]
llvmVersionList Maybe LlvmVersion
llvmVer of
               Just [Int
m] -> [ String
"-D__GLASGOW_HASKELL_LLVM__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int, Int) -> String
format (Int
m,Int
0) ]
               Just (Int
m:Int
n:[Int]
_) -> [ String
"-D__GLASGOW_HASKELL_LLVM__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int, Int) -> String
format (Int
m,Int
n) ]
               Maybe [Int]
_ -> []
  where
    format :: (Int, Int) -> String
format (Int
major, Int
minor)
      | Int
minor Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
100 = String -> String
forall a. HasCallStack => String -> a
error String
"getBackendDefs: Unsupported minor version"
      | Bool
otherwise = Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ (Int
100 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
major Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
minor :: Int) -- Contract is Int

getBackendDefs Logger
_ DynFlags
_ =
    [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []

-- | What phase to run after one of the backend code generators has run
hscPostBackendPhase :: HscSource -> Backend -> Phase
hscPostBackendPhase :: HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
HsBootFile Backend
_    =  Phase
StopLn
hscPostBackendPhase HscSource
HsigFile Backend
_      =  Phase
StopLn
hscPostBackendPhase HscSource
_ Backend
bcknd =
  case Backend
bcknd of
        Backend
ViaC        -> Phase
HCc
        Backend
NCG         -> Bool -> Phase
As Bool
False
        Backend
LLVM        -> Phase
LlvmOpt
        Backend
NoBackend   -> Phase
StopLn
        Backend
Interpreter -> Phase
StopLn


compileStub :: HscEnv -> FilePath -> IO FilePath
compileStub :: HscEnv -> String -> IO String
compileStub HscEnv
hsc_env String
stub_c = HscEnv -> ForeignSrcLang -> String -> IO String
compileForeign HscEnv
hsc_env ForeignSrcLang
LangC String
stub_c


-- ---------------------------------------------------------------------------
-- join object files into a single relocatable object file, using ld -r

{-
Note [Produce big objects on Windows]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The Windows Portable Executable object format has a limit of 32k sections, which
we tend to blow through pretty easily. Thankfully, there is a "big object"
extension, which raises this limit to 2^32. However, it must be explicitly
enabled in the toolchain:

 * the assembler accepts the -mbig-obj flag, which causes it to produce a
   bigobj-enabled COFF object.

 * the linker accepts the --oformat pe-bigobj-x86-64 flag. Despite what the name
   suggests, this tells the linker to produce a bigobj-enabled COFF object, no a
   PE executable.

Previously when we used ld.bfd we had to enable bigobj output in a few places:

 * When merging object files (GHC.Driver.Pipeline.Execute.joinObjectFiles)

 * When assembling (GHC.Driver.Pipeline.runPhase (RealPhase As ...))

However, this is no longer necessary with ld.lld, which detects that the
object is large on its own.

Unfortunately the big object format is not supported on 32-bit targets so
none of this can be used in that case.


Note [Object merging]
~~~~~~~~~~~~~~~~~~~~~
On most platforms one can "merge" a set of relocatable object files into a new,
partiall-linked-but-still-relocatable object. In a typical UNIX-style linker,
this is accomplished with the `ld -r` command. We rely on this for two ends:

 * We rely on `ld -r` to squash together split sections, making GHCi loading
   more efficient. See Note [Merging object files for GHCi].

 * We use merging to combine a module's object code (e.g. produced by the NCG)
   with its foreign stubs (typically produced by a C compiler).

The command used for object linking is set using the -pgmlm and -optlm
command-line options.

Sadly, the LLD linker that we use on Windows does not support the `-r` flag
needed to support object merging (see #21068). For this reason on Windows we do
not support GHCi objects.  To deal with foreign stubs we build a static archive
of all of a module's object files instead merging them. Consequently, we can
end up producing `.o` files which are in fact static archives. However,
toolchains generally don't have a problem with this as they use file headers,
not the filename, to determine the nature of inputs.

Note that this has somewhat non-obvious consequences when producing
initializers and finalizers. See Note [Initializers and finalizers in Cmm]
in GHC.Cmm.InitFini for details.


Note [Merging object files for GHCi]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
GHCi can usually loads standard linkable object files using GHC's linker
implementation. However, most users build their projects with -split-sections,
meaning that such object files can have an extremely high number of sections.
As the linker must map each of these sections individually, loading such object
files is very inefficient.

To avoid this inefficiency, we use the linker's `-r` flag and a linker script
to produce a merged relocatable object file. This file will contain a singe
text section section and can consequently be mapped far more efficiently. As
gcc tends to do unpredictable things to our linker command line, we opt to
invoke ld directly in this case, in contrast to our usual strategy of linking
via gcc.
-}

-- | See Note [Object merging].
joinObjectFiles :: HscEnv -> [FilePath] -> FilePath -> IO ()
joinObjectFiles :: HscEnv -> [String] -> String -> IO ()
joinObjectFiles HscEnv
hsc_env [String]
o_files String
output_fn
  | Bool
can_merge_objs = do
  let toolSettings' :: ToolSettings
toolSettings' = DynFlags -> ToolSettings
toolSettings DynFlags
dflags
      ldIsGnuLd :: Bool
ldIsGnuLd = ToolSettings -> Bool
toolSettings_ldIsGnuLd ToolSettings
toolSettings'
      ld_r :: [Option] -> IO ()
ld_r [Option]
args = Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runMergeObjects (HscEnv -> Logger
hsc_logger HscEnv
hsc_env) (HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env) (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) (
                        (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
GHC.SysTools.Option [String]
ld_build_id
                     [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
GHC.SysTools.Option String
"-o",
                          String -> String -> Option
GHC.SysTools.FileOption String
"" String
output_fn ]
                     [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
args)

      -- suppress the generation of the .note.gnu.build-id section,
      -- which we don't need and sometimes causes ld to emit a
      -- warning:
      ld_build_id :: [String]
ld_build_id | ToolSettings -> Bool
toolSettings_ldSupportsBuildId ToolSettings
toolSettings' = [String
"--build-id=none"]
                  | Bool
otherwise                                    = []

  if Bool
ldIsGnuLd
     then do
          String
script <- Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule String
"ldscript"
          String
cwd <- IO String
getCurrentDirectory
          let o_files_abs :: [String]
o_files_abs = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
x -> String
"\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (String
cwd String -> String -> String
</> String
x) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\"") [String]
o_files
          String -> String -> IO ()
writeFile String
script (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"INPUT(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
o_files_abs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
          [Option] -> IO ()
ld_r [String -> String -> Option
GHC.SysTools.FileOption String
"" String
script]
     else if ToolSettings -> Bool
toolSettings_ldSupportsFilelist ToolSettings
toolSettings'
     then do
          String
filelist <- Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule String
"filelist"
          String -> String -> IO ()
writeFile String
filelist (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String]
o_files
          [Option] -> IO ()
ld_r [String -> Option
GHC.SysTools.Option String
"-filelist",
                String -> String -> Option
GHC.SysTools.FileOption String
"" String
filelist]
     else
          [Option] -> IO ()
ld_r ((String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> Option
GHC.SysTools.FileOption String
"") [String]
o_files)

  | Bool
otherwise = do
  String -> (String -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadIO m =>
String -> (String -> m a) -> m a
withAtomicRename String
output_fn ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
tmp_ar ->
      IO () -> IO ()
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> Maybe String -> [Option] -> IO ()
runAr Logger
logger DynFlags
dflags Maybe String
forall a. Maybe a
Nothing ([Option] -> IO ()) -> [Option] -> IO ()
forall a b. (a -> b) -> a -> b
$ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option ([String] -> [Option]) -> [String] -> [Option]
forall a b. (a -> b) -> a -> b
$ [String
"qc" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dashL, String
tmp_ar] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
o_files
  where
    dashLSupported :: Bool
dashLSupported = Settings -> Bool
sArSupportsDashL (DynFlags -> Settings
settings DynFlags
dflags)
    dashL :: String
dashL = if Bool
dashLSupported then String
"L" else String
""
    can_merge_objs :: Bool
can_merge_objs = Maybe (String, [Option]) -> Bool
forall a. Maybe a -> Bool
isJust (DynFlags -> Maybe (String, [Option])
pgm_lm (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env))
    dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
    tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
    logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env


-----------------------------------------------------------------------------
-- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file

getHCFilePackages :: FilePath -> IO [UnitId]
getHCFilePackages :: String -> IO [UnitId]
getHCFilePackages String
filename =
  String -> IOMode -> (Handle -> IO [UnitId]) -> IO [UnitId]
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
filename IOMode
ReadMode ((Handle -> IO [UnitId]) -> IO [UnitId])
-> (Handle -> IO [UnitId]) -> IO [UnitId]
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
    String
l <- Handle -> IO String
hGetLine Handle
h
    case String
l of
      Char
'/':Char
'*':Char
' ':Char
'G':Char
'H':Char
'C':Char
'_':Char
'P':Char
'A':Char
'C':Char
'K':Char
'A':Char
'G':Char
'E':Char
'S':String
rest ->
          [UnitId] -> IO [UnitId]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((String -> UnitId) -> [String] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map String -> UnitId
stringToUnitId (String -> [String]
words String
rest))
      String
_other ->
          [UnitId] -> IO [UnitId]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []


linkDynLibCheck :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLibCheck :: Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLibCheck Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env [String]
o_files [UnitId]
dep_units = do
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (DynFlags -> Bool
haveRtsOptsFlags DynFlags
dflags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg Logger
logger MessageClass
MCInfo SrcSpan
noSrcSpan
      (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle
      (String -> SDoc
text String
"Warning: -rtsopts and -with-rtsopts have no effect with -shared." SDoc -> SDoc -> SDoc
$$
      String -> SDoc
text String
"    Call hs_init_ghc() from your main() function to set these options.")
  Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLib Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env [String]
o_files [UnitId]
dep_units



-- ---------------------------------------------------------------------------
-- Macros (cribbed from Cabal)

generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  -- Do not add any C-style comments. See #3389.
  [ String -> String -> Version -> String
generateMacros String
"" String
pkgname Version
version
  | UnitInfo
pkg <- [UnitInfo]
pkgs
  , let version :: Version
version = UnitInfo -> Version
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
unitPackageVersion UnitInfo
pkg
        pkgname :: String
pkgname = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar (UnitInfo -> String
forall u. GenUnitInfo u -> String
unitPackageNameString UnitInfo
pkg)
  ]

fixchar :: Char -> Char
fixchar :: Char -> Char
fixchar Char
'-' = Char
'_'
fixchar Char
c   = Char
c

generateMacros :: String -> String -> Version -> String
generateMacros :: String -> String -> Version -> String
generateMacros String
prefix String
name Version
version =
  [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [String
"#define ", String
prefix, String
"VERSION_",String
name,String
" ",String -> String
forall a. Show a => a -> String
show (Version -> String
showVersion Version
version),String
"\n"
  ,String
"#define MIN_", String
prefix, String
"VERSION_",String
name,String
"(major1,major2,minor) (\\\n"
  ,String
"  (major1) <  ",String
major1,String
" || \\\n"
  ,String
"  (major1) == ",String
major1,String
" && (major2) <  ",String
major2,String
" || \\\n"
  ,String
"  (major1) == ",String
major1,String
" && (major2) == ",String
major2,String
" && (minor) <= ",String
minor,String
")"
  ,String
"\n\n"
  ]
  where
    (String
major1:String
major2:String
minor:[String]
_) = (Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Int -> String
forall a. Show a => a -> String
show (Version -> [Int]
versionBranch Version
version [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Int -> [Int]
forall a. a -> [a]
repeat Int
0)


-- -----------------------------------------------------------------------------
-- Misc.



touchObjectFile :: Logger -> DynFlags -> FilePath -> IO ()
touchObjectFile :: Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
path = do
  Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
takeDirectory String
path
  Logger -> DynFlags -> String -> String -> IO ()
GHC.SysTools.touch Logger
logger DynFlags
dflags String
"Touching object file" String
path

-- | Find out path to @ghcversion.h@ file
getGhcVersionPathName :: DynFlags -> UnitEnv -> IO FilePath
getGhcVersionPathName :: DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env = do
  [String]
candidates <- case DynFlags -> Maybe String
ghcVersionFile DynFlags
dflags of
    Just String
path -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
path]
    Maybe String
Nothing -> do
        [UnitInfo]
ps <- MaybeErr UnitErr [UnitInfo] -> IO [UnitInfo]
forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr (UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' UnitEnv
unit_env [UnitId
rtsUnitId])
        [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((String -> String -> String
</> String
"ghcversion.h") (String -> String) -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [UnitInfo] -> [String]
collectIncludeDirs [UnitInfo]
ps)

  [String]
found <- (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesFileExist [String]
candidates
  case [String]
found of
      []    -> GhcException -> IO String
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
InstallationError
                                    (String
"ghcversion.h missing; tried: "
                                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
candidates))
      (String
x:[String]
_) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
x

-- Note [-fPIC for assembler]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~
-- When compiling .c source file GHC's driver pipeline basically
-- does the following two things:
--   1. ${CC}              -S 'PIC_CFLAGS' source.c
--   2. ${CC} -x assembler -c 'PIC_CFLAGS' source.S
--
-- Why do we need to pass 'PIC_CFLAGS' both to C compiler and assembler?
-- Because on some architectures (at least sparc32) assembler also chooses
-- the relocation type!
-- Consider the following C module:
--
--     /* pic-sample.c */
--     int v;
--     void set_v (int n) { v = n; }
--     int  get_v (void)  { return v; }
--
--     $ gcc -S -fPIC pic-sample.c
--     $ gcc -c       pic-sample.s -o pic-sample.no-pic.o # incorrect binary
--     $ gcc -c -fPIC pic-sample.s -o pic-sample.pic.o    # correct binary
--
--     $ objdump -r -d pic-sample.pic.o    > pic-sample.pic.o.od
--     $ objdump -r -d pic-sample.no-pic.o > pic-sample.no-pic.o.od
--     $ diff -u pic-sample.pic.o.od pic-sample.no-pic.o.od
--
-- Most of architectures won't show any difference in this test, but on sparc32
-- the following assembly snippet:
--
--    sethi   %hi(_GLOBAL_OFFSET_TABLE_-8), %l7
--
-- generates two kinds or relocations, only 'R_SPARC_PC22' is correct:
--
--       3c:  2f 00 00 00     sethi  %hi(0), %l7
--    -                       3c: R_SPARC_PC22        _GLOBAL_OFFSET_TABLE_-0x8
--    +                       3c: R_SPARC_HI22        _GLOBAL_OFFSET_TABLE_-0x8

{- Note [Don't normalise input filenames]
   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Summary
  We used to normalise input filenames when starting the unlit phase. This
  broke hpc in `--make` mode with imported literate modules (#2991).

Introduction
  1) --main
  When compiling a module with --main, GHC scans its imports to find out which
  other modules it needs to compile too. It turns out that there is a small
  difference between saying `ghc --make A.hs`, when `A` imports `B`, and
  specifying both modules on the command line with `ghc --make A.hs B.hs`. In
  the former case, the filename for B is inferred to be './B.hs' instead of
  'B.hs'.

  2) unlit
  When GHC compiles a literate haskell file, the source code first needs to go
  through unlit, which turns it into normal Haskell source code. At the start
  of the unlit phase, in `Driver.Pipeline.runPhase`, we call unlit with the
  option `-h` and the name of the original file. We used to normalise this
  filename using System.FilePath.normalise, which among other things removes
  an initial './'. unlit then uses that filename in #line directives that it
  inserts in the transformed source code.

  3) SrcSpan
  A SrcSpan represents a portion of a source code file. It has fields
  linenumber, start column, end column, and also a reference to the file it
  originated from. The SrcSpans for a literate haskell file refer to the
  filename that was passed to unlit -h.

  4) -fhpc
  At some point during compilation with -fhpc, in the function
  `GHC.HsToCore.Coverage.isGoodTickSrcSpan`, we compare the filename that a
  `SrcSpan` refers to with the name of the file we are currently compiling.
  For some reason I don't yet understand, they can sometimes legitimally be
  different, and then hpc ignores that SrcSpan.

Problem
  When running `ghc --make -fhpc A.hs`, where `A.hs` imports the literate
  module `B.lhs`, `B` is inferred to be in the file `./B.lhs` (1). At the
  start of the unlit phase, the name `./B.lhs` is normalised to `B.lhs` (2).
  Therefore the SrcSpans of `B` refer to the file `B.lhs` (3), but we are
  still compiling `./B.lhs`. Hpc thinks these two filenames are different (4),
  doesn't include ticks for B, and we have unhappy customers (#2991).

Solution
  Do not normalise `input_fn` when starting the unlit phase.

Alternative solution
  Another option would be to not compare the two filenames on equality, but to
  use System.FilePath.equalFilePath. That function first normalises its
  arguments. The problem is that by the time we need to do the comparison, the
  filenames have been turned into FastStrings, probably for performance
  reasons, so System.FilePath.equalFilePath can not be used directly.

Archeology
  The call to `normalise` was added in a commit called "Fix slash
  direction on Windows with the new filePath code" (c9b6b5e8). The problem
  that commit was addressing has since been solved in a different manner, in a
  commit called "Fix the filename passed to unlit" (1eedbc6b). So the
  `normalise` is no longer necessary.
-}