{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module GHC.Settings.IO
( SettingsError (..)
, initSettings
) where
import GHC.Prelude
import GHC.Settings.Utils
import GHC.Settings.Config
import GHC.Utils.CliOption
import GHC.Utils.Fingerprint
import GHC.Platform
import GHC.Utils.Panic
import GHC.ResponseFile
import GHC.Settings
import GHC.SysTools.BaseDir
import GHC.Unit.Types
import Control.Monad.Trans.Except
import Control.Monad.IO.Class
import Data.Char
import qualified Data.Map as Map
import System.FilePath
import System.Directory
data SettingsError
= SettingsError_MissingData String
| SettingsError_BadData String
initSettings
:: forall m
. MonadIO m
=> String
-> ExceptT SettingsError m Settings
initSettings :: forall (m :: * -> *).
MonadIO m =>
String -> ExceptT SettingsError m Settings
initSettings String
top_dir = do
let installed :: FilePath -> FilePath
installed :: String -> String
installed String
file = String
top_dir String -> String -> String
</> String
file
libexec :: FilePath -> FilePath
libexec :: String -> String
libexec String
file = String
top_dir String -> String -> String
</> String
".." String -> String -> String
</> String
"bin" String -> String -> String
</> String
file
settingsFile :: String
settingsFile = String -> String
installed String
"settings"
readFileSafe :: FilePath -> ExceptT SettingsError m String
readFileSafe :: String -> ExceptT SettingsError m String
readFileSafe String
path = IO Bool -> ExceptT SettingsError m Bool
forall a. IO a -> ExceptT SettingsError m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO Bool
doesFileExist String
path) ExceptT SettingsError m Bool
-> (Bool -> ExceptT SettingsError m String)
-> ExceptT SettingsError m String
forall a b.
ExceptT SettingsError m a
-> (a -> ExceptT SettingsError m b) -> ExceptT SettingsError m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> IO String -> ExceptT SettingsError m String
forall a. IO a -> ExceptT SettingsError m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> ExceptT SettingsError m String)
-> IO String -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$ String -> IO String
readFile String
path
Bool
False -> SettingsError -> ExceptT SettingsError m String
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (SettingsError -> ExceptT SettingsError m String)
-> SettingsError -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$ String -> SettingsError
SettingsError_MissingData (String -> SettingsError) -> String -> SettingsError
forall a b. (a -> b) -> a -> b
$ String
"Missing file: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path
settingsStr <- String -> ExceptT SettingsError m String
readFileSafe String
settingsFile
settingsList <- case maybeReadFuzzy settingsStr of
Just [(String, String)]
s -> [(String, String)] -> ExceptT SettingsError m [(String, String)]
forall a. a -> ExceptT SettingsError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(String, String)]
s
Maybe [(String, String)]
Nothing -> SettingsError -> ExceptT SettingsError m [(String, String)]
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (SettingsError -> ExceptT SettingsError m [(String, String)])
-> SettingsError -> ExceptT SettingsError m [(String, String)]
forall a b. (a -> b) -> a -> b
$ String -> SettingsError
SettingsError_BadData (String -> SettingsError) -> String -> SettingsError
forall a b. (a -> b) -> a -> b
$
String
"Can't parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
settingsFile
let mySettings = [(String, String)] -> Map String String
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String, String)]
settingsList
getBooleanSetting :: String -> ExceptT SettingsError m Bool
getBooleanSetting String
key = (String -> ExceptT SettingsError m Bool)
-> (Bool -> ExceptT SettingsError m Bool)
-> Either String Bool
-> ExceptT SettingsError m Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m Bool
forall a. HasCallStack => String -> a
pgmError Bool -> ExceptT SettingsError m Bool
forall a. a -> ExceptT SettingsError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Bool -> ExceptT SettingsError m Bool)
-> Either String Bool -> ExceptT SettingsError m Bool
forall a b. (a -> b) -> a -> b
$
String -> Map String String -> String -> Either String Bool
getRawBooleanSetting String
settingsFile Map String String
mySettings String
key
useInplaceMinGW <- getBooleanSetting "Use inplace MinGW toolchain"
mtool_dir <- liftIO $ findToolDir useInplaceMinGW top_dir
let escaped_top_dir = String -> String
escapeArg String
top_dir
escaped_mtool_dir = (String -> String) -> Maybe String -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> String
escapeArg Maybe String
mtool_dir
getSetting_raw String
key = (String -> ExceptT SettingsError m String)
-> (String -> ExceptT SettingsError m String)
-> Either String String
-> ExceptT SettingsError m String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m String
forall a. HasCallStack => String -> a
pgmError String -> ExceptT SettingsError m String
forall a. a -> ExceptT SettingsError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String String -> ExceptT SettingsError m String)
-> Either String String -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$
String -> Map String String -> String -> Either String String
getRawSetting String
settingsFile Map String String
mySettings String
key
getSetting_topDir String
top String
key = (String -> ExceptT SettingsError m String)
-> (String -> ExceptT SettingsError m String)
-> Either String String
-> ExceptT SettingsError m String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m String
forall a. HasCallStack => String -> a
pgmError String -> ExceptT SettingsError m String
forall a. a -> ExceptT SettingsError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String String -> ExceptT SettingsError m String)
-> Either String String -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$
String
-> String -> Map String String -> String -> Either String String
getRawFilePathSetting String
top String
settingsFile Map String String
mySettings String
key
getSetting_toolDir String
top Maybe String
tool String
key =
Bool -> Maybe String -> String -> String
expandToolDir Bool
useInplaceMinGW Maybe String
tool (String -> String)
-> ExceptT SettingsError m String -> ExceptT SettingsError m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> ExceptT SettingsError m String
getSetting_topDir String
top String
key
getSetting :: String -> ExceptT SettingsError m String
getSetting String
key = String -> String -> ExceptT SettingsError m String
getSetting_topDir String
top_dir String
key
getToolSetting :: String -> ExceptT SettingsError m String
getToolSetting String
key = String -> Maybe String -> String -> ExceptT SettingsError m String
getSetting_toolDir String
top_dir Maybe String
mtool_dir String
key
getFlagsSetting :: String -> ExceptT SettingsError m [String]
getFlagsSetting String
key = String -> [String]
unescapeArgs (String -> [String])
-> ExceptT SettingsError m String
-> ExceptT SettingsError m [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe String -> String -> ExceptT SettingsError m String
getSetting_toolDir String
escaped_top_dir Maybe String
escaped_mtool_dir String
key
targetPlatformString <- getSetting_raw "target platform string"
cc_prog <- getToolSetting "C compiler command"
cxx_prog <- getToolSetting "C++ compiler command"
cc_args0 <- getFlagsSetting "C compiler flags"
cxx_args <- getFlagsSetting "C++ compiler flags"
gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
cmmCppSupportsG0 <- getBooleanSetting "C-- CPP supports -g0"
cpp_prog <- getToolSetting "CPP command"
cpp_args <- map Option <$> getFlagsSetting "CPP flags"
hs_cpp_prog <- getToolSetting "Haskell CPP command"
hs_cpp_args <- map Option <$> getFlagsSetting "Haskell CPP flags"
js_cpp_prog <- getToolSetting "JavaScript CPP command"
js_cpp_args <- map Option <$> getFlagsSetting "JavaScript CPP flags"
cmmCpp_prog <- getToolSetting "C-- CPP command"
cmmCpp_args <- map Option <$> getFlagsSetting "C-- CPP flags"
platform <- either pgmError pure $ getTargetPlatform settingsFile mySettings
let unreg_cc_args = if Platform -> Bool
platformUnregisterised Platform
platform
then [String
"-DNO_REGS", String
"-DUSE_MINIINTERPRETER"]
else []
cc_args = [String]
cc_args0 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
unreg_cc_args
extraGccViaCFlags = if Platform -> Bool
platformUnregisterised Platform
platform
then [String
"-fwrapv", String
"-fno-builtin"]
else []
ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
ldSupportsFilelist <- getBooleanSetting "ld supports filelist"
ldSupportsSingleModule <- getBooleanSetting "ld supports single module"
mergeObjsSupportsResponseFiles <- getBooleanSetting "Merge objects supports response files"
ldIsGnuLd <- getBooleanSetting "ld is GNU ld"
arSupportsDashL <- getBooleanSetting "ar supports -L"
globalpkgdb_path <- installed <$> getSetting "Relative Global Package DB"
let ghc_usage_msg_path = String -> String
installed String
"ghc-usage.txt"
ghci_usage_msg_path = String -> String
installed String
"ghci-usage.txt"
unlit_path <- getToolSetting "unlit command"
windres_path <- getToolSetting "windres command"
ar_path <- getToolSetting "ar command"
otool_path <- getToolSetting "otool command"
install_name_tool_path <- getToolSetting "install_name_tool command"
ranlib_path <- getToolSetting "ranlib command"
cc_link_args <- getFlagsSetting "C compiler link flags"
let as_prog = String
cc_prog
as_args = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
cc_args
ld_prog = String
cc_prog
ld_args = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option ([String]
cc_args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
cc_link_args)
ld_r_prog <- getToolSetting "Merge objects command"
ld_r_args <- getFlagsSetting "Merge objects flags"
let ld_r
| String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ld_r_prog = Maybe (String, [Option])
forall a. Maybe a
Nothing
| Bool
otherwise = (String, [Option]) -> Maybe (String, [Option])
forall a. a -> Maybe a
Just (String
ld_r_prog, (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
ld_r_args)
llvmTarget <- getSetting_raw "LLVM target"
lc_prog <- getToolSetting "LLVM llc command"
lo_prog <- getToolSetting "LLVM opt command"
las_prog <- getToolSetting "LLVM llvm-as command"
las_args <- map Option <$> getFlagsSetting "LLVM llvm-as flags"
let iserv_prog = String -> String
libexec String
"ghc-iserv"
targetRTSLinkerOnlySupportsSharedLibs <- getBooleanSetting "target RTS linker only supports shared libraries"
ghcWithInterpreter <- getBooleanSetting "Use interpreter"
useLibFFI <- getBooleanSetting "Use LibFFI"
baseUnitId <- getSetting_raw "base unit-id"
return $ Settings
{ sGhcNameVersion = GhcNameVersion
{ ghcNameVersion_programName = "ghc"
, ghcNameVersion_projectVersion = cProjectVersion
}
, sFileSettings = FileSettings
{ fileSettings_ghcUsagePath = ghc_usage_msg_path
, fileSettings_ghciUsagePath = ghci_usage_msg_path
, fileSettings_toolDir = mtool_dir
, fileSettings_topDir = top_dir
, fileSettings_globalPackageDatabase = globalpkgdb_path
}
, sUnitSettings = UnitSettings
{
unitSettings_baseUnitId = stringToUnitId baseUnitId
}
, sToolSettings = ToolSettings
{ toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
, toolSettings_ldSupportsFilelist = ldSupportsFilelist
, toolSettings_ldSupportsSingleModule = ldSupportsSingleModule
, toolSettings_mergeObjsSupportsResponseFiles = mergeObjsSupportsResponseFiles
, toolSettings_ldIsGnuLd = ldIsGnuLd
, toolSettings_ccSupportsNoPie = gccSupportsNoPie
, toolSettings_useInplaceMinGW = useInplaceMinGW
, toolSettings_arSupportsDashL = arSupportsDashL
, toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0
, toolSettings_pgm_L = unlit_path
, toolSettings_pgm_P = (hs_cpp_prog, hs_cpp_args)
, toolSettings_pgm_JSP = (js_cpp_prog, js_cpp_args)
, toolSettings_pgm_CmmP = (cmmCpp_prog, cmmCpp_args)
, toolSettings_pgm_F = ""
, toolSettings_pgm_c = cc_prog
, toolSettings_pgm_cxx = cxx_prog
, toolSettings_pgm_cpp = (cpp_prog, cpp_args)
, toolSettings_pgm_a = (as_prog, as_args)
, toolSettings_pgm_l = (ld_prog, ld_args)
, toolSettings_pgm_lm = ld_r
, toolSettings_pgm_windres = windres_path
, toolSettings_pgm_ar = ar_path
, toolSettings_pgm_otool = otool_path
, toolSettings_pgm_install_name_tool = install_name_tool_path
, toolSettings_pgm_ranlib = ranlib_path
, toolSettings_pgm_lo = (lo_prog,[])
, toolSettings_pgm_lc = (lc_prog,[])
, toolSettings_pgm_las = (las_prog, las_args)
, toolSettings_pgm_i = iserv_prog
, toolSettings_opt_L = []
, toolSettings_opt_P = []
, toolSettings_opt_JSP = []
, toolSettings_opt_CmmP = []
, toolSettings_opt_P_fingerprint = fingerprint0
, toolSettings_opt_JSP_fingerprint = fingerprint0
, toolSettings_opt_CmmP_fingerprint = fingerprint0
, toolSettings_opt_F = []
, toolSettings_opt_c = cc_args
, toolSettings_opt_cxx = cxx_args
, toolSettings_opt_a = []
, toolSettings_opt_l = []
, toolSettings_opt_lm = []
, toolSettings_opt_windres = []
, toolSettings_opt_lo = []
, toolSettings_opt_lc = []
, toolSettings_opt_las = []
, toolSettings_opt_i = []
, toolSettings_extraGccViaCFlags = extraGccViaCFlags
}
, sTargetPlatform = platform
, sPlatformMisc = PlatformMisc
{ platformMisc_targetPlatformString = targetPlatformString
, platformMisc_ghcWithInterpreter = ghcWithInterpreter
, platformMisc_libFFI = useLibFFI
, platformMisc_llvmTarget = llvmTarget
, platformMisc_targetRTSLinkerOnlySupportsSharedLibs = targetRTSLinkerOnlySupportsSharedLibs
}
, sRawSettings = settingsList
}
getTargetPlatform
:: FilePath
-> RawSettings
-> Either String Platform
getTargetPlatform :: String -> Map String String -> Either String Platform
getTargetPlatform String
settingsFile Map String String
settings = do
let
getBooleanSetting :: String -> Either String Bool
getBooleanSetting = String -> Map String String -> String -> Either String Bool
getRawBooleanSetting String
settingsFile Map String String
settings
readSetting :: (Show a, Read a) => String -> Either String a
readSetting :: forall a. (Show a, Read a) => String -> Either String a
readSetting = String -> Map String String -> String -> Either String a
forall a.
(Show a, Read a) =>
String -> Map String String -> String -> Either String a
readRawSetting String
settingsFile Map String String
settings
targetArchOS <- String -> Map String String -> Either String ArchOS
getTargetArchOS String
settingsFile Map String String
settings
targetWordSize <- readSetting "target word size"
targetWordBigEndian <- getBooleanSetting "target word big endian"
targetLeadingUnderscore <- getBooleanSetting "Leading underscore"
targetUnregisterised <- getBooleanSetting "Unregisterised"
targetHasGnuNonexecStack <- getBooleanSetting "target has GNU nonexec stack"
targetHasIdentDirective <- getBooleanSetting "target has .ident directive"
targetHasSubsectionsViaSymbols <- getBooleanSetting "target has subsections via symbols"
targetHasLibm <- getBooleanSetting "target has libm"
crossCompiling <- getBooleanSetting "cross compiling"
tablesNextToCode <- getBooleanSetting "Tables next to code"
pure $ Platform
{ platformArchOS = targetArchOS
, platformWordSize = targetWordSize
, platformByteOrder = if targetWordBigEndian then BigEndian else LittleEndian
, platformUnregisterised = targetUnregisterised
, platformHasGnuNonexecStack = targetHasGnuNonexecStack
, platformHasIdentDirective = targetHasIdentDirective
, platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols
, platformIsCrossCompiling = crossCompiling
, platformLeadingUnderscore = targetLeadingUnderscore
, platformTablesNextToCode = tablesNextToCode
, platformHasLibm = targetHasLibm
, platform_constants = Nothing
}
escapeArg :: String -> String
escapeArg :: String -> String
escapeArg = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Char -> String) -> String -> String -> String
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' String -> Char -> String
escape []
escape :: String -> Char -> String
escape :: String -> Char -> String
escape String
cs Char
c
| Char -> Bool
isSpace Char
c
Bool -> Bool -> Bool
|| Char
'\\' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c
Bool -> Bool -> Bool
|| Char
'\'' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c
Bool -> Bool -> Bool
|| Char
'"' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c = Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:String
cs
| Bool
otherwise = Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:String
cs