-----------------------------------------------------------------------------
--
-- GHC Extra object linking code
--
-- (c) The GHC Team 2017
--
-----------------------------------------------------------------------------

module SysTools.ExtraObj (
  mkExtraObj, mkExtraObjToLinkIntoBinary, mkNoteObjsToLinkIntoBinary,
  checkLinkInfo, getLinkInfo, getCompilerInfo,
  ghcLinkInfoSectionName, ghcLinkInfoNoteName, platformSupportsSavingLinkOpts,
  haveRtsOptsFlags
) where

import AsmUtils
import ErrUtils
import DynFlags
import Packages
import GHC.Platform
import Outputable
import SrcLoc           ( noSrcSpan )
import Module
import Elf
import Util
import GhcPrelude

import Control.Monad
import Data.Maybe

import Control.Monad.IO.Class

import FileCleanup
import SysTools.Tasks
import SysTools.Info

mkExtraObj :: DynFlags -> Suffix -> String -> IO FilePath
mkExtraObj :: DynFlags -> Suffix -> Suffix -> IO Suffix
mkExtraObj DynFlags
dflags Suffix
extn Suffix
xs
 = do Suffix
cFile <- DynFlags -> TempFileLifetime -> Suffix -> IO Suffix
newTempName DynFlags
dflags TempFileLifetime
TFL_CurrentModule Suffix
extn
      Suffix
oFile <- DynFlags -> TempFileLifetime -> Suffix -> IO Suffix
newTempName DynFlags
dflags TempFileLifetime
TFL_GhcSession Suffix
"o"
      Suffix -> Suffix -> IO ()
writeFile Suffix
cFile Suffix
xs
      CompilerInfo
ccInfo <- IO CompilerInfo -> IO CompilerInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CompilerInfo -> IO CompilerInfo)
-> IO CompilerInfo -> IO CompilerInfo
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO CompilerInfo
getCompilerInfo DynFlags
dflags
      Maybe ForeignSrcLang -> DynFlags -> [Option] -> IO ()
