{-# LANGUAGE CPP, MultiWayIf, ScopedTypeVariables #-}
module GHC.SysTools (
initSysTools,
lazyInitLlvmConfig,
module GHC.SysTools.Tasks,
module GHC.SysTools.Info,
linkDynLib,
copy,
copyWithHeader,
Option(..),
expandTopDir,
libmLinkOpts,
getPkgFrameworkOpts,
getFrameworkOpts
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Settings.Utils
import GHC.Unit
import GHC.Utils.Outputable
import GHC.Utils.Error
import GHC.Platform
import GHC.Driver.Session
import GHC.Driver.Ways
import Control.Monad.Trans.Except (runExceptT)
import System.FilePath
import System.IO
import System.IO.Unsafe (unsafeInterleaveIO)
import GHC.SysTools.ExtraObj
import GHC.SysTools.Info
import GHC.SysTools.Tasks
import GHC.SysTools.BaseDir
import GHC.Settings.IO
import qualified Data.Set as Set
lazyInitLlvmConfig :: String
-> IO LlvmConfig
lazyInitLlvmConfig :: String -> IO LlvmConfig
lazyInitLlvmConfig String
top_dir
= IO LlvmConfig -> IO LlvmConfig
forall a. IO a -> IO a
unsafeInterleaveIO (IO LlvmConfig -> IO LlvmConfig) -> IO LlvmConfig -> IO LlvmConfig
forall a b. (a -> b) -> a -> b
$ do
[(String, LlvmTarget)]
targets <- String
-> ((String, String, String) -> LlvmTarget)
-> IO [(String, LlvmTarget)]
forall {f :: * -> *} {f :: * -> *} {a} {b}.
(Read (f (f a)), Functor f, Functor f) =>
String -> (a -> b) -> IO (f (f b))
External instance of the constraint type forall a. Functor ((,) a)
External instance of the constraint type Functor []
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a b c. (Read a, Read b, Read c) => Read (a, b, c)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
readAndParse String
"llvm-targets" (String, String, String) -> LlvmTarget
mkLlvmTarget
[(Int, String)]
passes <- String -> (String -> String) -> IO [(Int, String)]
forall {f :: * -> *} {f :: * -> *} {a} {b}.
(Read (f (f a)), Functor f, Functor f) =>
String -> (a -> b) -> IO (f (f b))
External instance of the constraint type forall a. Functor ((,) a)
External instance of the constraint type Functor []
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read Int
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
readAndParse String
"llvm-passes" String -> String
forall a. a -> a
id
LlvmConfig -> IO LlvmConfig
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (LlvmConfig -> IO LlvmConfig) -> LlvmConfig -> IO LlvmConfig
forall a b. (a -> b) -> a -> b
$ LlvmConfig :: [(String, LlvmTarget)] -> [(Int, String)] -> LlvmConfig
LlvmConfig { llvmTargets :: [(String, LlvmTarget)]
llvmTargets = [(String, LlvmTarget)]
targets, llvmPasses :: [(Int, String)]
llvmPasses = [(Int, String)]
passes }
where
readAndParse :: String -> (a -> b) -> IO (f (f b))
readAndParse String
name a -> b
builder =
do let llvmConfigFile :: String
llvmConfigFile = String
top_dir String -> String -> String
</> String
name
String
llvmConfigStr <- String -> IO String
readFile String
llvmConfigFile
case String -> Maybe (f (f a))
forall a. Read a => String -> Maybe a
Evidence bound by a type signature of the constraint type Read (f (f a))
maybeReadFuzzy String
llvmConfigStr of
Just f (f a)
s -> f (f b) -> IO (f (f b))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ((a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap a -> b
builder (f a -> f b) -> f (f a) -> f (f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
<$> f (f a)
s)
Maybe (f (f a))
Nothing -> String -> IO (f (f b))
forall a. String -> a
pgmError (String
"Can't parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show String
llvmConfigFile)
mkLlvmTarget :: (String, String, String) -> LlvmTarget
mkLlvmTarget :: (String, String, String) -> LlvmTarget
mkLlvmTarget (String
dl, String
cpu, String
attrs) = String -> String -> [String] -> LlvmTarget
LlvmTarget String
dl String
cpu (String -> [String]
words String
attrs)
initSysTools :: String
-> IO Settings
initSysTools :: String -> IO Settings
initSysTools String
top_dir = do
Either SettingsError Settings
res <- ExceptT SettingsError IO Settings
-> IO (Either SettingsError Settings)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT SettingsError IO Settings
-> IO (Either SettingsError Settings))
-> ExceptT SettingsError IO Settings
-> IO (Either SettingsError Settings)
forall a b. (a -> b) -> a -> b
$ String -> ExceptT SettingsError IO Settings
forall (m :: * -> *).
MonadIO m =>
String -> ExceptT SettingsError m Settings
External instance of the constraint type MonadIO IO
initSettings String
top_dir
case Either SettingsError Settings
res of
Right Settings
a -> Settings -> IO Settings
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure Settings
a
Left (SettingsError_MissingData String
msg) -> String -> IO Settings
forall a. String -> a
pgmError String
msg
Left (SettingsError_BadData String
msg) -> String -> IO Settings
forall a. String -> a
pgmError String
msg
copy :: DynFlags -> String -> FilePath -> FilePath -> IO ()
copy :: DynFlags -> String -> String -> String -> IO ()
copy DynFlags
dflags String
purpose String
from String
to = DynFlags -> String -> Maybe String -> String -> String -> IO ()
copyWithHeader DynFlags
dflags String
purpose Maybe String
forall a. Maybe a
Nothing String
from String
to
copyWithHeader :: DynFlags -> String -> Maybe String -> FilePath -> FilePath
-> IO ()
DynFlags
dflags String
purpose Maybe String
maybe_header String
from String
to = do
DynFlags -> String -> IO ()
showPass DynFlags
dflags String
purpose
Handle
hout <- String -> IOMode -> IO Handle
openBinaryFile String
to IOMode
WriteMode
Handle
hin <- String -> IOMode -> IO Handle
openBinaryFile String
from IOMode
ReadMode
String
ls <- Handle -> IO String
hGetContents Handle
hin
IO () -> (String -> IO ()) -> Maybe String -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()) (Handle -> String -> IO ()
header Handle
hout) Maybe String
maybe_header
Handle -> String -> IO ()
hPutStr Handle
hout String
ls
Handle -> IO ()
hClose Handle
hout
Handle -> IO ()
hClose Handle
hin
where
header :: Handle -> String -> IO ()
header Handle
h String
str = do
Handle -> TextEncoding -> IO ()
hSetEncoding Handle
h TextEncoding
utf8
Handle -> String -> IO ()
hPutStr Handle
h String
str
Handle -> Bool -> IO ()
hSetBinaryMode Handle
h Bool
True
linkDynLib :: DynFlags -> [String] -> [UnitId] -> IO ()
linkDynLib :: DynFlags -> [String] -> [UnitId] -> IO ()
linkDynLib DynFlags
dflags0 [String]
o_files [UnitId]
dep_packages
= do
let
dflags1 :: DynFlags
dflags1 = if PlatformMisc -> Bool
platformMisc_ghcThreaded (PlatformMisc -> Bool) -> PlatformMisc -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> PlatformMisc
platformMisc DynFlags
dflags0
then Way -> DynFlags -> DynFlags
addWay' Way
WayThreaded DynFlags
dflags0
else DynFlags
dflags0
dflags2 :: DynFlags
dflags2 = if PlatformMisc -> Bool
platformMisc_ghcDebugged (PlatformMisc -> Bool) -> PlatformMisc -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> PlatformMisc
platformMisc DynFlags
dflags1
then Way -> DynFlags -> DynFlags
addWay' Way
WayDebug DynFlags
dflags1
else DynFlags
dflags1
dflags :: DynFlags
dflags = DynFlags -> DynFlags
updateWays DynFlags
dflags2
verbFlags :: [String]
verbFlags = DynFlags -> [String]
getVerbFlags DynFlags
dflags
o_file :: Maybe String
o_file = DynFlags -> Maybe String
outputFile DynFlags
dflags
[UnitInfo]
pkgs <- DynFlags -> [UnitId] -> IO [UnitInfo]
getPreloadPackagesAnd DynFlags
dflags [UnitId]
dep_packages
let pkg_lib_paths :: [String]
pkg_lib_paths = DynFlags -> [UnitInfo] -> [String]
collectLibraryPaths DynFlags
dflags [UnitInfo]
pkgs
let pkg_lib_path_opts :: [String]
pkg_lib_path_opts = (String -> [String]) -> [String] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap String -> [String]
get_pkg_lib_path_opts [String]
pkg_lib_paths
get_pkg_lib_path_opts :: String -> [String]
get_pkg_lib_path_opts String
l
| ( OS -> Bool
osElfTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) Bool -> Bool -> Bool
||
OS -> Bool
osMachOTarget (Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)) ) Bool -> Bool -> Bool
&&
DynFlags -> DynLibLoader
dynLibLoader DynFlags
dflags DynLibLoader -> DynLibLoader -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq DynLibLoader
== DynLibLoader
SystemDependent Bool -> Bool -> Bool
&&
Way
WayDyn Way -> Set Way -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord Way
`Set.member` DynFlags -> Set Way
ways DynFlags
dflags
= [String
"-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l, String
"-Xlinker", String
"-rpath", String
"-Xlinker", String
l]
| Bool
otherwise = [String
"-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l]
let lib_paths :: [String]
lib_paths = DynFlags -> [String]
libraryPaths DynFlags
dflags
let lib_path_opts :: [String]
lib_path_opts = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"-L"String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
lib_paths
let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
os :: OS
os = Platform -> OS
platformOS Platform
platform
pkgs_no_rts :: [UnitInfo]
pkgs_no_rts = case OS
os of
OS
OSMinGW32 ->
[UnitInfo]
pkgs
OS
_ ->
(UnitInfo -> Bool) -> [UnitInfo] -> [UnitInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
rtsUnitId) (Unit -> Bool) -> (UnitInfo -> Unit) -> UnitInfo -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInfo -> Unit
mkUnit) [UnitInfo]
pkgs
let pkg_link_opts :: [String]
pkg_link_opts = let ([String]
package_hs_libs, [String]
extra_libs, [String]
other_flags) = DynFlags -> [UnitInfo] -> ([String], [String], [String])
collectLinkOpts DynFlags
dflags [UnitInfo]
pkgs_no_rts
in [String]
package_hs_libs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extra_libs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
other_flags
let extra_ld_inputs :: [Option]
extra_ld_inputs = DynFlags -> [Option]
ldInputs DynFlags
dflags
[String]
pkg_framework_opts <- DynFlags -> Platform -> [UnitId] -> IO [String]
getPkgFrameworkOpts DynFlags
dflags Platform
platform
((UnitInfo -> UnitId) -> [UnitInfo] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map UnitInfo -> UnitId
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId [UnitInfo]
pkgs)
let framework_opts :: [String]
framework_opts = DynFlags -> Platform -> [String]
getFrameworkOpts DynFlags
dflags Platform
platform
case OS
os of
OS
OSMinGW32 -> do
let output_fn :: String
output_fn = case Maybe String
o_file of
Just String
s -> String
s
Maybe String
Nothing -> String
"HSdll.dll"
DynFlags -> [Option] -> IO ()
runLink DynFlags
dflags (
(String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
verbFlags
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-o"
, String -> String -> Option
FileOption String
"" String
output_fn
, String -> Option
Option String
"-shared"
] [Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++
[ String -> String -> Option
FileOption String
"-Wl,--out-implib=" (String
output_fn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".a")
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_SharedImplib DynFlags
dflags
]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> Option
FileOption String
"") [String]
o_files
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [String -> Option
Option String
"-Wl,--enable-auto-import"]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
extra_ld_inputs
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option (
[String]
lib_path_opts
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_lib_path_opts
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_link_opts
))
OS
_ | OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq OS
== OS
OSDarwin -> do
let output_fn :: String
output_fn = case Maybe String
o_file of { Just String
s -> String
s; Maybe String
Nothing -> String
"a.out"; }
String
instName <- case DynFlags -> Maybe String
dylibInstallName DynFlags
dflags of
Just String
n -> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return String
n
Maybe String
Nothing -> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String
"@rpath" String -> String -> String
`combine` (String -> String
takeFileName String
output_fn)
DynFlags -> [Option] -> IO ()
runLink DynFlags
dflags (
(String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
verbFlags
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-dynamiclib"
, String -> Option
Option String
"-o"
, String -> String -> Option
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
Option [String]
o_files
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-undefined",
String -> Option
Option String
"dynamic_lookup",
String -> Option
Option String
"-single_module" ]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (if Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== Arch
ArchX86_64
then [ ]
else [ String -> Option
Option String
"-Wl,-read_only_relocs,suppress" ])
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-install_name", String -> Option
Option String
instName ]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
lib_path_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
extra_ld_inputs
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
framework_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
pkg_lib_path_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
pkg_link_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
pkg_framework_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-Wl,-dead_strip_dylibs" ]
)
OS
_ -> do
let output_fn :: String
output_fn = case Maybe String
o_file of { Just String
s -> String
s; Maybe String
Nothing -> String
"a.out"; }
unregisterised :: Bool
unregisterised = Platform -> Bool
platformUnregisterised (DynFlags -> Platform
targetPlatform DynFlags
dflags)
let bsymbolicFlag :: [String]
bsymbolicFlag =
[String
"-Wl,-Bsymbolic" | Bool -> Bool
not Bool
unregisterised]
DynFlags -> [Option] -> IO ()
runLink DynFlags
dflags (
(String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
verbFlags
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
libmLinkOpts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-o"
, String -> String -> Option
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
Option [String]
o_files
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option String
"-shared" ]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
bsymbolicFlag
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [ String -> Option
Option (String
"-Wl,-h," String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
takeFileName String
output_fn) ]
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ [Option]
extra_ld_inputs
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
lib_path_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
pkg_lib_path_opts
[Option] -> [Option] -> [Option]
forall a. [a] -> [a] -> [a]
++ (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
pkg_link_opts
)
libmLinkOpts :: [Option]
libmLinkOpts :: [Option]
libmLinkOpts =
#if defined(HAVE_LIBM)
[Option "-lm"]
#else
[]
#endif
getPkgFrameworkOpts :: DynFlags -> Platform -> [UnitId] -> IO [String]
getPkgFrameworkOpts :: DynFlags -> Platform -> [UnitId] -> IO [String]
getPkgFrameworkOpts DynFlags
dflags Platform
platform [UnitId]
dep_packages
| Platform -> Bool
platformUsesFrameworks Platform
platform = do
[String]
pkg_framework_path_opts <- do
[String]
pkg_framework_paths <- DynFlags -> [UnitId] -> IO [String]
getPackageFrameworkPath DynFlags
dflags [UnitId]
dep_packages
[String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"-F" String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
pkg_framework_paths
[String]
pkg_framework_opts <- do
[String]
pkg_frameworks <- DynFlags -> [UnitId] -> IO [String]
getPackageFrameworks DynFlags
dflags [UnitId]
dep_packages
[String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [ [String
"-framework", String
fw] | String
fw <- [String]
pkg_frameworks ]
[String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ([String]
pkg_framework_path_opts [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pkg_framework_opts)
| Bool
otherwise = [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return []
getFrameworkOpts :: DynFlags -> Platform -> [String]
getFrameworkOpts :: DynFlags -> Platform -> [String]
getFrameworkOpts DynFlags
dflags Platform
platform
| Platform -> Bool
platformUsesFrameworks Platform
platform = [String]
framework_path_opts [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
framework_opts
| Bool
otherwise = []
where
framework_paths :: [String]
framework_paths = DynFlags -> [String]
frameworkPaths DynFlags
dflags
framework_path_opts :: [String]
framework_path_opts = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"-F" String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
framework_paths
frameworks :: [String]
frameworks = DynFlags -> [String]
cmdlineFrameworks DynFlags
dflags
framework_opts :: [String]
framework_opts = [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [ [String
"-framework", String
fw]
| String
fw <- [String] -> [String]
forall a. [a] -> [a]
reverse [String]
frameworks ]