{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
#include <ghcplatform.h>
module GHC.SysTools.Cpp
( doCpp
, CppOpts (..)
, getGhcVersionPathName
, applyCDefs
, offsetIncludePaths
)
where
import GHC.Prelude
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.CmmToLlvm.Config
import GHC.Platform
import GHC.Platform.ArchOS
import GHC.SysTools
import GHC.Unit.Env
import GHC.Unit.Info
import GHC.Unit.State
import GHC.Unit.Types
import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Utils.Panic
import Data.Version
import Data.List (intercalate)
import Data.Maybe
import Control.Monad
import System.Directory
import System.FilePath
data CppOpts = CppOpts
{ CppOpts -> Bool
cppUseCc :: !Bool
, CppOpts -> Bool
cppLinePragmas :: !Bool
}
doCpp :: Logger -> TmpFs -> DynFlags -> UnitEnv -> CppOpts -> FilePath -> FilePath -> IO ()
doCpp :: Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> CppOpts
-> String
-> String
-> IO ()
doCpp Logger
logger TmpFs
tmpfs DynFlags
dflags UnitEnv
unit_env CppOpts
opts String
input_fn String
output_fn = do
let hscpp_opts :: [String]
hscpp_opts = DynFlags -> [String]
picPOpts DynFlags
dflags
let cmdline_include_paths :: IncludeSpecs
cmdline_include_paths = DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (DynFlags -> IncludeSpecs
includePaths DynFlags
dflags)
let unit_state :: UnitState
unit_state = (() :: Constraint) => UnitEnv -> UnitState
UnitEnv -> UnitState
ue_units UnitEnv
unit_env
[String]
pkg_include_dirs <- MaybeErr UnitErr [String] -> IO [String]
forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
([UnitInfo] -> [String]
collectIncludeDirs ([UnitInfo] -> [String])
-> MaybeErr UnitErr [UnitInfo] -> MaybeErr UnitErr [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UnitEnv -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo UnitEnv
unit_env)
let home_pkg_deps :: [DynFlags]
home_pkg_deps =
[HomeUnitEnv -> DynFlags
homeUnitEnv_dflags (HomeUnitEnv -> DynFlags)
-> (UnitEnv -> HomeUnitEnv) -> UnitEnv -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (() :: Constraint) => UnitId -> UnitEnv -> HomeUnitEnv
UnitId -> UnitEnv -> HomeUnitEnv
ue_findHomeUnitEnv UnitId
uid (UnitEnv -> DynFlags) -> UnitEnv -> DynFlags
forall a b. (a -> b) -> a -> b
$ UnitEnv
unit_env | UnitId
uid <- UnitId -> UnitEnv -> [UnitId]
ue_transitiveHomeDeps (UnitEnv -> UnitId
ue_currentUnit UnitEnv
unit_env) UnitEnv
unit_env]
dep_pkg_extra_inputs :: [IncludeSpecs]
dep_pkg_extra_inputs = [DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
fs (DynFlags -> IncludeSpecs
includePaths DynFlags
fs) | DynFlags
fs <- [DynFlags]
home_pkg_deps]
let include_paths_global :: [String]
include_paths_global = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
(IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_include_dirs
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (IncludeSpecs -> [String]) -> [IncludeSpecs] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IncludeSpecs -> [String]
includePathsGlobal [IncludeSpecs]
dep_pkg_extra_inputs)
let include_paths_quote :: [String]
include_paths_quote = (String -> [String] -> [String])
-> [String] -> [String] -> [String]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-iquote" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
xs) []
(IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
cmdline_include_paths [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
cmdline_include_paths)
let include_paths :: [String]
include_paths = [String]
include_paths_quote [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
include_paths_global
let verbFlags :: [String]
verbFlags = DynFlags -> [String]
getVerbFlags DynFlags
dflags
let cpp_prog :: [Option] -> IO ()
cpp_prog [Option]
args
| CppOpts -> Bool
cppUseCc CppOpts
opts = 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)
| Bool
otherwise = Logger -> DynFlags -> [Option] -> IO ()
GHC.SysTools.runCpp Logger
logger DynFlags
dflags [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 <- DefunctionalizedCDefs -> Logger -> DynFlags -> IO [String]
applyCDefs (Backend -> DefunctionalizedCDefs
backendCDefs (Backend -> DefunctionalizedCDefs)
-> Backend -> DefunctionalizedCDefs
forall a b. (a -> b) -> a -> b
$ DynFlags -> Backend
backend DynFlags
dflags) 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, Maybe PackageArg)]
uids = UnitState -> [(Unit, Maybe PackageArg)]
explicitUnits UnitState
unit_state
pkgs :: [UnitInfo]
pkgs = ((Unit, Maybe PackageArg) -> Maybe UnitInfo)
-> [(Unit, Maybe PackageArg)] -> [UnitInfo]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (UnitState -> Unit -> Maybe UnitInfo
lookupUnit UnitState
unit_state (Unit -> Maybe UnitInfo)
-> ((Unit, Maybe PackageArg) -> Unit)
-> (Unit, Maybe PackageArg)
-> Maybe UnitInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Unit, Maybe PackageArg) -> Unit
forall a b. (a, b) -> a
fst) [(Unit, Maybe PackageArg)]
uids
[Option]
mb_macro_include <-
if Bool -> Bool
not ([UnitInfo] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
pkgs) Bool -> Bool -> Bool
&& GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_VersionMacros DynFlags
dflags
then do String
macro_stub <- Logger
-> TmpFs -> TempDir -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs (DynFlags -> TempDir
tmpDir DynFlags
dflags) TempFileLifetime
TFL_CurrentModule String
"h"
String -> String -> IO ()
writeFile String
macro_stub ([UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs)
[Option] -> IO [Option]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String -> String -> Option
GHC.SysTools.FileOption String
"-include" String
macro_stub]
else [Option] -> IO [Option]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
let line_pragmas :: [Option]
line_pragmas
| CppOpts -> Bool
cppLinePragmas CppOpts
opts = []
| Bool
otherwise = [String -> Option
GHC.SysTools.Option String
"-P"]
[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]
++ [Option]
line_pragmas
[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
])
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 srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
unitPackageVersion UnitInfo
pkg
pkgname :: String
pkgname = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar (UnitInfo -> String
forall u. GenUnitInfo u -> String
unitPackageNameString UnitInfo
pkg)
]
fixchar :: Char -> Char
fixchar :: Char -> Char
fixchar Char
'-' = Char
'_'
fixchar Char
c = Char
c
generateMacros :: String -> String -> Version -> String
generateMacros :: String -> String -> Version -> String
generateMacros String
prefix String
name Version
version =
[String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[String
"#define ", String
prefix, String
"VERSION_",String
name,String
" ",String -> String
forall a. Show a => a -> String
show (Version -> String
showVersion Version
version),String
"\n"
,String
"#define MIN_", String
prefix, String
"VERSION_",String
name,String
"(major1,major2,minor) (\\\n"
,String
" (major1) < ",String
major1,String
" || \\\n"
,String
" (major1) == ",String
major1,String
" && (major2) < ",String
major2,String
" || \\\n"
,String
" (major1) == ",String
major1,String
" && (major2) == ",String
major2,String
" && (minor) <= ",String
minor,String
")"
,String
"\n\n"
]
where
take3 :: [c] -> (c, c, c)
take3 = \case
(c
a:c
b:c
c:[c]
_) -> (c
a,c
b,c
c)
[c]
_ -> String -> (c, c, c)
forall a. HasCallStack => String -> a
error String
"take3"
(String
major1,String
major2,String
minor) = [String] -> (String, String, String)
forall {c}. [c] -> (c, c, c)
take3 ([String] -> (String, String, String))
-> [String] -> (String, String, String)
forall a b. (a -> b) -> a -> b
$ (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) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
forall a. a -> [a]
repeat String
"0"
getGhcVersionPathName :: DynFlags -> UnitEnv -> IO FilePath
getGhcVersionPathName :: DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env = do
[String]
candidates <- case DynFlags -> Maybe String
ghcVersionFile DynFlags
dflags of
Just String
path -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
path]
Maybe String
Nothing -> do
[UnitInfo]
ps <- MaybeErr UnitErr [UnitInfo] -> IO [UnitInfo]
forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr (UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' UnitEnv
unit_env [UnitId
rtsUnitId])
[String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((String -> String -> String
</> String
"ghcversion.h") (String -> String) -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [UnitInfo] -> [String]
collectIncludeDirs [UnitInfo]
ps)
[String]
found <- (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesFileExist [String]
candidates
case [String]
found of
[] -> GhcException -> IO String
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
InstallationError
(String
"ghcversion.h missing; tried: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
candidates))
(String
x:[String]
_) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
x
applyCDefs :: DefunctionalizedCDefs -> Logger -> DynFlags -> IO [String]
applyCDefs :: DefunctionalizedCDefs -> Logger -> DynFlags -> IO [String]
applyCDefs DefunctionalizedCDefs
NoCDefs Logger
_ DynFlags
_ = [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
applyCDefs DefunctionalizedCDefs
LlvmCDefs Logger
logger DynFlags
dflags = do
Maybe LlvmVersion
llvmVer <- Logger -> DynFlags -> IO (Maybe LlvmVersion)
figureLlvmVersion Logger
logger DynFlags
dflags
[String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ case (LlvmVersion -> [Int]) -> Maybe LlvmVersion -> Maybe [Int]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LlvmVersion -> [Int]
llvmVersionList Maybe LlvmVersion
llvmVer of
Just [Int
m] -> [ String
"-D__GLASGOW_HASKELL_LLVM__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int, Int) -> String
format (Int
m,Int
0) ]
Just (Int
m:Int
n:[Int]
_) -> [ String
"-D__GLASGOW_HASKELL_LLVM__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int, Int) -> String
format (Int
m,Int
n) ]
Maybe [Int]
_ -> []
where
format :: (Int, Int) -> String
format (Int
major, Int
minor)
| Int
minor Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
100 = String -> String
forall a. HasCallStack => String -> a
error String
"backendCDefs: Unsupported minor version"
| Bool
otherwise = Int -> String
forall a. Show a => a -> String
show (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)
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (IncludeSpecs [String]
incs [String]
quotes [String]
impl) =
let go :: [String] -> [String]
go = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (DynFlags -> String -> String
augmentByWorkingDirectory DynFlags
dflags)
in [String] -> [String] -> [String] -> IncludeSpecs
IncludeSpecs ([String] -> [String]
go [String]
incs) ([String] -> [String]
go [String]
quotes) ([String] -> [String]
go [String]
impl)