runCc Maybe ForeignSrcLang
forall a. Maybe a
Nothing DynFlags
dflags
            ([Suffix -> Option
Option        Suffix
"-c",
              Suffix -> Suffix -> Option
FileOption Suffix
"" Suffix
cFile,
              Suffix -> Option
Option        Suffix
"-o",
              Suffix -> Suffix -> Option
FileOption Suffix
"" Suffix
oFile]
              [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ if Suffix
extn Suffix -> Suffix -> Bool
forall a. Eq a => a -> a -> Bool
/= Suffix
"s"
                    then [Option]
cOpts
                    else CompilerInfo -> [Option]
asmOpts CompilerInfo
ccInfo)
      Suffix -> IO Suffix
forall (m :: * -> *) a. Monad m => a -> m a
return Suffix
oFile
    where
      -- Pass a different set of options to the C compiler depending one whether
      -- we're compiling C or assembler. When compiling C, we pass the usual
      -- set of include directories and PIC flags.
      cOpts :: [Option]
cOpts = (Suffix -> Option) -> [Suffix] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map Suffix -> Option
Option (DynFlags -> [Suffix]
picCCOpts DynFlags
dflags)
                    [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (Suffix -> Option) -> [Suffix] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (Suffix -> Suffix -> Option
FileOption Suffix
"-I")
                            (InstalledPackageInfo
  ComponentId
  SourcePackageId
  PackageName
  InstalledUnitId
  UnitId
  ModuleName
  Module
-> [Suffix]
forall compid srcpkgid srcpkgname instunitid unitid modulename mod.
InstalledPackageInfo
  compid srcpkgid srcpkgname instunitid unitid modulename mod
-> [Suffix]
includeDirs (InstalledPackageInfo
   ComponentId
   SourcePackageId
   PackageName
   InstalledUnitId
   UnitId
   ModuleName
   Module
 -> [Suffix])
-> InstalledPackageInfo
     ComponentId
     SourcePackageId
     PackageName
     InstalledUnitId
     UnitId
     ModuleName
     Module
-> [Suffix]
forall a b. (a -> b) -> a -> b
$ DynFlags
-> UnitId
-> InstalledPackageInfo
     ComponentId
     SourcePackageId
     PackageName
     InstalledUnitId
     UnitId
     ModuleName
     Module
getPackageDetails DynFlags
dflags UnitId
rtsUnitId)

      -- When compiling assembler code, we drop the usual C options, and if the
      -- compiler is Clang, we add an extra argument to tell Clang to ignore
      -- unused command line options. See trac #11684.
      asmOpts :: CompilerInfo -> [Option]
asmOpts CompilerInfo
ccInfo =
            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 [Suffix -> Option
Option Suffix
"-Qunused-arguments"]
                else []

-- When linking a binary, we need to create a C main() function that
-- starts everything off.  This used to be compiled statically as part
-- of the RTS, but that made it hard to change the -rtsopts setting,
-- so now we generate and compile a main() stub as part of every
-- binary and pass the -rtsopts setting directly to the RTS (#5373)
--
-- On Windows, when making a shared library we also may need a DllMain.
--
mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
mkExtraObjToLinkIntoBinary :: DynFlags -> IO Suffix
mkExtraObjToLinkIntoBinary DynFlags
dflags = do
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_NoHsMain DynFlags
dflags Bool -> Bool -> Bool
&& DynFlags -> Bool
haveRtsOptsFlags DynFlags
dflags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
     DynFlags
-> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
putLogMsg DynFlags
dflags WarnReason
NoReason Severity
SevInfo SrcSpan
noSrcSpan
         (DynFlags -> PprStyle
defaultUserStyle DynFlags
dflags)
         (Suffix -> MsgDoc
text Suffix
"Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." MsgDoc -> MsgDoc -> MsgDoc
$$
          Suffix -> MsgDoc
text Suffix
"    Call hs_init_ghc() from your main() function to set these options.")

  DynFlags -> Suffix -> Suffix -> IO Suffix
mkExtraObj DynFlags
dflags Suffix
"c" (DynFlags -> MsgDoc -> Suffix
showSDoc DynFlags
dflags MsgDoc
main)
  where
    main :: MsgDoc
main
      | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_NoHsMain DynFlags
dflags = MsgDoc
Outputable.empty
      | Bool
otherwise
          = case DynFlags -> GhcLink
ghcLink DynFlags
dflags of
                  GhcLink
LinkDynLib -> if Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags) OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
                                    then MsgDoc
dllMain
                                    else MsgDoc
Outputable.empty
                  GhcLink
_                      -> MsgDoc
exeMain

    exeMain :: MsgDoc
exeMain = [MsgDoc] -> MsgDoc
vcat [
        Suffix -> MsgDoc
text Suffix
"#include <Rts.h>",
        Suffix -> MsgDoc
text Suffix
"extern StgClosure ZCMain_main_closure;",
        Suffix -> MsgDoc
text Suffix
"int main(int argc, char *argv[])",
        Char -> MsgDoc
char Char
'{',
        Suffix -> MsgDoc
text Suffix
" RtsConfig __conf = defaultRtsConfig;",
        Suffix -> MsgDoc
text Suffix
" __conf.rts_opts_enabled = "
            MsgDoc -> MsgDoc -> MsgDoc
<> Suffix -> MsgDoc
text (RtsOptsEnabled -> Suffix
forall a. Show a => a -> Suffix
show (DynFlags -> RtsOptsEnabled
rtsOptsEnabled DynFlags
dflags)) MsgDoc -> MsgDoc -> MsgDoc
<> MsgDoc
semi,
        Suffix -> MsgDoc
text Suffix
" __conf.rts_opts_suggestions = "
            MsgDoc -> MsgDoc -> MsgDoc
<> Suffix -> MsgDoc
text (if DynFlags -> Bool
rtsOptsSuggestions DynFlags
dflags
                        then Suffix
"true"
                        else Suffix
"false") MsgDoc -> MsgDoc -> MsgDoc
<> MsgDoc
semi,
        Suffix -> MsgDoc
text Suffix
"__conf.keep_cafs = "
            MsgDoc -> MsgDoc -> MsgDoc
<> Suffix -> MsgDoc
text (if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepCAFs DynFlags
dflags
                       then Suffix
"true"
                       else Suffix
"false") MsgDoc -> MsgDoc -> MsgDoc
<> MsgDoc
semi,
        case DynFlags -> Maybe Suffix
rtsOpts DynFlags
dflags of
            Maybe Suffix
Nothing   -> MsgDoc
Outputable.empty
            Just Suffix
opts -> Suffix -> MsgDoc
text Suffix
"    __conf.rts_opts= " MsgDoc -> MsgDoc -> MsgDoc
<>
                          Suffix -> MsgDoc
text (Suffix -> Suffix
forall a. Show a => a -> Suffix
show Suffix
opts) MsgDoc -> MsgDoc -> MsgDoc
<> MsgDoc
semi,
        Suffix -> MsgDoc
text Suffix
" __conf.rts_hs_main = true;",
        Suffix -> MsgDoc
text Suffix
" return hs_main(argc,argv,&ZCMain_main_closure,__conf);",
        Char -> MsgDoc
char Char
'}',
        Char -> MsgDoc
char Char
'\n' -- final newline, to keep gcc happy
        ]

    dllMain :: MsgDoc
dllMain = [MsgDoc] -> MsgDoc
vcat [
        Suffix -> MsgDoc
text Suffix
"#include <Rts.h>",
        Suffix -> MsgDoc
text Suffix
"#include <windows.h>",
        Suffix -> MsgDoc
text Suffix
"#include <stdbool.h>",
        Char -> MsgDoc
char Char
'\n',
        Suffix -> MsgDoc
text Suffix
"bool",
        Suffix -> MsgDoc
text Suffix
"WINAPI",
        Suffix -> MsgDoc
text Suffix
"DllMain ( HINSTANCE hInstance STG_UNUSED",
        Suffix -> MsgDoc
text Suffix
"        , DWORD reason STG_UNUSED",
        Suffix -> MsgDoc
text Suffix
"        , LPVOID reserved STG_UNUSED",
        Suffix -> MsgDoc
text Suffix
"        )",
        Suffix -> MsgDoc
text Suffix
"{",
        Suffix -> MsgDoc
text Suffix
"  return true;",
        Suffix -> MsgDoc
text Suffix
"}",
        Char -> MsgDoc
char Char
'\n' -- final newline, to keep gcc happy
        ]

-- Write out the link info section into a new assembly file. Previously
-- this was included as inline assembly in the main.c file but this
-- is pretty fragile. gas gets upset trying to calculate relative offsets
-- that span the .note section (notably .text) when debug info is present
mkNoteObjsToLinkIntoBinary :: DynFlags -> [InstalledUnitId] -> IO [FilePath]
mkNoteObjsToLinkIntoBinary :: DynFlags -> [InstalledUnitId] -> IO [Suffix]
mkNoteObjsToLinkIntoBinary DynFlags
dflags [InstalledUnitId]
dep_packages = do
   Suffix
link_info <- DynFlags -> [InstalledUnitId] -> IO Suffix
getLinkInfo DynFlags
dflags [InstalledUnitId]
dep_packages

   if (OS -> Bool
platformSupportsSavingLinkOpts (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)))
     then (Suffix -> [Suffix]) -> IO Suffix -> IO [Suffix]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Suffix -> [Suffix] -> [Suffix]
forall a. a -> [a] -> [a]
:[]) (IO Suffix -> IO [Suffix]) -> IO Suffix -> IO [Suffix]
forall a b. (a -> b) -> a -> b
$ DynFlags -> Suffix -> Suffix -> IO Suffix
mkExtraObj DynFlags
dflags Suffix
"s" (DynFlags -> MsgDoc -> Suffix
showSDoc DynFlags
dflags (Suffix -> MsgDoc
link_opts Suffix
link_info))
     else [Suffix] -> IO [Suffix]
