{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
#include <ghcplatform.h>
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.Types
import GHC.Types.SourceFile
import GHC.Unit.Module.Status
import GHC.Unit.Module.ModIface
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.Utils.Error
import Data.Maybe
import GHC.CmmToLlvm.Mangler
import GHC.SysTools
import GHC.SysTools.Cpp
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 GHC.Driver.Config.Parser
import GHC.Parser.Header
import GHC.Data.StringBuffer
import GHC.Types.SourceError
import GHC.Unit.Finder
import Data.IORef
import GHC.Types.Name.Env
import GHC.Platform.Ways
import GHC.Driver.LlvmConfigCache (readLlvmConfigCache)
import GHC.CmmToLlvm.Config (LlvmTarget (..), LlvmConfig (..))
import {-# SOURCE #-} GHC.Driver.Pipeline (compileForeign, compileEmptyStub)
import GHC.Settings
import System.IO
import GHC.Linker.ExtraObj
import GHC.Linker.Dynamic
import GHC.Utils.Panic
import GHC.Unit.Module.Env
import GHC.Driver.Env.KnotVars
import GHC.Driver.Config.Finder
import GHC.Rename.Names
import GHC.StgToJS.Linker.Linker (embedJsFile)
import Language.Haskell.Syntax.Module.Name
import GHC.Unit.Home.ModInfo
import GHC.Runtime.Loader (initializePlugins)
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. (HasCallStack, Exception e) => e -> HookedUse a)
-> MonadThrow HookedUse
forall e a. (HasCallStack, Exception e) => e -> HookedUse a
forall (m :: * -> *).
Monad m =>
(forall e a. (HasCallStack, Exception e) => e -> m a)
-> MonadThrow m
$cthrowM :: forall e a. (HasCallStack, Exception e) => e -> HookedUse a
throwM :: forall e a. (HasCallStack, Exception e) => e -> HookedUse a
MonadThrow, MonadThrow HookedUse
MonadThrow HookedUse =>
(forall e a.
(HasCallStack, Exception e) =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a)
-> MonadCatch HookedUse
forall e a.
(HasCallStack, Exception e) =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a
forall (m :: * -> *).
MonadThrow m =>
(forall e a.
(HasCallStack, Exception e) =>
m a -> (e -> m a) -> m a)
-> MonadCatch m
$ccatch :: forall e a.
(HasCallStack, Exception e) =>
HookedUse a -> (e -> HookedUse a) -> HookedUse a
catch :: forall e a.
(HasCallStack, 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
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)
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, HomeModLinkable, 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
-> CppOpts
-> 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)
(CppOpts
{ cppUseCc :: Bool
cppUseCc = Bool
True
, cppLinePragmas :: Bool
cppLinePragmas = Bool
True
})
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_Js PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
js_src) =
PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runJsPhase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
js_src
runPhase (T_ForeignJs PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
js_src) =
PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runForeignJsPhase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location String
js_src
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 Maybe ModLocation
location String
input_fn) = Phase
-> PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runCcPhase Phase
phase PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location 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
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
LlvmConfig
llvm_config <- LlvmConfigCache -> IO LlvmConfig
readLlvmConfigCache (HscEnv -> LlvmConfigCache
hsc_llvm_config HscEnv
hsc_env)
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"
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 (LlvmConfig -> DynFlags -> [(String, String)]
llvmOptions LlvmConfig
llvm_config 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
| 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
LlvmConfig
llvm_config <- LlvmConfigCache -> IO LlvmConfig
readLlvmConfigCache (HscEnv -> LlvmConfigCache
hsc_llvm_config HscEnv
hsc_env)
let
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
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
llvm_config of
Just String
passes -> String
passes
Maybe String
Nothing -> String -> String
forall a. HasCallStack => 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 (LlvmConfig -> DynFlags -> [(String, String)]
llvmOptions LlvmConfig
llvm_config 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_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
let (Logger -> DynFlags -> Platform -> [Option] -> IO ()
as_prog, Logger -> DynFlags -> Platform -> IO CompilerInfo
get_asm_info) =
( DefunctionalizedAssemblerProg
-> Logger -> DynFlags -> Platform -> [Option] -> IO ()
applyAssemblerProg (DefunctionalizedAssemblerProg
-> Logger -> DynFlags -> Platform -> [Option] -> IO ())
-> DefunctionalizedAssemblerProg
-> Logger
-> DynFlags
-> Platform
-> [Option]
-> IO ()
forall a b. (a -> b) -> a -> b
$ Backend -> DefunctionalizedAssemblerProg
backendAssemblerProg (DynFlags -> Backend
backend DynFlags
dflags)
, DefunctionalizedAssemblerInfoGetter
-> Logger -> DynFlags -> Platform -> IO CompilerInfo
applyAssemblerInfoGetter (DefunctionalizedAssemblerInfoGetter
-> Logger -> DynFlags -> Platform -> IO CompilerInfo)
-> DefunctionalizedAssemblerInfoGetter
-> Logger
-> DynFlags
-> Platform
-> IO CompilerInfo
forall a b. (a -> b) -> a -> b
$ Backend -> DefunctionalizedAssemblerInfoGetter
backendAssemblerInfoGetter (DynFlags -> Backend
backend DynFlags
dflags)
)
CompilerInfo
asmInfo <- Logger -> DynFlags -> Platform -> IO CompilerInfo
get_asm_info Logger
logger DynFlags
dflags Platform
platform
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
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 -> Platform -> [Option] -> IO ()
as_prog
Logger
logger DynFlags
dflags
Platform
platform
([Option]
local_includes [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
global_includes
[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
[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]
++ [ String -> Option
GHC.SysTools.Option String
"-Wa,--no-type-check"
| Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchWasm32]
[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
forall doc. IsLine doc => String -> doc
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
runJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
runJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runJsPhase 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
Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
input_fn
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
input_fn
runForeignJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
runForeignJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runForeignJsPhase 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 tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
let unit_env :: UnitEnv
unit_env = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
StopLn PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
forall a. Maybe a
Nothing
Logger -> DynFlags -> TmpFs -> UnitEnv -> String -> String -> IO ()
embedJsFile Logger
logger DynFlags
dflags TmpFs
tmpfs UnitEnv
unit_env 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
applyAssemblerInfoGetter
:: DefunctionalizedAssemblerInfoGetter
-> Logger -> DynFlags -> Platform -> IO CompilerInfo
applyAssemblerInfoGetter :: DefunctionalizedAssemblerInfoGetter
-> Logger -> DynFlags -> Platform -> IO CompilerInfo
applyAssemblerInfoGetter DefunctionalizedAssemblerInfoGetter
StandardAssemblerInfoGetter Logger
logger DynFlags
dflags Platform
_platform =
Logger -> DynFlags -> IO CompilerInfo
getAssemblerInfo Logger
logger DynFlags
dflags
applyAssemblerInfoGetter DefunctionalizedAssemblerInfoGetter
JSAssemblerInfoGetter Logger
_ DynFlags
_ Platform
_ =
CompilerInfo -> IO CompilerInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CompilerInfo
Emscripten
applyAssemblerInfoGetter DefunctionalizedAssemblerInfoGetter
DarwinClangAssemblerInfoGetter Logger
logger DynFlags
dflags Platform
platform =
if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin then
CompilerInfo -> IO CompilerInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CompilerInfo
Clang
else
Logger -> DynFlags -> IO CompilerInfo
getAssemblerInfo Logger
logger DynFlags
dflags
applyAssemblerProg
:: DefunctionalizedAssemblerProg
-> Logger -> DynFlags -> Platform -> [Option] -> IO ()
applyAssemblerProg :: DefunctionalizedAssemblerProg
-> Logger -> DynFlags -> Platform -> [Option] -> IO ()
applyAssemblerProg DefunctionalizedAssemblerProg
StandardAssemblerProg Logger
logger DynFlags
dflags Platform
_platform =
Logger -> DynFlags -> [Option] -> IO ()
runAs Logger
logger DynFlags
dflags
applyAssemblerProg DefunctionalizedAssemblerProg
JSAssemblerProg Logger
logger DynFlags
dflags Platform
_platform =
Logger -> DynFlags -> [Option] -> IO ()
runEmscripten Logger
logger DynFlags
dflags
applyAssemblerProg DefunctionalizedAssemblerProg
DarwinClangAssemblerProg Logger
logger DynFlags
dflags Platform
platform =
if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin then
Logger -> DynFlags -> [Option] -> IO ()
runClang Logger
logger DynFlags
dflags
else
Logger -> DynFlags -> [Option] -> IO ()
runAs Logger
logger DynFlags
dflags
runCcPhase :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
runCcPhase :: Phase
-> PipeEnv -> HscEnv -> Maybe ModLocation -> String -> IO String
runCcPhase Phase
cc_phase 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 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)
[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 []
[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
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
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 = []
String
output_fn <- Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO String
phaseOutputFilenameNew Phase
StopLn PipeEnv
pipe_env HscEnv
hsc_env Maybe ModLocation
location
Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
output_fn)
let
more_hcc_opts :: [String]
more_hcc_opts =
(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]
++
[String
"-fno-strict-aliasing"]
String
ghcVersionH <- DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env
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
temp_outputFilename ->
Maybe ForeignSrcLang
-> Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runCc (Phase -> Maybe ForeignSrcLang
phaseForeignLanguage Phase
cc_phase) Logger
logger TmpFs
tmpfs DynFlags
dflags (
[ String -> Option
GHC.SysTools.Option String
"-c"
, 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
temp_outputFilename
]
[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
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ 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)
]
[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 [])
[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]
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
runHscBackendPhase :: PipeEnv
-> HscEnv
-> ModuleName
-> HscSource
-> ModLocation
-> HscBackendAction
-> IO ([FilePath], ModIface, HomeModLinkable, FilePath)
runHscBackendPhase :: PipeEnv
-> HscEnv
-> ModuleName
-> HscSource
-> ModLocation
-> HscBackendAction
-> IO ([String], ModIface, HomeModLinkable, 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
next_phase :: Phase
next_phase = HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
src_flavour (DynFlags -> Backend
backend DynFlags
dflags)
case HscBackendAction
result of
HscUpdate ModIface
iface ->
if | Bool -> Bool
not (Backend -> Bool
backendGeneratesCode (DynFlags -> Backend
backend DynFlags
dflags)) ->
String -> IO ([String], ModIface, HomeModLinkable, String)
forall a. HasCallStack => String -> a
panic String
"HscUpdate not relevant for NoBackend"
| Bool -> Bool
not (Backend -> Bool
backendGeneratesCodeForHsBoot (DynFlags -> Backend
backend DynFlags
dflags)) -> do
([String], ModIface, HomeModLinkable, String)
-> IO ([String], ModIface, HomeModLinkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], ModIface
iface, HomeModLinkable
emptyHomeModInfoLinkable, String
o_file)
| Bool
otherwise -> do
case HscSource
src_flavour of
HscSource
HsigFile -> do
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
HscSource
HsBootFile -> Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
o_file
HscSource
HsSrcFile -> String -> IO ()
forall a. HasCallStack => String -> a
panic String
"HscUpdate not relevant for HscSrcFile"
([String], ModIface, HomeModLinkable, String)
-> IO ([String], ModIface, HomeModLinkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], ModIface
iface, HomeModLinkable
emptyHomeModInfoLinkable, 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
}
-> if Bool -> Bool
not (Backend -> Bool
backendGeneratesCode (DynFlags -> Backend
backend DynFlags
dflags)) then
String -> IO ([String], ModIface, HomeModLinkable, String)
forall a. HasCallStack => String -> a
panic String
"HscRecomp not relevant for NoBackend"
else if Backend -> Bool
backendWritesFiles (DynFlags -> Backend
backend DynFlags
dflags) then
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
stg_infos, Maybe CmmCgInfos
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
stg_infos Maybe CmmCgInfos
cg_infos
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
HomeModLinkable
mlinkable <-
if Backend -> Bool
backendGeneratesCode (DynFlags -> Backend
backend DynFlags
dflags) Bool -> Bool -> Bool
&& GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ByteCodeAndObjectCode DynFlags
dflags
then do
Linkable
bc <- HscEnv
-> ModuleName -> CgInteractiveGuts -> ModLocation -> IO Linkable
generateFreshByteCode HscEnv
hsc_env ModuleName
mod_name (CgGuts -> CgInteractiveGuts
mkCgInteractiveGuts CgGuts
cgguts) ModLocation
mod_location
HomeModLinkable -> IO HomeModLinkable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModLinkable -> IO HomeModLinkable)
-> HomeModLinkable -> IO HomeModLinkable
forall a b. (a -> b) -> a -> b
$ HomeModLinkable
emptyHomeModInfoLinkable { homeMod_bytecode = Just bc }
else HomeModLinkable -> IO HomeModLinkable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return HomeModLinkable
emptyHomeModInfoLinkable
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)
([String], ModIface, HomeModLinkable, String)
-> IO ([String], ModIface, HomeModLinkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
fos, ModIface
final_iface, HomeModLinkable
mlinkable, String
outputFilename)
else
do
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
Linkable
bc <- HscEnv
-> ModuleName -> CgInteractiveGuts -> ModLocation -> IO Linkable
generateFreshByteCode HscEnv
hsc_env ModuleName
mod_name (CgGuts -> CgInteractiveGuts
mkCgInteractiveGuts CgGuts
cgguts) ModLocation
mod_location
([String], ModIface, HomeModLinkable, String)
-> IO ([String], ModIface, HomeModLinkable, String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], ModIface
final_iface, HomeModLinkable
emptyHomeModInfoLinkable { homeMod_bytecode = Just bc } , String -> String
forall a. HasCallStack => String -> a
panic String
"interpreter")
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 :: 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 = [
String -> Option
GHC.SysTools.Option String
"-h"
, 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
-> CppOpts
-> 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)
(CppOpts
{ cppUseCc :: Bool
cppUseCc = Bool
False
, cppLinePragmas :: Bool
cppLinePragmas = Bool
True
})
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
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 = new_includes }
hsc_env1 :: HscEnv
hsc_env1 = (() :: Constraint) => DynFlags -> HscEnv -> HscEnv
DynFlags -> HscEnv -> HscEnv
hscSetFlags DynFlags
dflags HscEnv
hsc_env0
HscEnv
hsc_env <- HscEnv -> IO HscEnv
initializePlugins HscEnv
hsc_env1
(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)
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
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
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
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 }
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
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 hsc_env' :: HscEnv
hsc_env' = HscEnv
hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
HscRecompStatus
status <- Maybe Messager
-> HscEnv
-> ModSummary
-> Maybe ModIface
-> HomeModLinkable
-> (Int, Int)
-> IO HscRecompStatus
hscRecompStatus (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
msg) HscEnv
hsc_env' ModSummary
mod_summary
Maybe ModIface
forall a. Maybe a
Nothing HomeModLinkable
emptyHomeModInfoLinkable (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
hsc_env', ModSummary
mod_summary, HscRecompStatus
status)
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
let location2 :: ModLocation
location2
| HscSource
HsBootFile <- HscSource
src_flavour = ModLocation -> ModLocation
addBootSuffixLocnOut ModLocation
location1
| Bool
otherwise = ModLocation
location1
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 = 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 = fn }
| Bool
otherwise = ModLocation
location3
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 = ofile
, ml_dyn_obj_file = dyn_ofile }
| Just String
dyn_ofile <- Maybe String
expl_dyn_o_file
= ModLocation
location4 { ml_dyn_obj_file = 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
-> PipeEnv
-> HscEnv
-> Maybe ModLocation
-> 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
getOutputFilename
:: Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> 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
| 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
| Bool
is_last_phase, PipelineOutput
Persistent <- PipelineOutput
output = IO String
persistent_fn
| 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 -> SDoc
forall a. Outputable a => a -> SDoc
ppr (DynFlags -> Bool
dynamicNow DynFlags
dflags) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"-" (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
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
Phase
_other -> Bool
False
suffix :: String
suffix = Phase -> String
myPhaseInputExt Phase
next_phase
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
llvmOptions :: LlvmConfig
-> DynFlags
-> [(String, String)]
llvmOptions :: LlvmConfig -> DynFlags -> [(String, String)]
llvmOptions LlvmConfig
llvm_config 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 ]
[(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
llvm_config)
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
ArchLoongArch64 -> String
"lp64d"
Arch
_ -> String
""
hscPostBackendPhase :: HscSource -> Backend -> Phase
hscPostBackendPhase :: HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
HsBootFile Backend
_ = Phase
StopLn
hscPostBackendPhase HscSource
HsigFile Backend
_ = Phase
StopLn
hscPostBackendPhase HscSource
_ Backend
bcknd = Backend -> Phase
backendNormalSuccessorPhase Backend
bcknd
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
joinObjectFiles :: HscEnv -> [FilePath] -> FilePath -> IO ()
joinObjectFiles :: HscEnv -> [String] -> String -> IO ()
joinObjectFiles HscEnv
hsc_env [String]
o_files String
output_fn
| Bool
can_merge_objs Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
dashLSupported = 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
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)
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
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
forall doc. IsLine doc => String -> doc
text String
"Warning: -rtsopts and -with-rtsopts have no effect with -shared." SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
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
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