{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Driver.Pipeline (
oneShot, compileFile,
preprocess,
compileOne, compileOne',
link,
PhasePlus(..), CompPipeline(..), PipeEnv(..), PipeState(..),
phaseOutputFilename, getOutputFilename, getPipeState, getPipeEnv,
hscPostBackendPhase, getLocation, setModLocation, setDynFlags,
runPhase,
doCpp,
linkingNeeded, checkLinkInfo, writeInterfaceOnlyMode
) where
#include <ghcplatform.h>
#include "HsVersions.h"
import GHC.Prelude
import GHC.Platform
import GHC.Tc.Types
import GHC.Driver.Main
import GHC.Driver.Env hiding ( Hsc )
import GHC.Driver.Errors
import GHC.Driver.Pipeline.Monad
import GHC.Driver.Config
import GHC.Driver.Phases
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.Driver.Ppr
import GHC.Driver.Hooks
import GHC.Platform.Ways
import GHC.Platform.ArchOS
import GHC.Parser.Header
import GHC.Parser.Errors.Ppr
import GHC.SysTools
import GHC.Utils.TmpFs
import GHC.Linker.ExtraObj
import GHC.Linker.Dynamic
import GHC.Linker.Static
import GHC.Linker.Types
import GHC.Utils.Outputable
import GHC.Utils.Error
import GHC.Utils.Panic
import GHC.Utils.Misc
import GHC.Utils.Monad
import GHC.Utils.Exception as Exception
import GHC.Utils.Logger
import GHC.CmmToLlvm ( llvmFixupAsm, llvmVersionList )
import qualified GHC.LanguageExtensions as LangExt
import GHC.Settings
import GHC.Data.Bag ( unitBag )
import GHC.Data.FastString ( mkFastString )
import GHC.Data.StringBuffer ( hGetStringBuffer, hPutStringBuffer )
import GHC.Data.Maybe ( expectJust )
import GHC.Iface.Make ( mkFullIface )
import GHC.Types.Basic ( SuccessFlag(..) )
import GHC.Types.Target
import GHC.Types.SrcLoc
import GHC.Types.SourceFile
import GHC.Types.SourceError
import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.State
import GHC.Unit.Finder
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.Graph (needsTemplateHaskellOrQQ)
import GHC.Unit.Module.Deps
import GHC.Unit.Home.ModInfo
import System.Directory
import System.FilePath
import System.IO
import Control.Monad
import qualified Control.Monad.Catch as MC (handle)
import Data.List ( isInfixOf, intercalate )
import Data.Maybe
import Data.Version
import Data.Either ( partitionEithers )
import Data.Time ( UTCTime )
preprocess :: HscEnv
-> FilePath
-> Maybe InputFileBuffer
-> Maybe Phase
-> IO (Either ErrorMessages (DynFlags, FilePath))
preprocess :: HscEnv
-> String
-> Maybe InputFileBuffer
-> Maybe Phase
-> IO (Either ErrorMessages (DynFlags, String))
preprocess HscEnv
hsc_env String
input_fn Maybe InputFileBuffer
mb_input_buf Maybe Phase
mb_phase =
(SourceError -> IO (Either ErrorMessages (DynFlags, String)))
-> IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String))
forall (m :: * -> *) a.
MonadCatch m =>
(SourceError -> m a) -> m a -> m a
handleSourceError (\SourceError
err -> Either ErrorMessages (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String))
forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorMessages -> Either ErrorMessages (DynFlags, String)
forall a b. a -> Either a b
Left (SourceError -> ErrorMessages
srcErrorMessages SourceError
err))) (IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String)))
-> IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String))
forall a b. (a -> b) -> a -> b
$
(GhcException -> IO (Either ErrorMessages (DynFlags, String)))
-> IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String))
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
MC.handle GhcException -> IO (Either ErrorMessages (DynFlags, String))
handler (IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String)))
-> IO (Either ErrorMessages (DynFlags, String))
-> IO (Either ErrorMessages (DynFlags, String))
forall a b. (a -> b) -> a -> b
$
((DynFlags, String) -> Either ErrorMessages (DynFlags, String))
-> IO (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DynFlags, String) -> Either ErrorMessages (DynFlags, String)
forall a b. b -> Either a b
Right (IO (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String)))
-> IO (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String))
forall a b. (a -> b) -> a -> b
$ do
MASSERT2(isJust mb_phase || isHaskellSrcFilename input_fn, text input_fn)
(DynFlags
dflags, String
fp, Maybe ModIface
mb_iface) <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
anyHsc HscEnv
hsc_env (String
input_fn, Maybe InputFileBuffer
mb_input_buf, (Phase -> PhasePlus) -> Maybe Phase -> Maybe PhasePlus
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Phase -> PhasePlus
RealPhase Maybe Phase
mb_phase)
Maybe String
forall a. Maybe a
Nothing
(TempFileLifetime -> PipelineOutput
Temporary TempFileLifetime
TFL_GhcSession)
Maybe ModLocation
forall a. Maybe a
Nothing
[]
MASSERT(isNothing mb_iface)
(DynFlags, String) -> IO (DynFlags, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
dflags, String
fp)
where
srcspan :: SrcSpan
srcspan = SrcLoc -> SrcSpan
srcLocSpan (SrcLoc -> SrcSpan) -> SrcLoc -> SrcSpan
forall a b. (a -> b) -> a -> b
$ FastString -> Int -> Int -> SrcLoc
mkSrcLoc (String -> FastString
mkFastString String
input_fn) Int
1 Int
1
handler :: GhcException -> IO (Either ErrorMessages (DynFlags, String))
handler (ProgramError String
msg) = Either ErrorMessages (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrorMessages (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String)))
-> Either ErrorMessages (DynFlags, String)
-> IO (Either ErrorMessages (DynFlags, String))
forall a b. (a -> b) -> a -> b
$ ErrorMessages -> Either ErrorMessages (DynFlags, String)
forall a b. a -> Either a b
Left (ErrorMessages -> Either ErrorMessages (DynFlags, String))
-> ErrorMessages -> Either ErrorMessages (DynFlags, String)
forall a b. (a -> b) -> a -> b
$ MsgEnvelope DecoratedSDoc -> ErrorMessages
forall a. a -> Bag a
unitBag (MsgEnvelope DecoratedSDoc -> ErrorMessages)
-> MsgEnvelope DecoratedSDoc -> ErrorMessages
forall a b. (a -> b) -> a -> b
$
SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc
mkPlainMsgEnvelope SrcSpan
srcspan (SDoc -> MsgEnvelope DecoratedSDoc)
-> SDoc -> MsgEnvelope DecoratedSDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
msg
handler GhcException
ex = GhcException -> IO (Either ErrorMessages (DynFlags, String))
forall a. GhcException -> IO a
throwGhcExceptionIO GhcException
ex
compileOne :: HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne :: HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne = Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne' Maybe TcGblEnv
forall a. Maybe a
Nothing (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
batchMsg)
compileOne' :: Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne' :: Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne' Maybe TcGblEnv
m_tc_result Maybe Messager
mHscMessage
HscEnv
hsc_env0 ModSummary
summary Int
mod_index Int
nmods Maybe ModIface
mb_old_iface Maybe Linkable
mb_old_linkable
SourceModified
source_modified0
= do
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env0
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env0
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags1 Int
2 (String -> SDoc
text String
"compile: input file" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
input_fnpp)
(HscStatus
status, HscEnv
plugin_hsc_env) <- Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int, Int)
-> IO (HscStatus, HscEnv)
hscIncrementalCompile
Bool
always_do_basic_recompilation_check
Maybe TcGblEnv
m_tc_result Maybe Messager
mHscMessage
HscEnv
hsc_env ModSummary
summary SourceModified
source_modified Maybe ModIface
mb_old_iface (Int
mod_index, Int
nmods)
let hsc_env' :: HscEnv
hsc_env' = HscEnv
plugin_hsc_env
let flags :: DynFlags
flags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env0
in do Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepHiFiles DynFlags
flags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
TFL_CurrentModule ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$
[ModLocation -> String
ml_hi_file (ModLocation -> String) -> ModLocation -> String
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
summary]
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepOFiles DynFlags
flags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
TFL_GhcSession ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$
[ModLocation -> String
ml_obj_file (ModLocation -> String) -> ModLocation -> String
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
summary]
case (HscStatus
status, Backend
bcknd) of
(HscUpToDate ModIface
iface ModDetails
hmi_details, Backend
_) ->
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details Maybe Linkable
mb_old_linkable
(HscNotGeneratingCode ModIface
iface ModDetails
hmi_details, Backend
NoBackend) ->
let mb_linkable :: Maybe Linkable
mb_linkable = if HscSource -> Bool
isHsBootOrSig HscSource
src_flavour
then Maybe Linkable
forall a. Maybe a
Nothing
else Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just (UTCTime -> Module -> [Unlinked] -> Linkable
LM (ModSummary -> UTCTime
ms_hs_date ModSummary
summary) Module
this_mod [])
in HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details Maybe Linkable
mb_linkable
(HscNotGeneratingCode ModIface
_ ModDetails
_, Backend
_) -> String -> IO HomeModInfo
forall a. String -> a
panic String
"compileOne HscNotGeneratingCode"
(HscStatus
_, Backend
NoBackend) -> String -> IO HomeModInfo
forall a. String -> a
panic String
"compileOne NoBackend"
(HscUpdateBoot ModIface
iface ModDetails
hmi_details, Backend
Interpreter) ->
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details Maybe Linkable
forall a. Maybe a
Nothing
(HscUpdateBoot ModIface
iface ModDetails
hmi_details, Backend
_) -> do
Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
object_filename
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details Maybe Linkable
forall a. Maybe a
Nothing
(HscUpdateSig ModIface
iface ModDetails
hmi_details, Backend
Interpreter) -> do
let !linkable :: Linkable
linkable = UTCTime -> Module -> [Unlinked] -> Linkable
LM (ModSummary -> UTCTime
ms_hs_date ModSummary
summary) Module
this_mod []
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details (Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
linkable)
(HscUpdateSig ModIface
iface ModDetails
hmi_details, Backend
_) -> do
String
output_fn <- Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs Phase
next_phase
(TempFileLifetime -> PipelineOutput
Temporary TempFileLifetime
TFL_CurrentModule) String
basename DynFlags
dflags
Phase
next_phase (ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
(DynFlags, String, Maybe ModIface)
_ <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
StopLn HscEnv
hsc_env'
(String
output_fn,
Maybe InputFileBuffer
forall a. Maybe a
Nothing,
PhasePlus -> Maybe PhasePlus
forall a. a -> Maybe a
Just (HscSource -> ModuleName -> HscStatus -> PhasePlus
HscOut HscSource
src_flavour
ModuleName
mod_name (ModIface -> ModDetails -> HscStatus
HscUpdateSig ModIface
iface ModDetails
hmi_details)))
(String -> Maybe String
forall a. a -> Maybe a
Just String
basename)
PipelineOutput
Persistent
(ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
[]
UTCTime
o_time <- String -> IO UTCTime
getModificationUTCTime String
object_filename
let !linkable :: Linkable
linkable = UTCTime -> Module -> [Unlinked] -> Linkable
LM UTCTime
o_time Module
this_mod [String -> Unlinked
DotO String
object_filename]
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
hmi_details (Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
linkable)
(HscRecomp { hscs_guts :: HscStatus -> CgGuts
hscs_guts = CgGuts
cgguts,
hscs_mod_location :: HscStatus -> ModLocation
hscs_mod_location = ModLocation
mod_location,
hscs_partial_iface :: HscStatus -> PartialModIface
hscs_partial_iface = PartialModIface
partial_iface,
hscs_old_iface_hash :: HscStatus -> Maybe Fingerprint
hscs_old_iface_hash = Maybe Fingerprint
mb_old_iface_hash
}, Backend
Interpreter) -> do
ModIface
final_iface <- HscEnv -> PartialModIface -> Maybe CgInfos -> IO ModIface
mkFullIface HscEnv
hsc_env' PartialModIface
partial_iface Maybe CgInfos
forall a. Maybe a
Nothing
ModDetails
hmi_details <- IO ModDetails -> IO ModDetails
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModDetails -> IO ModDetails) -> IO ModDetails -> IO ModDetails
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModSummary -> ModIface -> IO ModDetails
initModDetails HscEnv
hsc_env' ModSummary
summary ModIface
final_iface
IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Logger
-> DynFlags
-> Bool
-> ModIface
-> Maybe Fingerprint
-> ModLocation
-> IO ()
hscMaybeWriteIface Logger
logger DynFlags
dflags Bool
True ModIface
final_iface Maybe Fingerprint
mb_old_iface_hash (ModSummary -> ModLocation
ms_location ModSummary
summary)
(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 (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 (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]
unlinked_time :: UTCTime
unlinked_time = ModSummary -> UTCTime
ms_hs_date ModSummary
summary
let !linkable :: Linkable
linkable = UTCTime -> Module -> [Unlinked] -> Linkable
LM UTCTime
unlinked_time (ModSummary -> Module
ms_mod ModSummary
summary)
([Unlinked]
hs_unlinked [Unlinked] -> [Unlinked] -> [Unlinked]
forall a. [a] -> [a] -> [a]
++ [Unlinked]
stub_o)
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
final_iface ModDetails
hmi_details (Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
linkable)
(HscRecomp{}, Backend
_) -> do
String
output_fn <- Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs Phase
next_phase
(TempFileLifetime -> PipelineOutput
Temporary TempFileLifetime
TFL_CurrentModule)
String
basename DynFlags
dflags Phase
next_phase (ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
(DynFlags
_, String
_, Just ModIface
iface) <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
StopLn HscEnv
hsc_env'
(String
output_fn,
Maybe InputFileBuffer
forall a. Maybe a
Nothing,
PhasePlus -> Maybe PhasePlus
forall a. a -> Maybe a
Just (HscSource -> ModuleName -> HscStatus -> PhasePlus
HscOut HscSource
src_flavour ModuleName
mod_name HscStatus
status))
(String -> Maybe String
forall a. a -> Maybe a
Just String
basename)
PipelineOutput
Persistent
(ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
[]
UTCTime
o_time <- String -> IO UTCTime
getModificationUTCTime String
object_filename
let !linkable :: Linkable
linkable = UTCTime -> Module -> [Unlinked] -> Linkable
LM UTCTime
o_time Module
this_mod [String -> Unlinked
DotO String
object_filename]
ModDetails
details <- HscEnv -> ModSummary -> ModIface -> IO ModDetails
initModDetails HscEnv
hsc_env' ModSummary
summary ModIface
iface
HomeModInfo -> IO HomeModInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (HomeModInfo -> IO HomeModInfo) -> HomeModInfo -> IO HomeModInfo
forall a b. (a -> b) -> a -> b
$! ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
details (Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
linkable)
where dflags0 :: DynFlags
dflags0 = ModSummary -> DynFlags
ms_hspp_opts ModSummary
summary
this_mod :: Module
this_mod = ModSummary -> Module
ms_mod ModSummary
summary
location :: ModLocation
location = ModSummary -> ModLocation
ms_location ModSummary
summary
input_fn :: String
input_fn = String -> Maybe String -> String
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"compile:hs" (ModLocation -> Maybe String
ml_hs_file ModLocation
location)
input_fnpp :: String
input_fnpp = ModSummary -> String
ms_hspp_file ModSummary
summary
mod_graph :: ModuleGraph
mod_graph = HscEnv -> ModuleGraph
hsc_mod_graph HscEnv
hsc_env0
needsLinker :: Bool
needsLinker = ModuleGraph -> Bool
needsTemplateHaskellOrQQ ModuleGraph
mod_graph
isDynWay :: Bool
isDynWay = (Way -> Bool) -> Set Way -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Way -> Way -> Bool
forall a. Eq a => a -> a -> Bool
== Way
WayDyn) (DynFlags -> Set Way
ways DynFlags
dflags0)
isProfWay :: Bool
isProfWay = (Way -> Bool) -> Set Way -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Way -> Way -> Bool
forall a. Eq a => a -> a -> Bool
== Way
WayProf) (DynFlags -> Set Way
ways DynFlags
dflags0)
internalInterpreter :: Bool
internalInterpreter = Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExternalInterpreter DynFlags
dflags0)
src_flavour :: HscSource
src_flavour = ModSummary -> HscSource
ms_hsc_src ModSummary
summary
mod_name :: ModuleName
mod_name = ModSummary -> ModuleName
ms_mod_name ModSummary
summary
next_phase :: Phase
next_phase = HscSource -> Backend -> Phase
hscPostBackendPhase HscSource
src_flavour Backend
bcknd
object_filename :: String
object_filename = ModLocation -> String
ml_obj_file ModLocation
location
dflags1 :: DynFlags
dflags1 = if Bool
hostIsDynamic Bool -> Bool -> Bool
&& Bool
internalInterpreter Bool -> Bool -> Bool
&&
Bool -> Bool
not Bool
isDynWay Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
isProfWay Bool -> Bool -> Bool
&& Bool
needsLinker
then DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
dflags0 GeneralFlag
Opt_BuildDynamicToo
else DynFlags
dflags0
dflags2 :: DynFlags
dflags2 = if Bool -> Bool
not Bool
internalInterpreter Bool -> Bool -> Bool
&& Bool
needsLinker
then DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
dflags1 GeneralFlag
Opt_ExternalInterpreter
else DynFlags
dflags1
basename :: String
basename = String -> String
dropExtension String
input_fn
current_dir :: String
current_dir = String -> String
takeDirectory String
basename
old_paths :: IncludeSpecs
old_paths = DynFlags -> IncludeSpecs
includePaths DynFlags
dflags2
loadAsByteCode :: Bool
loadAsByteCode
| Just (Target TargetId
_ Bool
obj Maybe (InputFileBuffer, UTCTime)
_) <- ModSummary -> [Target] -> Maybe Target
findTarget ModSummary
summary (HscEnv -> [Target]
hsc_targets HscEnv
hsc_env0)
, Bool -> Bool
not Bool
obj
= Bool
True
| Bool
otherwise = Bool
False
(Backend
bcknd, DynFlags
dflags3)
| Bool
loadAsByteCode
= (Backend
Interpreter, DynFlags
dflags2 { backend :: Backend
backend = Backend
Interpreter })
| Bool
otherwise
= (DynFlags -> Backend
backend DynFlags
dflags, DynFlags
dflags2)
dflags :: DynFlags
dflags = DynFlags
dflags3 { includePaths :: IncludeSpecs
includePaths = IncludeSpecs -> [String] -> IncludeSpecs
addImplicitQuoteInclude IncludeSpecs
old_paths [String
current_dir] }
hsc_env :: HscEnv
hsc_env = HscEnv
hsc_env0 {hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags}
force_recomp :: Bool
force_recomp = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ForceRecomp DynFlags
dflags
source_modified :: SourceModified
source_modified
| Bool
force_recomp Bool -> Bool -> Bool
|| Bool
loadAsByteCode = SourceModified
SourceModified
| Bool
otherwise = SourceModified
source_modified0
always_do_basic_recompilation_check :: Bool
always_do_basic_recompilation_check = case Backend
bcknd of
Backend
Interpreter -> Bool
True
Backend
_ -> Bool
False
compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath
compileForeign :: HscEnv -> ForeignSrcLang -> String -> IO String
compileForeign HscEnv
_ ForeignSrcLang
RawObject String
object_file = String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
object_file
compileForeign HscEnv
hsc_env ForeignSrcLang
lang String
stub_c = do
let phase :: Phase
phase = case ForeignSrcLang
lang of
ForeignSrcLang
LangC -> Phase
Cc
ForeignSrcLang
LangCxx -> Phase
Ccxx
ForeignSrcLang
LangObjc -> Phase
Cobjc
ForeignSrcLang
LangObjcxx -> Phase
Cobjcxx
ForeignSrcLang
LangAsm -> Bool -> Phase
As Bool
True
#if __GLASGOW_HASKELL__ < 811
RawObject -> panic "compileForeign: should be unreachable"
#endif
(DynFlags
_, String
stub_o, Maybe ModIface
_) <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
StopLn HscEnv
hsc_env
(String
stub_c, Maybe InputFileBuffer
forall a. Maybe a
Nothing, PhasePlus -> Maybe PhasePlus
forall a. a -> Maybe a
Just (Phase -> PhasePlus
RealPhase Phase
phase))
Maybe String
forall a. Maybe a
Nothing (TempFileLifetime -> PipelineOutput
Temporary TempFileLifetime
TFL_GhcSession)
Maybe ModLocation
forall a. Maybe a
Nothing
[]
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
stub_o
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
compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO ()
compileEmptyStub :: DynFlags -> HscEnv -> String -> ModLocation -> ModuleName -> IO ()
compileEmptyStub DynFlags
dflags HscEnv
hsc_env String
basename ModLocation
location ModuleName
mod_name = do
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
String
empty_stub <- Logger
-> TmpFs -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
TFL_CurrentModule String
"c"
let home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
src :: SDoc
src = String -> SDoc
text String
"int" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit ModuleName
mod_name) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"= 0;"
String -> String -> IO ()
writeFile String
empty_stub (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (LabelStyle -> SDoc -> SDoc
pprCode LabelStyle
CStyle SDoc
src))
(DynFlags, String, Maybe ModIface)
_ <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
StopLn HscEnv
hsc_env
(String
empty_stub, Maybe InputFileBuffer
forall a. Maybe a
Nothing, Maybe PhasePlus
forall a. Maybe a
Nothing)
(String -> Maybe String
forall a. a -> Maybe a
Just String
basename)
PipelineOutput
Persistent
(ModLocation -> Maybe ModLocation
forall a. a -> Maybe a
Just ModLocation
location)
[]
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
link :: GhcLink
-> Logger
-> TmpFs
-> Hooks
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link :: GhcLink
-> Logger
-> TmpFs
-> Hooks
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link GhcLink
ghcLink Logger
logger TmpFs
tmpfs Hooks
hooks DynFlags
dflags UnitEnv
unit_env Bool
batch_attempt_linking HomePackageTable
hpt =
case Hooks
-> Maybe
(GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag)
linkHook Hooks
hooks of
Maybe
(GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag)
Nothing -> case GhcLink
ghcLink of
GhcLink
NoLink -> SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
GhcLink
LinkBinary -> Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link' Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env Bool
batch_attempt_linking HomePackageTable
hpt
GhcLink
LinkStaticLib -> Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link' Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env Bool
batch_attempt_linking HomePackageTable
hpt
GhcLink
LinkDynLib -> Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link' Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env Bool
batch_attempt_linking HomePackageTable
hpt
GhcLink
LinkInMemory
| PlatformMisc -> Bool
platformMisc_ghcWithInterpreter (PlatformMisc -> Bool) -> PlatformMisc -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> PlatformMisc
platformMisc DynFlags
dflags
->
SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
| Bool
otherwise
-> GhcLink -> IO SuccessFlag
forall a. GhcLink -> a
panicBadLink GhcLink
LinkInMemory
Just GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag
h -> GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag
h GhcLink
ghcLink DynFlags
dflags Bool
batch_attempt_linking HomePackageTable
hpt
panicBadLink :: GhcLink -> a
panicBadLink :: forall a. GhcLink -> a
panicBadLink GhcLink
other = String -> a
forall a. String -> a
panic (String
"link: GHC not built to link this way: " String -> String -> String
forall a. [a] -> [a] -> [a]
++
GhcLink -> String
forall a. Show a => a -> String
show GhcLink
other)
link' :: Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link' :: Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> HomePackageTable
-> IO SuccessFlag
link' Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env Bool
batch_attempt_linking HomePackageTable
hpt
| Bool
batch_attempt_linking
= do
let
staticLink :: Bool
staticLink = case DynFlags -> GhcLink
ghcLink DynFlags
dflags of
GhcLink
LinkStaticLib -> Bool
True
GhcLink
_ -> Bool
False
home_mod_infos :: [HomeModInfo]
home_mod_infos = HomePackageTable -> [HomeModInfo]
eltsHpt HomePackageTable
hpt
pkg_deps :: [UnitId]
pkg_deps = (HomeModInfo -> [UnitId]) -> [HomeModInfo] -> [UnitId]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((UnitId, Bool) -> UnitId) -> [(UnitId, Bool)] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (UnitId, Bool) -> UnitId
forall a b. (a, b) -> a
fst ([(UnitId, Bool)] -> [UnitId])
-> (HomeModInfo -> [(UnitId, Bool)]) -> HomeModInfo -> [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependencies -> [(UnitId, Bool)]
dep_pkgs (Dependencies -> [(UnitId, Bool)])
-> (HomeModInfo -> Dependencies) -> HomeModInfo -> [(UnitId, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps (ModIface -> Dependencies)
-> (HomeModInfo -> ModIface) -> HomeModInfo -> Dependencies
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModIface
hm_iface) [HomeModInfo]
home_mod_infos
linkables :: [Linkable]
linkables = (HomeModInfo -> Linkable) -> [HomeModInfo] -> [Linkable]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Maybe Linkable -> Linkable
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"link"(Maybe Linkable -> Linkable)
-> (HomeModInfo -> Maybe Linkable) -> HomeModInfo -> Linkable
forall b c a. (b -> c) -> (a -> b) -> a -> c
.HomeModInfo -> Maybe Linkable
hm_linkable) [HomeModInfo]
home_mod_infos
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
3 (String -> SDoc
text String
"link: linkables are ..." SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((Linkable -> SDoc) -> [Linkable] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Linkable -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Linkable]
linkables))
if GhcLink -> Bool
isNoLink (DynFlags -> GhcLink
ghcLink DynFlags
dflags)
then do Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
3 (String -> SDoc
text String
"link(batch): linking omitted (-c flag given).")
SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
else do
let getOfiles :: Linkable -> [String]
getOfiles (LM UTCTime
_ Module
_ [Unlinked]
us) = (Unlinked -> String) -> [Unlinked] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Unlinked -> String
nameOfObject ((Unlinked -> Bool) -> [Unlinked] -> [Unlinked]
forall a. (a -> Bool) -> [a] -> [a]
filter Unlinked -> Bool
isObject [Unlinked]
us)
obj_files :: [String]
obj_files = (Linkable -> [String]) -> [Linkable] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [String]
getOfiles [Linkable]
linkables
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
exe_file :: String
exe_file = Platform -> Bool -> Maybe String -> String
exeFileName Platform
platform Bool
staticLink (DynFlags -> Maybe String
outputFile DynFlags
dflags)
Bool
linking_needed <- Logger
-> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO Bool
linkingNeeded Logger
logger DynFlags
dflags UnitEnv
unit_env Bool
staticLink [Linkable]
linkables [UnitId]
pkg_deps
if Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ForceRecomp DynFlags
dflags) Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
linking_needed
then do Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2 (String -> SDoc
text String
exe_file SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is up to date, linking not required.")
SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
else do
Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg Logger
logger DynFlags
dflags (String -> SDoc
text String
"Linking " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
exe_file SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" ...")
let link :: DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
link = case DynFlags -> GhcLink
ghcLink DynFlags
dflags of
GhcLink
LinkBinary -> Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkBinary Logger
logger TmpFs
tmpfs
GhcLink
LinkStaticLib -> Logger -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkStaticLib Logger
logger
GhcLink
LinkDynLib -> Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLibCheck Logger
logger TmpFs
tmpfs
GhcLink
other -> GhcLink -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
forall a. GhcLink -> a
panicBadLink GhcLink
other
DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
link DynFlags
dflags UnitEnv
unit_env [String]
obj_files [UnitId]
pkg_deps
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
3 (String -> SDoc
text String
"link: done")
SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
| Bool
otherwise
= do Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
3 (String -> SDoc
text String
"link(batch): upsweep (partially) failed OR" SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
" Main.main not exported; not linking.")
SuccessFlag -> IO SuccessFlag
forall (m :: * -> *) a. Monad m => a -> m a
return SuccessFlag
Succeeded
linkingNeeded :: Logger -> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO Bool
linkingNeeded :: Logger
-> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO Bool
linkingNeeded Logger
logger DynFlags
dflags UnitEnv
unit_env Bool
staticLink [Linkable]
linkables [UnitId]
pkg_deps = do
let platform :: Platform
platform = UnitEnv -> Platform
ue_platform UnitEnv
unit_env
unit_state :: UnitState
unit_state = UnitEnv -> UnitState
ue_units UnitEnv
unit_env
exe_file :: String
exe_file = Platform -> Bool -> Maybe String -> String
exeFileName Platform
platform Bool
staticLink (DynFlags -> Maybe String
outputFile DynFlags
dflags)
Either IOException UTCTime
e_exe_time <- IO UTCTime -> IO (Either IOException UTCTime)
forall a. IO a -> IO (Either IOException a)
tryIO (IO UTCTime -> IO (Either IOException UTCTime))
-> IO UTCTime -> IO (Either IOException UTCTime)
forall a b. (a -> b) -> a -> b
$ String -> IO UTCTime
getModificationUTCTime String
exe_file
case Either IOException UTCTime
e_exe_time of
Left IOException
_ -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Right UTCTime
t -> do
let extra_ld_inputs :: [String]
extra_ld_inputs = [ String
f | FileOption String
_ String
f <- DynFlags -> [Option]
ldInputs DynFlags
dflags ]
[Either IOException UTCTime]
e_extra_times <- (String -> IO (Either IOException UTCTime))
-> [String] -> IO [Either IOException UTCTime]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (IO UTCTime -> IO (Either IOException UTCTime)
forall a. IO a -> IO (Either IOException a)
tryIO (IO UTCTime -> IO (Either IOException UTCTime))
-> (String -> IO UTCTime)
-> String
-> IO (Either IOException UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO UTCTime
getModificationUTCTime) [String]
extra_ld_inputs
let ([IOException]
errs,[UTCTime]
extra_times) = [Either IOException UTCTime] -> ([IOException], [UTCTime])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either IOException UTCTime]
e_extra_times
let obj_times :: [UTCTime]
obj_times = (Linkable -> UTCTime) -> [Linkable] -> [UTCTime]
forall a b. (a -> b) -> [a] -> [b]
map Linkable -> UTCTime
linkableTime [Linkable]
linkables [UTCTime] -> [UTCTime] -> [UTCTime]
forall a. [a] -> [a] -> [a]
++ [UTCTime]
extra_times
if Bool -> Bool
not ([IOException] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IOException]
errs) Bool -> Bool -> Bool
|| (UTCTime -> Bool) -> [UTCTime] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (UTCTime
t UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
<) [UTCTime]
obj_times
then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else do
let pkg_hslibs :: [([String], String)]
pkg_hslibs = [ (Set Way -> [UnitInfo] -> [String]
collectLibraryDirs (DynFlags -> Set Way
ways DynFlags
dflags) [UnitInfo
c], String
lib)
| Just UnitInfo
c <- (UnitId -> Maybe UnitInfo) -> [UnitId] -> [Maybe UnitInfo]
forall a b. (a -> b) -> [a] -> [b]
map (UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
unit_state) [UnitId]
pkg_deps,
String
lib <- GhcNameVersion -> Set Way -> UnitInfo -> [String]
unitHsLibs (DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags) (DynFlags -> Set Way
ways DynFlags
dflags) UnitInfo
c ]
[Maybe String]
pkg_libfiles <- (([String], String) -> IO (Maybe String))
-> [([String], String)] -> IO [Maybe String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (([String] -> String -> IO (Maybe String))
-> ([String], String) -> IO (Maybe String)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Platform -> Set Way -> [String] -> String -> IO (Maybe String)
findHSLib Platform
platform (DynFlags -> Set Way
ways DynFlags
dflags))) [([String], String)]
pkg_hslibs
if (Maybe String -> Bool) -> [Maybe String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing [Maybe String]
pkg_libfiles then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True else do
[Either IOException UTCTime]
e_lib_times <- (String -> IO (Either IOException UTCTime))
-> [String] -> IO [Either IOException UTCTime]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (IO UTCTime -> IO (Either IOException UTCTime)
forall a. IO a -> IO (Either IOException a)
tryIO (IO UTCTime -> IO (Either IOException UTCTime))
-> (String -> IO UTCTime)
-> String
-> IO (Either IOException UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO UTCTime
getModificationUTCTime)
([Maybe String] -> [String]
forall a. [Maybe a] -> [a]
catMaybes [Maybe String]
pkg_libfiles)
let ([IOException]
lib_errs,[UTCTime]
lib_times) = [Either IOException UTCTime] -> ([IOException], [UTCTime])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either IOException UTCTime]
e_lib_times
if Bool -> Bool
not ([IOException] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IOException]
lib_errs) Bool -> Bool -> Bool
|| (UTCTime -> Bool) -> [UTCTime] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (UTCTime
t UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
<) [UTCTime]
lib_times
then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else Logger -> DynFlags -> UnitEnv -> [UnitId] -> String -> IO Bool
checkLinkInfo Logger
logger DynFlags
dflags UnitEnv
unit_env [UnitId]
pkg_deps String
exe_file
findHSLib :: Platform -> Ways -> [String] -> String -> IO (Maybe FilePath)
findHSLib :: Platform -> Set Way -> [String] -> String -> IO (Maybe String)
findHSLib Platform
platform Set Way
ws [String]
dirs String
lib = do
let batch_lib_file :: String
batch_lib_file = if Way
WayDyn Way -> Set Way -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Set Way
ws
then String
"lib" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lib String -> String -> String
<.> String
"a"
else Platform -> String -> String
platformSOName Platform
platform String
lib
[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 -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
</> String
batch_lib_file) [String]
dirs)
case [String]
found of
[] -> Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
(String
x:[String]
_) -> Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
x)
oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO ()
oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO ()
oneShot HscEnv
hsc_env Phase
stop_phase [(String, Maybe Phase)]
srcs = do
[String]
o_files <- ((String, Maybe Phase) -> IO String)
-> [(String, Maybe Phase)] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (HscEnv -> Phase -> (String, Maybe Phase) -> IO String
compileFile HscEnv
hsc_env Phase
stop_phase) [(String, Maybe Phase)]
srcs
HscEnv -> Phase -> [String] -> IO ()
doLink HscEnv
hsc_env Phase
stop_phase [String]
o_files
compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
compileFile :: HscEnv -> Phase -> (String, Maybe Phase) -> IO String
compileFile HscEnv
hsc_env Phase
stop_phase (String
src, Maybe Phase
mb_phase) = do
Bool
exists <- String -> IO Bool
doesFileExist String
src
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
CmdLineError (String
"does not exist: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
src))
let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
mb_o_file :: Maybe String
mb_o_file = DynFlags -> Maybe String
outputFile DynFlags
dflags
ghc_link :: GhcLink
ghc_link = DynFlags -> GhcLink
ghcLink DynFlags
dflags
output :: PipelineOutput
output
| Backend
NoBackend <- DynFlags -> Backend
backend DynFlags
dflags = TempFileLifetime -> PipelineOutput
Temporary TempFileLifetime
TFL_CurrentModule
| Phase
StopLn <- Phase
stop_phase, Bool -> Bool
not (GhcLink -> Bool
isNoLink GhcLink
ghc_link) = PipelineOutput
Persistent
| Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mb_o_file = PipelineOutput
SpecificFile
| Bool
otherwise = PipelineOutput
Persistent
( DynFlags
_, String
out_file, Maybe ModIface
_) <- Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
stop_phase HscEnv
hsc_env
(String
src, Maybe InputFileBuffer
forall a. Maybe a
Nothing, (Phase -> PhasePlus) -> Maybe Phase -> Maybe PhasePlus
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Phase -> PhasePlus
RealPhase Maybe Phase
mb_phase)
Maybe String
forall a. Maybe a
Nothing
PipelineOutput
output
Maybe ModLocation
forall a. Maybe a
Nothing []
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
out_file
doLink :: HscEnv -> Phase -> [FilePath] -> IO ()
doLink :: HscEnv -> Phase -> [String] -> IO ()
doLink HscEnv
hsc_env Phase
stop_phase [String]
o_files
| Bool -> Bool
not (Phase -> Bool
isStopLn Phase
stop_phase)
= () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
unit_env :: UnitEnv
unit_env = HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env
tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
in case DynFlags -> GhcLink
ghcLink DynFlags
dflags of
GhcLink
NoLink -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
GhcLink
LinkBinary -> Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkBinary Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env [String]
o_files []
GhcLink
LinkStaticLib -> Logger -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkStaticLib Logger
logger DynFlags
dflags UnitEnv
unit_env [String]
o_files []
GhcLink
LinkDynLib -> Logger
-> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
linkDynLibCheck Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env [String]
o_files []
GhcLink
other -> GhcLink -> IO ()
forall a. GhcLink -> a
panicBadLink GhcLink
other
runPipeline
:: Phase
-> HscEnv
-> (FilePath, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe FilePath
-> PipelineOutput
-> Maybe ModLocation
-> [FilePath]
-> IO (DynFlags, FilePath, Maybe ModIface)
runPipeline :: Phase
-> HscEnv
-> (String, Maybe InputFileBuffer, Maybe PhasePlus)
-> Maybe String
-> PipelineOutput
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline Phase
stop_phase HscEnv
hsc_env0 (String
input_fn, Maybe InputFileBuffer
mb_input_buf, Maybe PhasePlus
mb_phase)
Maybe String
mb_basename PipelineOutput
output Maybe ModLocation
maybe_loc [String]
foreign_os
= do let
dflags0 :: DynFlags
dflags0 = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env0
dflags :: DynFlags
dflags = DynFlags
dflags0 { dumpPrefix :: Maybe String
dumpPrefix = String -> Maybe String
forall a. a -> Maybe a
Just (String
basename String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".") }
hsc_env :: HscEnv
hsc_env = HscEnv
hsc_env0 {hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags}
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
(String
input_basename, String
suffix) = String -> (String, String)
splitExtension String
input_fn
suffix' :: String
suffix' = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 String
suffix
basename :: String
basename | Just String
b <- Maybe String
mb_basename = String
b
| Bool
otherwise = String
input_basename
start_phase :: PhasePlus
start_phase = PhasePlus -> Maybe PhasePlus -> PhasePlus
forall a. a -> Maybe a -> a
fromMaybe (Phase -> PhasePlus
RealPhase (String -> Phase
startPhase String
suffix')) Maybe PhasePlus
mb_phase
isHaskell :: PhasePlus -> Bool
isHaskell (RealPhase (Unlit HscSource
_)) = Bool
True
isHaskell (RealPhase (Cpp HscSource
_)) = Bool
True
isHaskell (RealPhase (HsPp HscSource
_)) = Bool
True
isHaskell (RealPhase (Hsc HscSource
_)) = Bool
True
isHaskell (HscOut {}) = Bool
True
isHaskell PhasePlus
_ = Bool
False
isHaskellishFile :: Bool
isHaskellishFile = PhasePlus -> Bool
isHaskell PhasePlus
start_phase
env :: PipeEnv
env = PipeEnv{ Phase
stop_phase :: Phase
stop_phase :: Phase
stop_phase,
src_filename :: String
src_filename = String
input_fn,
src_basename :: String
src_basename = String
basename,
src_suffix :: String
src_suffix = String
suffix',
output_spec :: PipelineOutput
output_spec = PipelineOutput
output }
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String -> Bool
isBackpackishSuffix String
suffix') (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
UsageError
(String
"use --backpack to process " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
input_fn))
let happensBefore' :: Phase -> Phase -> Bool
happensBefore' = Platform -> Phase -> Phase -> Bool
happensBefore (DynFlags -> Platform
targetPlatform DynFlags
dflags)
case PhasePlus
start_phase of
RealPhase Phase
start_phase' ->
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Phase
start_phase' Phase -> Phase -> Bool
`happensBefore'` Phase
stop_phase Bool -> Bool -> Bool
||
Phase
start_phase' Phase -> Phase -> Bool
`eqPhase` Phase
stop_phase)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
UsageError
(String
"cannot compile this file to desired target: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
input_fn))
HscOut {} -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
String
input_fn' <- case (PhasePlus
start_phase, Maybe InputFileBuffer
mb_input_buf) of
(RealPhase Phase
real_start_phase, Just InputFileBuffer
input_buf) -> do
let suffix :: String
suffix = Phase -> String
phaseInputExt Phase
real_start_phase
String
fn <- Logger
-> TmpFs -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
TFL_CurrentModule String
suffix
Handle
hdl <- String -> IOMode -> IO Handle
openBinaryFile String
fn IOMode
WriteMode
Handle -> String -> IO ()
hPutStrLn Handle
hdl (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"{-# LINE 1 \""String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
input_fn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\"#-}"
Handle -> InputFileBuffer -> IO ()
hPutStringBuffer Handle
hdl InputFileBuffer
input_buf
Handle -> IO ()
hClose Handle
hdl
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
fn
(PhasePlus
_, Maybe InputFileBuffer
_) -> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
input_fn
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
4 (String -> SDoc
text String
"Running the pipeline")
(DynFlags, String, Maybe ModIface)
r <- PhasePlus
-> HscEnv
-> PipeEnv
-> String
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline' PhasePlus
start_phase HscEnv
hsc_env PipeEnv
env String
input_fn'
Maybe ModLocation
maybe_loc [String]
foreign_os
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isHaskellishFile (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> IO DynamicTooState
forall (m :: * -> *). MonadIO m => DynFlags -> m DynamicTooState
dynamicTooState DynFlags
dflags IO DynamicTooState -> (DynamicTooState -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
DynamicTooState
DT_Dont -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
DynamicTooState
DT_Dyn -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
DynamicTooState
DT_OK -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
DynamicTooState
DT_Failed
| OS
OSMinGW32 <- Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags) -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise -> do
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
4
(String -> SDoc
text String
"Running the full pipeline again for -dynamic-too")
let dflags0 :: DynFlags
dflags0 = (DynFlags -> GeneralFlag -> DynFlags)
-> GeneralFlag -> DynFlags -> DynFlags
forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> GeneralFlag -> DynFlags
gopt_unset GeneralFlag
Opt_BuildDynamicToo
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> DynFlags
setDynamicNow
(DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags
dflags
HscEnv
hsc_env' <- DynFlags -> IO HscEnv
newHscEnv DynFlags
dflags0
([UnitDatabase UnitId]
dbs,UnitState
unit_state,HomeUnit
home_unit,Maybe PlatformConstants
mconstants) <- Logger
-> DynFlags
-> Maybe [UnitDatabase UnitId]
-> IO
([UnitDatabase UnitId], UnitState, HomeUnit,
Maybe PlatformConstants)
initUnits Logger
logger DynFlags
dflags0 Maybe [UnitDatabase UnitId]
forall a. Maybe a
Nothing
DynFlags
dflags1 <- DynFlags -> Maybe PlatformConstants -> IO DynFlags
updatePlatformConstants DynFlags
dflags0 Maybe PlatformConstants
mconstants
let unit_env :: UnitEnv
unit_env = UnitEnv
{ ue_platform :: Platform
ue_platform = DynFlags -> Platform
targetPlatform DynFlags
dflags1
, ue_namever :: GhcNameVersion
ue_namever = DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags1
, ue_home_unit :: HomeUnit
ue_home_unit = HomeUnit
home_unit
, ue_units :: UnitState
ue_units = UnitState
unit_state
}
let hsc_env'' :: HscEnv
hsc_env'' = HscEnv
hsc_env'
{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags1
, hsc_unit_env :: UnitEnv
hsc_unit_env = UnitEnv
unit_env
, hsc_unit_dbs :: Maybe [UnitDatabase UnitId]
hsc_unit_dbs = [UnitDatabase UnitId] -> Maybe [UnitDatabase UnitId]
forall a. a -> Maybe a
Just [UnitDatabase UnitId]
dbs
}
(DynFlags, String, Maybe ModIface)
_ <- PhasePlus
-> HscEnv
-> PipeEnv
-> String
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline' PhasePlus
start_phase HscEnv
hsc_env'' PipeEnv
env String
input_fn'
Maybe ModLocation
maybe_loc [String]
foreign_os
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(DynFlags, String, Maybe ModIface)
-> IO (DynFlags, String, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags, String, Maybe ModIface)
r
runPipeline'
:: PhasePlus
-> HscEnv
-> PipeEnv
-> FilePath
-> Maybe ModLocation
-> [FilePath]
-> IO (DynFlags, FilePath, Maybe ModIface)
runPipeline' :: PhasePlus
-> HscEnv
-> PipeEnv
-> String
-> Maybe ModLocation
-> [String]
-> IO (DynFlags, String, Maybe ModIface)
runPipeline' PhasePlus
start_phase HscEnv
hsc_env PipeEnv
env String
input_fn
Maybe ModLocation
maybe_loc [String]
foreign_os
= do
let state :: PipeState
state = PipeState{ HscEnv
hsc_env :: HscEnv
hsc_env :: HscEnv
hsc_env, Maybe ModLocation
maybe_loc :: Maybe ModLocation
maybe_loc :: Maybe ModLocation
maybe_loc, foreign_os :: [String]
foreign_os = [String]
foreign_os, iface :: Maybe ModIface
iface = Maybe ModIface
forall a. Maybe a
Nothing }
(PipeState
pipe_state, String
fp) <- CompPipeline String
-> PipeEnv -> PipeState -> IO (PipeState, String)
forall a.
CompPipeline a -> PipeEnv -> PipeState -> IO (PipeState, a)
evalP (PhasePlus -> String -> CompPipeline String
pipeLoop PhasePlus
start_phase String
input_fn) PipeEnv
env PipeState
state
(DynFlags, String, Maybe ModIface)
-> IO (DynFlags, String, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (PipeState -> DynFlags
pipeStateDynFlags PipeState
pipe_state, String
fp, PipeState -> Maybe ModIface
pipeStateModIface PipeState
pipe_state)
pipeLoop :: PhasePlus -> FilePath -> CompPipeline FilePath
pipeLoop :: PhasePlus -> String -> CompPipeline String
pipeLoop PhasePlus
phase String
input_fn = do
PipeEnv
env <- CompPipeline PipeEnv
getPipeEnv
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
let happensBefore' :: Phase -> Phase -> Bool
happensBefore' = Platform -> Phase -> Phase -> Bool
happensBefore (DynFlags -> Platform
targetPlatform DynFlags
dflags)
stopPhase :: Phase
stopPhase = PipeEnv -> Phase
stop_phase PipeEnv
env
case PhasePlus
phase of
RealPhase Phase
realPhase | Phase
realPhase Phase -> Phase -> Bool
`eqPhase` Phase
stopPhase
->
case PipeEnv -> PipelineOutput
output_spec PipeEnv
env of
Temporary TempFileLifetime
_ ->
String -> CompPipeline String
forall (m :: * -> *) a. Monad m => a -> m a
return String
input_fn
PipelineOutput
output ->
do PipeState
pst <- CompPipeline PipeState
getPipeState
TmpFs
tmpfs <- HscEnv -> TmpFs
hsc_tmpfs (HscEnv -> TmpFs) -> CompPipeline HscEnv -> CompPipeline TmpFs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompPipeline HscEnv
getPipeSession
String
final_fn <- IO String -> CompPipeline String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> CompPipeline String)
-> IO String -> CompPipeline String
forall a b. (a -> b) -> a -> b
$ Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs
Phase
stopPhase PipelineOutput
output (PipeEnv -> String
src_basename PipeEnv
env)
DynFlags
dflags Phase
stopPhase (PipeState -> Maybe ModLocation
maybe_loc PipeState
pst)
Bool -> CompPipeline () -> CompPipeline ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
final_fn String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
input_fn) (CompPipeline () -> CompPipeline ())
-> CompPipeline () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ do
let msg :: String
msg = (String
"Copying `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
input_fn String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"' to `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
final_fn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'")
line_prag :: Maybe String
line_prag = String -> Maybe String
forall a. a -> Maybe a
Just (String
"{-# LINE 1 \"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ PipeEnv -> String
src_filename PipeEnv
env String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\" #-}\n")
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger
-> DynFlags -> String -> Maybe String -> String -> String -> IO ()
copyWithHeader Logger
logger DynFlags
dflags String
msg Maybe String
line_prag String
input_fn String
final_fn
String -> CompPipeline String
forall (m :: * -> *) a. Monad m => a -> m a
return String
final_fn
| Bool -> Bool
not (Phase
realPhase Phase -> Phase -> Bool
`happensBefore'` Phase
stopPhase)
-> String -> CompPipeline String
forall a. String -> a
panic (String
"pipeLoop: at phase " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Phase -> String
forall a. Show a => a -> String
show Phase
realPhase String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" but I wanted to stop at phase " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Phase -> String
forall a. Show a => a -> String
show Phase
stopPhase)
PhasePlus
_
-> do IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
4
(String -> SDoc
text String
"Running phase" SDoc -> SDoc -> SDoc
<+> PhasePlus -> SDoc
forall a. Outputable a => a -> SDoc
ppr PhasePlus
phase)
case PhasePlus
phase of
HscOut {} -> do
let noDynToo :: CompPipeline String
noDynToo = do
(PhasePlus
next_phase, String
output_fn) <- PhasePlus -> String -> CompPipeline (PhasePlus, String)
runHookedPhase PhasePlus
phase String
input_fn
PhasePlus -> String -> CompPipeline String
pipeLoop PhasePlus
next_phase String
output_fn
let dynToo :: CompPipeline String
dynToo = do
String
r <- CompPipeline String
noDynToo
DynFlags -> CompPipeline DynamicTooState
forall (m :: * -> *). MonadIO m => DynFlags -> m DynamicTooState
dynamicTooState DynFlags
dflags CompPipeline DynamicTooState
-> (DynamicTooState -> CompPipeline String) -> CompPipeline String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
DynamicTooState
DT_OK -> do
let dflags' :: DynFlags
dflags' = DynFlags -> DynFlags
setDynamicNow DynFlags
dflags
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags'
(PhasePlus
next_phase, String
output_fn) <- PhasePlus -> String -> CompPipeline (PhasePlus, String)
runHookedPhase PhasePlus
phase String
input_fn
String
_ <- PhasePlus -> String -> CompPipeline String
pipeLoop PhasePlus
next_phase String
output_fn
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags
String -> CompPipeline String
forall (m :: * -> *) a. Monad m => a -> m a
return String
r
DynamicTooState
_ -> String -> CompPipeline String
forall (m :: * -> *) a. Monad m => a -> m a
return String
r
DynFlags -> CompPipeline DynamicTooState
forall (m :: * -> *). MonadIO m => DynFlags -> m DynamicTooState
dynamicTooState DynFlags
dflags CompPipeline DynamicTooState
-> (DynamicTooState -> CompPipeline String) -> CompPipeline String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
DynamicTooState
DT_Dont -> CompPipeline String
noDynToo
DynamicTooState
DT_Failed -> CompPipeline String
noDynToo
DynamicTooState
DT_OK -> CompPipeline String
dynToo
DynamicTooState
DT_Dyn -> CompPipeline String
noDynToo
PhasePlus
_ -> do
(PhasePlus
next_phase, String
output_fn) <- PhasePlus -> String -> CompPipeline (PhasePlus, String)
runHookedPhase PhasePlus
phase String
input_fn
PhasePlus -> String -> CompPipeline String
pipeLoop PhasePlus
next_phase String
output_fn
runHookedPhase :: PhasePlus -> FilePath -> CompPipeline (PhasePlus, FilePath)
runHookedPhase :: PhasePlus -> String -> CompPipeline (PhasePlus, String)
runHookedPhase PhasePlus
pp String
input = do
Hooks
hooks <- HscEnv -> Hooks
hsc_hooks (HscEnv -> Hooks) -> CompPipeline HscEnv -> CompPipeline Hooks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompPipeline HscEnv
getPipeSession
case Hooks
-> Maybe (PhasePlus -> String -> CompPipeline (PhasePlus, String))
runPhaseHook Hooks
hooks of
Maybe (PhasePlus -> String -> CompPipeline (PhasePlus, String))
Nothing -> PhasePlus -> String -> CompPipeline (PhasePlus, String)
runPhase PhasePlus
pp String
input
Just PhasePlus -> String -> CompPipeline (PhasePlus, String)
h -> PhasePlus -> String -> CompPipeline (PhasePlus, String)
h PhasePlus
pp String
input
phaseOutputFilename :: Phase -> CompPipeline FilePath
phaseOutputFilename :: Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase = do
PipeEnv{Phase
stop_phase :: Phase
stop_phase :: PipeEnv -> Phase
stop_phase, String
src_basename :: String
src_basename :: PipeEnv -> String
src_basename, PipelineOutput
output_spec :: PipelineOutput
output_spec :: PipeEnv -> PipelineOutput
output_spec} <- CompPipeline PipeEnv
getPipeEnv
PipeState{Maybe ModLocation
maybe_loc :: Maybe ModLocation
maybe_loc :: PipeState -> Maybe ModLocation
maybe_loc,HscEnv
hsc_env :: HscEnv
hsc_env :: PipeState -> HscEnv
hsc_env} <- CompPipeline PipeState
getPipeState
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
IO String -> CompPipeline String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> CompPipeline String)
-> IO String -> CompPipeline String
forall a b. (a -> b) -> a -> b
$ Logger
-> TmpFs
-> Phase
-> PipelineOutput
-> String
-> DynFlags
-> Phase
-> Maybe ModLocation
-> IO String
getOutputFilename Logger
logger TmpFs
tmpfs Phase
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
| Bool
is_last_phase, PipelineOutput
Persistent <- PipelineOutput
output = IO String
persistent_fn
| Bool
is_last_phase, PipelineOutput
SpecificFile <- PipelineOutput
output = case DynFlags -> Maybe String
outputFile DynFlags
dflags of
Just String
f -> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
f
Maybe String
Nothing ->
String -> IO String
forall a. String -> a
panic String
"SpecificFile: No filename"
| Bool
keep_this_output = IO String
persistent_fn
| Temporary TempFileLifetime
lifetime <- PipelineOutput
output = Logger
-> TmpFs -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
lifetime String
suffix
| Bool
otherwise = Logger
-> TmpFs -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
TFL_CurrentModule
String
suffix
where
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 (m :: * -> *) a. Monad m => a -> m a
return String
odir_persistent
| Bool
otherwise = String -> IO String
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 ModLocation
loc <- Maybe ModLocation
maybe_location = ModLocation -> String
ml_obj_file ModLocation
loc
| Just String
d <- Maybe String
odir = String
d String -> String -> String
</> String
persistent
| Bool
otherwise = String
persistent
llvmOptions :: DynFlags
-> [(String, String)]
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 (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 (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 (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 (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)
rmodel :: String
rmodel | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PIC DynFlags
dflags = String
"pic"
| DynFlags -> Bool
positionIndependent DynFlags
dflags = String
"pic"
| Way
WayDyn Way -> Set Way -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DynFlags -> Set Way
ways DynFlags
dflags = 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
""
runPhase :: PhasePlus
-> FilePath
-> CompPipeline (PhasePlus,
FilePath)
runPhase :: PhasePlus -> String -> CompPipeline (PhasePlus, String)
runPhase (RealPhase (Unlit HscSource
sf)) String
input_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 [] = []
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename (HscSource -> Phase
Cpp HscSource
sf)
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
]
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runUnlit Logger
logger DynFlags
dflags [Option]
flags
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase (HscSource -> Phase
Cpp HscSource
sf), String
output_fn)
runPhase (RealPhase (Cpp HscSource
sf)) String
input_fn
= do
DynFlags
dflags0 <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
[Located String]
src_opts <- IO [Located String] -> CompPipeline [Located String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Located String] -> CompPipeline [Located String])
-> IO [Located String] -> CompPipeline [Located String]
forall a b. (a -> b) -> a -> b
$ DynFlags -> String -> IO [Located String]
getOptionsFromFile DynFlags
dflags0 String
input_fn
(DynFlags
dflags1, [Located String]
unhandled_flags, [Warn]
warns)
<- IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn]))
-> IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall a b. (a -> b) -> a -> b
$ 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
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags1
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ [Located String] -> IO ()
forall (m :: * -> *). MonadIO m => [Located String] -> m ()
checkProcessArgsResult [Located String]
unhandled_flags
if Bool -> Bool
not (Extension -> DynFlags -> Bool
xopt Extension
LangExt.Cpp DynFlags
dflags1) then do
Bool -> CompPipeline () -> CompPipeline ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Pp DynFlags
dflags1) (CompPipeline () -> CompPipeline ())
-> CompPipeline () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Warn] -> IO ()
handleFlagWarnings Logger
logger DynFlags
dflags1 [Warn]
warns
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase (HscSource -> Phase
HsPp HscSource
sf), String
input_fn)
else do
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename (HscSource -> Phase
HsPp HscSource
sf)
HscEnv
hsc_env <- CompPipeline HscEnv
getPipeSession
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> String
-> String
-> IO ()
doCpp Logger
logger
(HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env)
(HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
(HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
Bool
True
String
input_fn String
output_fn
[Located String]
src_opts <- IO [Located String] -> CompPipeline [Located String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Located String] -> CompPipeline [Located String])
-> IO [Located String] -> CompPipeline [Located String]
forall a b. (a -> b) -> a -> b
$ DynFlags -> String -> IO [Located String]
getOptionsFromFile DynFlags
dflags0 String
output_fn
(DynFlags
dflags2, [Located String]
unhandled_flags, [Warn]
warns)
<- IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn]))
-> IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall a b. (a -> b) -> a -> b
$ 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
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ [Located String] -> IO ()
forall (m :: * -> *). MonadIO m => [Located String] -> m ()
checkProcessArgsResult [Located String]
unhandled_flags
Bool -> CompPipeline () -> CompPipeline ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Pp DynFlags
dflags2) (CompPipeline () -> CompPipeline ())
-> CompPipeline () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Warn] -> IO ()
handleFlagWarnings Logger
logger DynFlags
dflags2 [Warn]
warns
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags2
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase (HscSource -> Phase
HsPp HscSource
sf), String
output_fn)
runPhase (RealPhase (HsPp HscSource
sf)) String
input_fn = do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
if Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Pp DynFlags
dflags) then
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase (HscSource -> Phase
Hsc HscSource
sf), String
input_fn)
else do
PipeEnv{String
src_basename :: String
src_basename :: PipeEnv -> String
src_basename, String
src_suffix :: String
src_suffix :: PipeEnv -> String
src_suffix} <- CompPipeline PipeEnv
getPipeEnv
let orig_fn :: String
orig_fn = String
src_basename String -> String -> String
<.> String
src_suffix
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename (HscSource -> Phase
Hsc HscSource
sf)
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ 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
]
)
[Located String]
src_opts <- IO [Located String] -> CompPipeline [Located String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Located String] -> CompPipeline [Located String])
-> IO [Located String] -> CompPipeline [Located String]
forall a b. (a -> b) -> a -> b
$ DynFlags -> String -> IO [Located String]
getOptionsFromFile DynFlags
dflags String
output_fn
(DynFlags
dflags1, [Located String]
unhandled_flags, [Warn]
warns)
<- IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn]))
-> IO (DynFlags, [Located String], [Warn])
-> CompPipeline (DynFlags, [Located String], [Warn])
forall a b. (a -> b) -> a -> b
$ DynFlags
-> [Located String] -> IO (DynFlags, [Located String], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located String] -> m (DynFlags, [Located String], [Warn])
parseDynamicFilePragma DynFlags
dflags [Located String]
src_opts
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags1
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ [Located String] -> IO ()
forall (m :: * -> *). MonadIO m => [Located String] -> m ()
checkProcessArgsResult [Located String]
unhandled_flags
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Warn] -> IO ()
handleFlagWarnings Logger
logger DynFlags
dflags1 [Warn]
warns
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase (HscSource -> Phase
Hsc HscSource
sf), String
output_fn)
runPhase (RealPhase (Hsc HscSource
src_flavour)) String
input_fn
= do
DynFlags
dflags0 <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
PipeEnv{ stop_phase :: PipeEnv -> Phase
stop_phase=Phase
stop,
src_basename :: PipeEnv -> String
src_basename=String
basename,
src_suffix :: PipeEnv -> String
src_suffix=String
suff } <- CompPipeline PipeEnv
getPipeEnv
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 }
DynFlags -> CompPipeline ()
setDynFlags DynFlags
dflags
(Maybe InputFileBuffer
hspp_buf,ModuleName
mod_name,[(Maybe FastString, Located ModuleName)]
imps,[(Maybe FastString, Located ModuleName)]
src_imps) <- IO
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
-> CompPipeline
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
-> CompPipeline
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)]))
-> IO
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
-> CompPipeline
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
forall a b. (a -> b) -> a -> b
$ do
InputFileBuffer
buf <- String -> IO InputFileBuffer
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
Either
(Bag PsError)
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
eimps <- ParserOpts
-> Bool
-> InputFileBuffer
-> String
-> String
-> IO
(Either
(Bag PsError)
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
getImports ParserOpts
popts Bool
imp_prelude InputFileBuffer
buf String
input_fn (String
basename String -> String -> String
<.> String
suff)
case Either
(Bag PsError)
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
eimps of
Left Bag PsError
errs -> ErrorMessages
-> IO
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
forall (io :: * -> *) a. MonadIO io => ErrorMessages -> io a
throwErrors ((PsError -> MsgEnvelope DecoratedSDoc)
-> Bag PsError -> ErrorMessages
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> MsgEnvelope DecoratedSDoc
pprError Bag PsError
errs)
Right ([(Maybe FastString, Located ModuleName)]
src_imps,[(Maybe FastString, Located ModuleName)]
imps,L SrcSpan
_ ModuleName
mod_name) -> (Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
-> IO
(Maybe InputFileBuffer, ModuleName,
[(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)])
forall (m :: * -> *) a. Monad m => a -> m a
return
(InputFileBuffer -> Maybe InputFileBuffer
forall a. a -> Maybe a
Just InputFileBuffer
buf, ModuleName
mod_name, [(Maybe FastString, Located ModuleName)]
imps, [(Maybe FastString, Located ModuleName)]
src_imps)
ModLocation
location <- HscSource -> ModuleName -> CompPipeline ModLocation
getLocation 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
dest_file :: String
dest_file | DynFlags -> Bool
writeInterfaceOnlyMode DynFlags
dflags
= String
hi_file
| Bool
otherwise
= String
o_file
UTCTime
src_timestamp <- IO UTCTime -> CompPipeline UTCTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UTCTime -> CompPipeline UTCTime)
-> IO UTCTime -> CompPipeline UTCTime
forall a b. (a -> b) -> a -> b
$ String -> IO UTCTime
getModificationUTCTime (String
basename String -> String -> String
<.> String
suff)
SourceModified
source_unchanged <- IO SourceModified -> CompPipeline SourceModified
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SourceModified -> CompPipeline SourceModified)
-> IO SourceModified -> CompPipeline SourceModified
forall a b. (a -> b) -> a -> b
$
if Bool -> Bool
not (Phase -> Bool
isStopLn Phase
stop)
then SourceModified -> IO SourceModified
forall (m :: * -> *) a. Monad m => a -> m a
return SourceModified
SourceModified
else do Bool
dest_file_mod <- String -> UTCTime -> IO Bool
sourceModified String
dest_file UTCTime
src_timestamp
Bool
hie_file_mod <- if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_WriteHie DynFlags
dflags
then String -> UTCTime -> IO Bool
sourceModified String
hie_file
UTCTime
src_timestamp
else Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
if Bool
dest_file_mod Bool -> Bool -> Bool
|| Bool
hie_file_mod
then SourceModified -> IO SourceModified
forall (m :: * -> *) a. Monad m => a -> m a
return SourceModified
SourceModified
else SourceModified -> IO SourceModified
forall (m :: * -> *) a. Monad m => a -> m a
return SourceModified
SourceUnmodified
PipeState{hsc_env :: PipeState -> HscEnv
hsc_env=HscEnv
hsc_env'} <- CompPipeline PipeState
getPipeState
Module
mod <- IO Module -> CompPipeline Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Module -> CompPipeline Module)
-> IO Module -> CompPipeline Module
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder HscEnv
hsc_env' 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 InputFileBuffer
ms_hspp_buf = Maybe InputFileBuffer
hspp_buf,
ms_location :: ModLocation
ms_location = ModLocation
location,
ms_hs_date :: UTCTime
ms_hs_date = UTCTime
src_timestamp,
ms_obj_date :: Maybe UTCTime
ms_obj_date = Maybe UTCTime
forall a. Maybe a
Nothing,
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
forall a. Maybe a
Nothing,
ms_hie_date :: Maybe UTCTime
ms_hie_date = Maybe UTCTime
forall a. Maybe a
Nothing,
ms_textual_imps :: [(Maybe FastString, Located ModuleName)]
ms_textual_imps = [(Maybe FastString, Located ModuleName)]
imps,
ms_srcimps :: [(Maybe FastString, Located ModuleName)]
ms_srcimps = [(Maybe FastString, Located ModuleName)]
src_imps }
let msg :: HscEnv -> p -> RecompileRequired -> p -> IO ()
msg HscEnv
hsc_env p
_ RecompileRequired
what p
_ = HscEnv -> RecompileRequired -> IO ()
oneShotMsg HscEnv
hsc_env RecompileRequired
what
(HscStatus
result, HscEnv
plugin_hsc_env) <-
IO (HscStatus, HscEnv) -> CompPipeline (HscStatus, HscEnv)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (HscStatus, HscEnv) -> CompPipeline (HscStatus, HscEnv))
-> IO (HscStatus, HscEnv) -> CompPipeline (HscStatus, HscEnv)
forall a b. (a -> b) -> a -> b
$ Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int, Int)
-> IO (HscStatus, HscEnv)
hscIncrementalCompile Bool
True Maybe TcGblEnv
forall a. Maybe a
Nothing (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
forall {p} {p}. HscEnv -> p -> RecompileRequired -> p -> IO ()
msg) HscEnv
hsc_env'
ModSummary
mod_summary SourceModified
source_unchanged Maybe ModIface
forall a. Maybe a
Nothing (Int
1,Int
1)
[LoadedPlugin] -> [StaticPlugin] -> CompPipeline ()
setPlugins (HscEnv -> [LoadedPlugin]
hsc_plugins HscEnv
plugin_hsc_env)
(HscEnv -> [StaticPlugin]
hsc_static_plugins HscEnv
plugin_hsc_env)
DynFlags -> CompPipeline ()
setDynFlags (HscEnv -> DynFlags
hsc_dflags HscEnv
plugin_hsc_env)
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (HscSource -> ModuleName -> HscStatus -> PhasePlus
HscOut HscSource
src_flavour ModuleName
mod_name HscStatus
result,
String -> String
forall a. String -> a
panic String
"HscOut doesn't have an input filename")
runPhase (HscOut HscSource
src_flavour ModuleName
mod_name HscStatus
result) String
_ = do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
ModLocation
location <- HscSource -> ModuleName -> CompPipeline ModLocation
getLocation HscSource
src_flavour ModuleName
mod_name
ModLocation -> CompPipeline ()
setModLocation ModLocation
location
let o_file :: String
o_file = 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 HscStatus
result of
HscNotGeneratingCode ModIface
_ ModDetails
_ ->
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
StopLn,
String -> String
forall a. String -> a
panic String
"No output filename from Hsc when no-code")
HscUpToDate ModIface
_ ModDetails
_ ->
do IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
o_file
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
StopLn, String
o_file)
HscUpdateBoot ModIface
_ ModDetails
_ ->
do
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> String -> IO ()
touchObjectFile Logger
logger DynFlags
dflags String
o_file
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
StopLn, String
o_file)
HscUpdateSig ModIface
_ ModDetails
_ ->
do
PipeState{hsc_env :: PipeState -> HscEnv
hsc_env=HscEnv
hsc_env'} <- CompPipeline PipeState
getPipeState
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
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> HscEnv -> String -> ModLocation -> ModuleName -> IO ()
compileEmptyStub DynFlags
dflags HscEnv
hsc_env' String
basename ModLocation
location ModuleName
mod_name
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
StopLn, String
o_file)
HscRecomp { hscs_guts :: HscStatus -> CgGuts
hscs_guts = CgGuts
cgguts,
hscs_mod_location :: HscStatus -> ModLocation
hscs_mod_location = ModLocation
mod_location,
hscs_partial_iface :: HscStatus -> PartialModIface
hscs_partial_iface = PartialModIface
partial_iface,
hscs_old_iface_hash :: HscStatus -> Maybe Fingerprint
hscs_old_iface_hash = Maybe Fingerprint
mb_old_iface_hash
}
-> do String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase
PipeState{hsc_env :: PipeState -> HscEnv
hsc_env=HscEnv
hsc_env'} <- CompPipeline PipeState
getPipeState
(String
outputFilename, Maybe String
mStub, [(ForeignSrcLang, String)]
foreign_files, CgInfos
cg_infos) <- IO (String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
-> CompPipeline
(String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
-> CompPipeline
(String, Maybe String, [(ForeignSrcLang, String)], CgInfos))
-> IO (String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
-> CompPipeline
(String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
forall a b. (a -> b) -> a -> b
$
HscEnv
-> CgGuts
-> ModLocation
-> String
-> IO (String, Maybe String, [(ForeignSrcLang, String)], CgInfos)
hscGenHardCode HscEnv
hsc_env' CgGuts
cgguts ModLocation
mod_location String
output_fn
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env'
ModIface
final_iface <- IO ModIface -> CompPipeline ModIface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (HscEnv -> PartialModIface -> Maybe CgInfos -> IO ModIface
mkFullIface HscEnv
hsc_env' PartialModIface
partial_iface (CgInfos -> Maybe CgInfos
forall a. a -> Maybe a
Just CgInfos
cg_infos))
ModIface -> CompPipeline ()
setIface ModIface
final_iface
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ 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 <- IO (Maybe String) -> CompPipeline (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((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)
mapM (HscEnv -> String -> IO String
compileStub HscEnv
hsc_env') Maybe String
mStub)
[String]
foreign_os <- IO [String] -> CompPipeline [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [String] -> CompPipeline [String])
-> IO [String] -> CompPipeline [String]
forall a b. (a -> b) -> a -> b
$
((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)
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
[String] -> CompPipeline ()
setForeignOs ([String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
stub_o [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
foreign_os)
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
outputFilename)
runPhase (RealPhase Phase
CmmCpp) String
input_fn = do
HscEnv
hsc_env <- CompPipeline HscEnv
getPipeSession
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
Cmm
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> Bool
-> String
-> String
-> IO ()
doCpp Logger
logger
(HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env)
(HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
(HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
Bool
False
String
input_fn String
output_fn
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
Cmm, String
output_fn)
runPhase (RealPhase Phase
Cmm) String
input_fn = do
HscEnv
hsc_env <- CompPipeline HscEnv
getPipeSession
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 -> CompPipeline String
phaseOutputFilename Phase
next_phase
PipeState{HscEnv
hsc_env :: HscEnv
hsc_env :: PipeState -> HscEnv
hsc_env} <- CompPipeline PipeState
getPipeState
Maybe String
mstub <- IO (Maybe String) -> CompPipeline (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> CompPipeline (Maybe String))
-> IO (Maybe String) -> CompPipeline (Maybe String)
forall a b. (a -> b) -> a -> b
$ HscEnv -> String -> String -> IO (Maybe String)
hscCompileCmmFile HscEnv
hsc_env String
input_fn String
output_fn
Maybe String
stub_o <- IO (Maybe String) -> CompPipeline (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((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)
mapM (HscEnv -> String -> IO String
compileStub HscEnv
hsc_env) Maybe String
mstub)
[String] -> CompPipeline ()
setForeignOs (Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
stub_o)
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
output_fn)
runPhase (RealPhase Phase
cc_phase) String
input_fn
| (Phase -> Bool) -> [Phase] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Phase
cc_phase Phase -> Phase -> Bool
`eqPhase`) [Phase
Cc, Phase
Ccxx, Phase
HCc, Phase
Cobjc, Phase
Cobjcxx]
= do
HscEnv
hsc_env <- CompPipeline HscEnv
getPipeSession
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags 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
includePaths DynFlags
dflags
[UnitId]
pkgs <- if Bool
hcc then IO [UnitId] -> CompPipeline [UnitId]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [UnitId] -> CompPipeline [UnitId])
-> IO [UnitId] -> CompPipeline [UnitId]
forall a b. (a -> b) -> a -> b
$ String -> IO [UnitId]
getHCFilePackages String
input_fn else [UnitId] -> CompPipeline [UnitId]
forall (m :: * -> *) a. Monad m => a -> m a
return []
[UnitInfo]
ps <- IO [UnitInfo] -> CompPipeline [UnitInfo]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [UnitInfo] -> CompPipeline [UnitInfo])
-> IO [UnitInfo] -> CompPipeline [UnitInfo]
forall a b. (a -> b) -> a -> b
$ 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 (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 (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 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 <- DynFlags -> (DynFlags -> [String]) -> [String]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [String]
opt_P
]
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
optLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 = [ String
"-O2" ]
| DynFlags -> Int
optLevel DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 = [ String
"-O" ]
| Bool
otherwise = []
let next_phase :: Phase
next_phase = Bool -> Phase
As Bool
False
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase
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 <- IO String -> CompPipeline String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> CompPipeline String)
-> IO String -> CompPipeline String
forall a b. (a -> b) -> a -> b
$ DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ 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
[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 Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchSPARC
then [String
"-mcpu=v9"]
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
"-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
))
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
output_fn)
runPhase (RealPhase (As Bool
with_cpp)) String
input_fn
= do
HscEnv
hsc_env <- CompPipeline HscEnv
getPipeSession
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 as_prog :: Logger -> DynFlags -> [Option] -> IO ()
as_prog | 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
| Bool
otherwise
= Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runAs
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
Phase
next_phase <- CompPipeline Phase
maybeMergeForeign
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
output_fn)
CompilerInfo
ccInfo <- IO CompilerInfo -> CompPipeline CompilerInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CompilerInfo -> CompPipeline CompilerInfo)
-> IO CompilerInfo -> CompPipeline CompilerInfo
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> IO CompilerInfo
getCompilerInfo Logger
logger DynFlags
dflags
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 -> CompPipeline ()
runAssembler String
inputFilename String
outputFilename
= IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$
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
[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]
++ (if Platform -> Arch
platformArch (DynFlags -> Platform
targetPlatform DynFlags
dflags) Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchSPARC
then [String -> Option
GHC.SysTools.Option String
"-mcpu=v9"]
else [])
[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
ccInfo 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
])
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
4 (String -> SDoc
text String
"Running the assembler")
String -> String -> CompPipeline ()
runAssembler String
input_fn String
output_fn
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
output_fn)
runPhase (RealPhase Phase
LlvmOpt) String
input_fn = do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
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
optLevel 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 -> [(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 (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)
optFlag :: [Option]
optFlag = if [String] -> 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 -> CompPipeline String
phaseOutputFilename Phase
LlvmLlc
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ 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]
)
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
LlvmLlc, String
output_fn)
runPhase (RealPhase Phase
LlvmLlc) String
input_fn = do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
let
llvmOpts :: String
llvmOpts = case DynFlags -> Int
optLevel 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 (DynFlags -> [(String, String)]
llvmOptions DynFlags
dflags)
optFlag :: [Option]
optFlag = if [String] -> 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 -> CompPipeline Phase
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Phase
As Bool
False)
| Bool
otherwise -> Phase -> CompPipeline Phase
forall (m :: * -> *) a. Monad m => a -> m a
return Phase
LlvmMangle
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ 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
]
)
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
output_fn)
runPhase (RealPhase Phase
LlvmMangle) String
input_fn = do
let next_phase :: Phase
next_phase = Bool -> Phase
As Bool
False
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
next_phase
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> String -> String -> IO ()
llvmFixupAsm Logger
logger DynFlags
dflags String
input_fn String
output_fn
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
next_phase, String
output_fn)
runPhase (RealPhase Phase
MergeForeign) String
input_fn = do
PipeState{[String]
foreign_os :: [String]
foreign_os :: PipeState -> [String]
foreign_os,HscEnv
hsc_env :: HscEnv
hsc_env :: PipeState -> HscEnv
hsc_env} <- CompPipeline PipeState
getPipeState
String
output_fn <- Phase -> CompPipeline String
phaseOutputFilename Phase
StopLn
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
output_fn)
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
foreign_os
then String -> CompPipeline (PhasePlus, String)
forall a. String -> a
panic String
"runPhase(MergeForeign): no foreign objects"
else do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- CompPipeline Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
IO () -> CompPipeline ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> CompPipeline ()) -> IO () -> CompPipeline ()
forall a b. (a -> b) -> a -> b
$ Logger -> TmpFs -> DynFlags -> [String] -> String -> IO ()
joinObjectFiles Logger
logger TmpFs
tmpfs DynFlags
dflags (String
input_fn String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
foreign_os) String
output_fn
(PhasePlus, String) -> CompPipeline (PhasePlus, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Phase -> PhasePlus
RealPhase Phase
StopLn, String
output_fn)
runPhase (RealPhase Phase
other) String
_input_fn =
String -> CompPipeline (PhasePlus, String)
forall a. String -> a
panic (String
"runPhase: don't know how to run phase " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Phase -> String
forall a. Show a => a -> String
show Phase
other)
maybeMergeForeign :: CompPipeline Phase
maybeMergeForeign :: CompPipeline Phase
maybeMergeForeign
= do
PipeState{[String]
foreign_os :: [String]
foreign_os :: PipeState -> [String]
foreign_os} <- CompPipeline PipeState
getPipeState
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
foreign_os then Phase -> CompPipeline Phase
forall (m :: * -> *) a. Monad m => a -> m a
return Phase
StopLn else Phase -> CompPipeline Phase
forall (m :: * -> *) a. Monad m => a -> m a
return Phase
MergeForeign
getLocation :: HscSource -> ModuleName -> CompPipeline ModLocation
getLocation :: HscSource -> ModuleName -> CompPipeline ModLocation
getLocation HscSource
src_flavour ModuleName
mod_name = do
DynFlags
dflags <- CompPipeline DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
PipeEnv{ src_basename :: PipeEnv -> String
src_basename=String
basename,
src_suffix :: PipeEnv -> String
src_suffix=String
suff } <- CompPipeline PipeEnv
getPipeEnv
PipeState { maybe_loc :: PipeState -> Maybe ModLocation
maybe_loc=Maybe ModLocation
maybe_loc} <- CompPipeline PipeState
getPipeState
case Maybe ModLocation
maybe_loc of
Just ModLocation
l -> ModLocation -> CompPipeline ModLocation
forall (m :: * -> *) a. Monad m => a -> m a
return (ModLocation -> CompPipeline ModLocation)
-> ModLocation -> CompPipeline ModLocation
forall a b. (a -> b) -> a -> b
$ ModLocation
l
{ ml_hs_file :: Maybe String
ml_hs_file = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String
basename String -> String -> String
<.> String
suff
, ml_hi_file :: String
ml_hi_file = ModLocation -> String
ml_hi_file ModLocation
l String -> String -> String
-<.> DynFlags -> String
hiSuf DynFlags
dflags
, ml_obj_file :: String
ml_obj_file = ModLocation -> String
ml_obj_file ModLocation
l String -> String -> String
-<.> DynFlags -> String
objectSuf DynFlags
dflags
}
Maybe ModLocation
_ -> do
ModLocation
location1 <- IO ModLocation -> CompPipeline ModLocation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModLocation -> CompPipeline ModLocation)
-> IO ModLocation -> CompPipeline ModLocation
forall a b. (a -> b) -> a -> b
$ DynFlags -> ModuleName -> String -> String -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags 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 :: String
ml_hi_file = String
fn }
| Bool
otherwise = ModLocation
location2
let expl_o_file :: Maybe String
expl_o_file = DynFlags -> Maybe String
outputFile DynFlags
dflags
location4 :: ModLocation
location4 | Just String
ofile <- Maybe String
expl_o_file
, GhcLink -> Bool
isNoLink (DynFlags -> GhcLink
ghcLink DynFlags
dflags)
= ModLocation
location3 { ml_obj_file :: String
ml_obj_file = String
ofile }
| Bool
otherwise = ModLocation
location3
ModLocation -> CompPipeline ModLocation
forall (m :: * -> *) a. Monad m => a -> m a
return ModLocation
location4
getHCFilePackages :: FilePath -> IO [UnitId]
getHCFilePackages :: String -> IO [UnitId]
getHCFilePackages String
filename =
IO Handle
-> (Handle -> IO ()) -> (Handle -> IO [UnitId]) -> IO [UnitId]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket (String -> IOMode -> IO Handle
openFile String
filename IOMode
ReadMode) Handle -> IO ()
hClose ((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 (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 (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 -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevInfo 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
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
includePaths DynFlags
dflags
let unit_state :: UnitState
unit_state = 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)
let include_paths_global :: [String]
include_paths_global = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
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 (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" ]
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__" ]
String
ghcVersionH <- DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env
let hsSourceCppOpts :: [String]
hsSourceCppOpts = [ String
"-include", String
ghcVersionH ]
let uids :: [Unit]
uids = UnitState -> [Unit]
explicitUnits UnitState
unit_state
pkgs :: [UnitInfo]
pkgs = [Maybe UnitInfo] -> [UnitInfo]
forall a. [Maybe a] -> [a]
catMaybes ((Unit -> Maybe UnitInfo) -> [Unit] -> [Maybe UnitInfo]
forall a b. (a -> b) -> [a] -> [b]
map (UnitState -> Unit -> Maybe UnitInfo
lookupUnit UnitState
unit_state) [Unit]
uids)
[Option]
mb_macro_include <-
if Bool -> Bool
not ([UnitInfo] -> 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 -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
TFL_CurrentModule String
"h"
String -> String -> IO ()
writeFile String
macro_stub ([UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs)
[Option] -> IO [Option]
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 (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
[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
, 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 (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 (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)
getBackendDefs Logger
_ DynFlags
_ =
[String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return []
generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String -> String -> Version -> String
generateMacros String
"" String
pkgname Version
version
| UnitInfo
pkg <- [UnitInfo]
pkgs
, let version :: Version
version = UnitInfo -> Version
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid 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)
joinObjectFiles :: Logger -> TmpFs -> DynFlags -> [FilePath] -> FilePath -> IO ()
joinObjectFiles :: Logger -> TmpFs -> DynFlags -> [String] -> String -> IO ()
joinObjectFiles Logger
logger TmpFs
tmpfs DynFlags
dflags [String]
o_files String
output_fn = do
let toolSettings' :: ToolSettings
toolSettings' = DynFlags -> ToolSettings
toolSettings DynFlags
dflags
ldIsGnuLd :: Bool
ldIsGnuLd = ToolSettings -> Bool
toolSettings_ldIsGnuLd ToolSettings
toolSettings'
osInfo :: OS
osInfo = Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)
ld_r :: [Option] -> IO ()
ld_r [Option]
args = Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runMergeObjects Logger
logger TmpFs
tmpfs DynFlags
dflags (
[[Option]] -> [Option]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [String -> Option
GHC.SysTools.Option String
"--oformat", String -> Option
GHC.SysTools.Option String
"pe-bigobj-x86-64"]
| OS
OSMinGW32 OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
osInfo
, 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) -> [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)
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 -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs 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 -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs 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)
writeInterfaceOnlyMode :: DynFlags -> Bool
writeInterfaceOnlyMode :: DynFlags -> Bool
writeInterfaceOnlyMode DynFlags
dflags =
GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_WriteInterface DynFlags
dflags Bool -> Bool -> Bool
&&
Backend
NoBackend Backend -> Backend -> Bool
forall a. Eq a => a -> a -> Bool
== DynFlags -> Backend
backend DynFlags
dflags
sourceModified :: FilePath
-> UTCTime
-> IO Bool
sourceModified :: String -> UTCTime -> IO Bool
sourceModified String
dest_file UTCTime
src_timestamp = do
Bool
dest_file_exists <- String -> IO Bool
doesFileExist String
dest_file
if Bool -> Bool
not Bool
dest_file_exists
then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else do UTCTime
t2 <- String -> IO UTCTime
getModificationUTCTime String
dest_file
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime
t2 UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
<= UTCTime
src_timestamp)
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
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
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 (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 (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 (m :: * -> *) a. Monad m => a -> m a
return String
x