forall (m :: * -> *) a. Monad m => a -> m a
return []

  where
    link_opts :: Suffix -> MsgDoc
link_opts Suffix
info = [MsgDoc] -> MsgDoc
hcat [
      -- "link info" section (see Note [LinkInfo section])
      Suffix -> Suffix -> Word32 -> Suffix -> MsgDoc
makeElfNote Suffix
ghcLinkInfoSectionName Suffix
ghcLinkInfoNoteName Word32
0 Suffix
info,

      -- ALL generated assembly must have this section to disable
      -- executable stacks.  See also
      -- compiler/nativeGen/AsmCodeGen.hs for another instance
      -- where we need to do this.
      if Platform -> Bool
platformHasGnuNonexecStack (DynFlags -> Platform
targetPlatform DynFlags
dflags)
        then Suffix -> MsgDoc
text Suffix
".section .note.GNU-stack,\"\","
             MsgDoc -> MsgDoc -> MsgDoc
<> Suffix -> MsgDoc
sectionType Suffix
"progbits" MsgDoc -> MsgDoc -> MsgDoc
<> Char -> MsgDoc
char Char
'\n'
        else MsgDoc
Outputable.empty
      ]

-- | Return the "link info" string
--
-- See Note [LinkInfo section]
getLinkInfo :: DynFlags -> [InstalledUnitId] -> IO String
getLinkInfo :: DynFlags -> [InstalledUnitId] -> IO Suffix
getLinkInfo DynFlags
dflags [InstalledUnitId]
dep_packages = do
   ([Suffix], [Suffix], [Suffix])
