{-# 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 -- ^ Use "cc -E" as preprocessor, otherwise use "cpp"
  , CppOpts -> Bool
cppLinePragmas :: !Bool -- ^ Enable generation of LINE pragmas
  }

-- | Run CPP
--
-- UnitEnv is needed to compute MIN_VERSION macros
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 = HasDebugCallStack => UnitEnv -> UnitState
ue_units UnitEnv
unit_env
    [String]
pkg_include_dirs <- forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
                        ([UnitInfo] -> [String]
collectIncludeDirs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UnitEnv -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo UnitEnv
unit_env)
    -- MP: This is not quite right, the headers which are supposed to be installed in
    -- the package might not be the same as the provided include paths, but it's a close
    -- enough approximation for things to work. A proper solution would be to have to declare which paths should
    -- be propagated to dependent packages.
    let home_pkg_deps :: [DynFlags]
home_pkg_deps =
         [HomeUnitEnv -> DynFlags
homeUnitEnv_dflags forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasDebugCallStack => UnitId -> UnitEnv -> HomeUnitEnv
ue_findHomeUnitEnv UnitId
uid 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 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-I" forall a. [a] -> [a] -> [a]
++ String
x) forall a. a -> [a] -> [a]
: [String]
xs) []
          (IncludeSpecs -> [String]
includePathsGlobal IncludeSpecs
cmdline_include_paths forall a. [a] -> [a] -> [a]
++ [String]
pkg_include_dirs
                                                    forall a. [a] -> [a] -> [a]
++ 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 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ String
x [String]
xs -> (String
"-iquote" forall a. [a] -> [a] -> [a]
++ String
x) forall a. a -> [a] -> [a]
: [String]
xs) []
          (IncludeSpecs -> [String]
includePathsQuote IncludeSpecs
cmdline_include_paths forall a. [a] -> [a] -> [a]
++
           IncludeSpecs -> [String]
includePathsQuoteImplicit IncludeSpecs
cmdline_include_paths)
    let include_paths :: [String]
include_paths = [String]
include_paths_quote 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 forall a. Maybe a
Nothing Logger
logger TmpFs
tmpfs DynFlags
dflags
                                               (String -> Option
GHC.SysTools.Option String
"-E" 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 forall a b. (a -> b) -> a -> b
$ Platform -> Arch
platformArch Platform
platform
        targetOS :: String
targetOS = OS -> String
stringEncodeOS forall a b. (a -> b) -> a -> b
$ Platform -> OS
platformOS Platform
platform
        isWindows :: Bool
isWindows = Platform -> OS
platformOS Platform
platform forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
    let target_defs :: [String]
target_defs =
          [ String
"-D" forall a. [a] -> [a] -> [a]
++ String
HOST_OS     forall a. [a] -> [a] -> [a]
++ String
"_BUILD_OS",
            String
"-D" forall a. [a] -> [a] -> [a]
++ HOST_ARCH   ++ "_BUILD_ARCH",
            String
"-D" forall a. [a] -> [a] -> [a]
++ String
targetOS    forall a. [a] -> [a] -> [a]
++ String
"_HOST_OS",
            String
"-D" forall a. [a] -> [a] -> [a]
++ String
targetArch  forall a. [a] -> [a] -> [a]
++ String
"_HOST_ARCH" ]
        -- remember, in code we *compile*, the HOST is the same our TARGET,
        -- and BUILD is the same as our HOST.

    let io_manager_defs :: [String]
io_manager_defs =
          [ String
"-D__IO_MANAGER_WINIO__=1" | Bool
isWindows ] 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 ] forall a. [a] -> [a] -> [a]
++
          [ String
"-D__SSE2__"     | Platform -> Bool
isSse2Enabled     Platform
platform ] 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 ] forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX2__"     | DynFlags -> Bool
isAvx2Enabled     DynFlags
dflags ] forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512CD__" | DynFlags -> Bool
isAvx512cdEnabled DynFlags
dflags ] forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512ER__" | DynFlags -> Bool
isAvx512erEnabled DynFlags
dflags ] forall a. [a] -> [a] -> [a]
++
          [ String
"-D__AVX512F__"  | DynFlags -> Bool
isAvx512fEnabled  DynFlags
dflags ] 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 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__" ]
    -- Default CPP defines in Haskell source
    String
ghcVersionH <- DynFlags -> UnitEnv -> IO String
getGhcVersionPathName DynFlags
dflags UnitEnv
unit_env
    let hsSourceCppOpts :: [String]
hsSourceCppOpts = [ String
"-include", String
ghcVersionH ]

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

    let line_pragmas :: [Option]
line_pragmas
          | CppOpts -> Bool
cppLinePragmas CppOpts
opts = [] -- on by default
          | Bool
otherwise           = [String -> Option
GHC.SysTools.Option String
"-P"] -- disable LINE markers

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

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

generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros :: [UnitInfo] -> String
generatePackageVersionMacros [UnitInfo]
pkgs = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  -- Do not add any C-style comments. See #3389.
  [ String -> String -> Version -> String
generateMacros String
"" String
pkgname Version
version
  | UnitInfo
pkg <- [UnitInfo]
pkgs
  , let version :: Version
version = forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
unitPackageVersion UnitInfo
pkg
        pkgname :: String
pkgname = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar (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 =
  forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [String
"#define ", String
prefix, String
"VERSION_",String
name,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]
_         -> forall a. HasCallStack => String -> a
error String
"take3"
    (String
major1,String
major2,String
minor) = forall {c}. [c] -> (c, c, c)
take3 forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show (Version -> [Int]
versionBranch Version
version) forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat String
"0"


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

  [String]
found <- forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesFileExist [String]
candidates
  case [String]
found of
      []    -> forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
InstallationError
                                    (String
"ghcversion.h missing; tried: "
                                      forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
candidates))
      (String
x:[String]
_) -> 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
_ = 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
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case 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__=" forall a. [a] -> [a] -> [a]
++ (Int, Int) -> String
format (Int
m,Int
0) ]
               Just (Int
m:Int
n:[Int]
_) -> [ String
"-D__GLASGOW_HASKELL_LLVM__=" 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 forall a. Ord a => a -> a -> Bool
>= Int
100 = forall a. HasCallStack => String -> a
error String
"backendCDefs: Unsupported minor version"
      | Bool
otherwise = forall a. Show a => a -> String
show (Int
100 forall a. Num a => a -> a -> a
* Int
major forall a. Num a => a -> a -> a
+ Int
minor :: Int) -- Contract is Int


-- Note [Filepaths and Multiple Home Units]
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths :: DynFlags -> IncludeSpecs -> IncludeSpecs
offsetIncludePaths DynFlags
dflags (IncludeSpecs [String]
incs [String]
quotes [String]
impl) =
     let go :: [String] -> [String]
go = 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)