package_link_opts <- DynFlags -> [InstalledUnitId] -> IO ([Suffix], [Suffix], [Suffix])
getPackageLinkOpts DynFlags
dflags [InstalledUnitId]
dep_packages
   [Suffix]
pkg_frameworks <- if Platform -> Bool
platformUsesFrameworks (DynFlags -> Platform
targetPlatform DynFlags
dflags)
                     then DynFlags -> [InstalledUnitId] -> IO [Suffix]
getPackageFrameworks DynFlags
dflags [InstalledUnitId]
dep_packages
                     else [Suffix] -> IO [Suffix]
forall (m :: * -> *) a. Monad m => a -> m a
return []
   let extra_ld_inputs :: [Option]
extra_ld_inputs = DynFlags -> [Option]
ldInputs DynFlags
dflags
   let
      link_info :: (([Suffix], [Suffix], [Suffix]), [Suffix], Maybe Suffix,
 RtsOptsEnabled, Bool, [Suffix], [Suffix])
link_info = (([Suffix], [Suffix], [Suffix])
package_link_opts,
                   [Suffix]
pkg_frameworks,
                   DynFlags -> Maybe Suffix
rtsOpts DynFlags
dflags,
                   DynFlags -> RtsOptsEnabled
rtsOptsEnabled DynFlags
dflags,
                   GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_NoHsMain DynFlags
dflags,
                   (Option -> Suffix) -> [Option] -> [Suffix]
forall a b. (a -> b) -> [a] -> [b]
map Option -> Suffix
showOpt [Option]
extra_ld_inputs,
                   DynFlags -> (DynFlags -> [Suffix]) -> [Suffix]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [Suffix]
opt_l)
   --
   Suffix -> IO Suffix
forall (m :: * -> *) a. Monad m => a -> m a
return ((([Suffix], [Suffix], [Suffix]), [Suffix], Maybe Suffix,
 RtsOptsEnabled, Bool, [Suffix], [Suffix])
-> Suffix
forall a. Show a => a -> Suffix
show (([Suffix], [Suffix], [Suffix]), [Suffix], Maybe Suffix,
 RtsOptsEnabled, Bool, [Suffix], [Suffix])
link_info)

platformSupportsSavingLinkOpts :: OS -> Bool
platformSupportsSavingLinkOpts :: OS -> Bool
platformSupportsSavingLinkOpts OS
os
 | OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSSolaris2 = Bool
False -- see #5382
 | Bool
otherwise        = OS -> Bool
osElfTarget OS
os

-- See Note [LinkInfo section]
ghcLinkInfoSectionName :: String
ghcLinkInfoSectionName :: Suffix
ghcLinkInfoSectionName = Suffix
".debug-ghc-link-info"
  -- if we use the ".debug" prefix, then strip will strip it by default

-- Identifier for the note (see Note [LinkInfo section])
ghcLinkInfoNoteName :: String
ghcLinkInfoNoteName :: Suffix
ghcLinkInfoNoteName = Suffix
"GHC link info"

-- Returns 'False' if it was, and we can avoid linking, because the
-- previous binary was linked with "the same options".
checkLinkInfo :: DynFlags -> [InstalledUnitId] -> FilePath -> IO Bool
checkLinkInfo :: DynFlags -> [InstalledUnitId] -> Suffix -> IO Bool
checkLinkInfo DynFlags
dflags [InstalledUnitId]
pkg_deps Suffix
exe_file
 | Bool -> Bool
not (OS -> Bool
platformSupportsSavingLinkOpts (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)))
 -- ToDo: Windows and OS X do not use the ELF binary format, so
 -- readelf does not work there.  We need to find another way to do
 -- this.
 = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False -- conservatively we should return True, but not
                -- linking in this case was the behaviour for a long
                -- time so we leave it as-is.
 | Bool
otherwise
 = do
   Suffix
link_info <- DynFlags -> [InstalledUnitId] -> IO Suffix
getLinkInfo DynFlags
dflags [InstalledUnitId]
pkg_deps
   DynFlags -> Int -> MsgDoc -> IO ()
debugTraceMsg DynFlags
dflags Int
3 (MsgDoc -> IO ()) -> MsgDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ Suffix -> MsgDoc
text (Suffix
"Link info: " Suffix -> Suffix -> Suffix
forall a. [a] -> [a] -> [a]
++ Suffix
link_info)
   Maybe Suffix
m_exe_link_info <- DynFlags -> Suffix -> Suffix -> Suffix -> IO (Maybe Suffix)
readElfNoteAsString DynFlags
dflags Suffix
exe_file
                          Suffix
ghcLinkInfoSectionName Suffix
ghcLinkInfoNoteName
   let sameLinkInfo :: Bool
sameLinkInfo = (Suffix -> Maybe Suffix
forall a. a -> Maybe a
Just Suffix
link_info Maybe Suffix -> Maybe Suffix -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Suffix
m_exe_link_info)
   DynFlags -> Int -> MsgDoc -> IO ()
debugTraceMsg DynFlags
dflags Int
3 (MsgDoc -> IO ()) -> MsgDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ case Maybe Suffix
m_exe_link_info of
     Maybe Suffix
Nothing -> Suffix -> MsgDoc
text Suffix
"Exe link info: Not found"
     Just Suffix
s
       | Bool
sameLinkInfo -> Suffix -> MsgDoc
text (Suffix
"Exe link info is the same")
       | Bool
otherwise    -> Suffix -> MsgDoc
text (Suffix
"Exe link info is different: " Suffix -> Suffix -> Suffix
forall a. [a] -> [a] -> [a]
++ Suffix
s)
   Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Bool
not Bool
sameLinkInfo)

{- Note [LinkInfo section]
   ~~~~~~~~~~~~~~~~~~~~~~~

The "link info" is a string representing the parameters of the link. We save
this information in the binary, and the next time we link, if nothing else has
changed, we use the link info stored in the existing binary to decide whether
to re-link or not.

The "link info" string is stored in a ELF section called ".debug-ghc-link-info"
(see ghcLinkInfoSectionName) with the SHT_NOTE type.  For some time, it used to
not follow the specified record-based format (see #11022).

-}

haveRtsOptsFlags :: DynFlags -> Bool
haveRtsOptsFlags :: DynFlags -> Bool
haveRtsOptsFlags DynFlags
dflags =
        Maybe Suffix -> Bool
forall a. Maybe a -> Bool
isJust (DynFlags -> Maybe Suffix
rtsOpts DynFlags
dflags) Bool -> Bool -> Bool
|| case DynFlags -> RtsOptsEnabled
rtsOptsEnabled DynFlags
dflags of
                                       RtsOptsEnabled
RtsOptsSafeOnly -> Bool
False
                                       RtsOptsEnabled
_ -> Bool
True