{-# 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 Data.Char
import Control.Monad.Trans.Except
import Control.Monad.IO.Class
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
"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
String
settingsStr <- String -> ExceptT SettingsError m String
readFileSafe String
settingsFile
[(String, String)]
settingsList <- case String -> Maybe [(String, String)]
forall a. Read a => String -> Maybe a
maybeReadFuzzy String
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 :: Map String String
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 -> 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
Bool
useInplaceMinGW <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use inplace MinGW toolchain"
Maybe String
mtool_dir <- IO (Maybe String) -> ExceptT SettingsError m (Maybe String)
forall a. IO a -> ExceptT SettingsError m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> ExceptT SettingsError m (Maybe String))
-> IO (Maybe String) -> ExceptT SettingsError m (Maybe String)
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO (Maybe String)
findToolDir Bool
useInplaceMinGW String
top_dir
let getSetting :: String -> ExceptT SettingsError m String
getSetting 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 -> String
escapeArg String
top_dir) String
settingsFile Map String String
mySettings String
key
getToolSetting :: String -> ExceptT SettingsError m String
getToolSetting :: String -> ExceptT SettingsError m String
getToolSetting String
key = Bool -> Maybe String -> String -> String
expandToolDir Bool
useInplaceMinGW ((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) (String -> String)
-> ExceptT SettingsError m String -> ExceptT SettingsError m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ExceptT SettingsError m String
getSetting String
key
String
targetPlatformString <- String -> ExceptT SettingsError m String
getSetting String
"target platform string"
String
myExtraGccViaCFlags <- String -> ExceptT SettingsError m String
getSetting String
"GCC extra via C opts"
String
cc_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"C compiler command"
String
cxx_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"C++ compiler command"
String
cc_args_str <- String -> ExceptT SettingsError m String
getToolSetting String
"C compiler flags"
String
cxx_args_str <- String -> ExceptT SettingsError m String
getToolSetting String
"C++ compiler flags"
Bool
gccSupportsNoPie <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"C compiler supports -no-pie"
String
cpp_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"Haskell CPP command"
String
cpp_args_str <- String -> ExceptT SettingsError m String
getToolSetting String
"Haskell CPP flags"
Platform
platform <- (String -> ExceptT SettingsError m Platform)
-> (Platform -> ExceptT SettingsError m Platform)
-> Either String Platform
-> ExceptT SettingsError m Platform
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m Platform
forall a. HasCallStack => String -> a
pgmError Platform -> ExceptT SettingsError m Platform
forall a. a -> ExceptT SettingsError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Platform -> ExceptT SettingsError m Platform)
-> Either String Platform -> ExceptT SettingsError m Platform
forall a b. (a -> b) -> a -> b
$ String -> Map String String -> Either String Platform
getTargetPlatform String
settingsFile Map String String
mySettings
let unreg_cc_args :: [String]
unreg_cc_args = if Platform -> Bool
platformUnregisterised Platform
platform
then [String
"-DNO_REGS", String
"-DUSE_MINIINTERPRETER"]
else []
cpp_args :: [Option]
cpp_args = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option (String -> [String]
unescapeArgs String
cpp_args_str)
cc_args :: [String]
cc_args = String -> [String]
unescapeArgs String
cc_args_str [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
unreg_cc_args
cxx_args :: [String]
cxx_args = String -> [String]
unescapeArgs String
cxx_args_str
Bool
ldSupportsCompactUnwind <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports compact unwind"
Bool
ldSupportsFilelist <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports filelist"
Bool
ldSupportsSingleModule <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports single module"
Bool
ldIsGnuLd <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld is GNU ld"
Bool
arSupportsDashL <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ar supports -L"
let globalpkgdb_path :: String
globalpkgdb_path = String -> String
installed String
"package.conf.d"
ghc_usage_msg_path :: String
ghc_usage_msg_path = String -> String
installed String
"ghc-usage.txt"
ghci_usage_msg_path :: String
ghci_usage_msg_path = String -> String
installed String
"ghci-usage.txt"
String
unlit_path <- String -> ExceptT SettingsError m String
getToolSetting String
"unlit command"
String
windres_path <- String -> ExceptT SettingsError m String
getToolSetting String
"windres command"
String
ar_path <- String -> ExceptT SettingsError m String
getToolSetting String
"ar command"
String
otool_path <- String -> ExceptT SettingsError m String
getToolSetting String
"otool command"
String
install_name_tool_path <- String -> ExceptT SettingsError m String
getToolSetting String
"install_name_tool command"
String
ranlib_path <- String -> ExceptT SettingsError m String
getToolSetting String
"ranlib command"
String
touch_path <- String -> ExceptT SettingsError m String
getToolSetting String
"touch command"
String
mkdll_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"dllwrap command"
let mkdll_args :: [a]
mkdll_args = []
String
cc_link_args_str <- String -> ExceptT SettingsError m String
getToolSetting String
"C compiler link flags"
let as_prog :: String
as_prog = String
cc_prog
as_args :: [Option]
as_args = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
cc_args
ld_prog :: String
ld_prog = String
cc_prog
ld_args :: [Option]
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 -> [String]
unescapeArgs String
cc_link_args_str)
String
ld_r_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"Merge objects command"
String
ld_r_args <- String -> ExceptT SettingsError m String
getToolSetting String
"Merge objects flags"
let ld_r :: Maybe (String, [Option])
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] -> [Option]) -> [String] -> [Option]
forall a b. (a -> b) -> a -> b
$ String -> [String]
unescapeArgs String
ld_r_args)
String
llvmTarget <- String -> ExceptT SettingsError m String
getSetting String
"LLVM target"
String
lc_prog <- String -> ExceptT SettingsError m String
getSetting String
"LLVM llc command"
String
lo_prog <- String -> ExceptT SettingsError m String
getSetting String
"LLVM opt command"
String
lcc_prog <- String -> ExceptT SettingsError m String
getSetting String
"LLVM clang command"
let iserv_prog :: String
iserv_prog = String -> String
libexec String
"ghc-iserv"
Bool
ghcWithInterpreter <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use interpreter"
Bool
useLibFFI <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use LibFFI"
Settings -> ExceptT SettingsError m Settings
forall a. a -> ExceptT SettingsError m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Settings -> ExceptT SettingsError m Settings)
-> Settings -> ExceptT SettingsError m Settings
forall a b. (a -> b) -> a -> b
$ Settings
{ sGhcNameVersion :: GhcNameVersion
sGhcNameVersion = GhcNameVersion
{ ghcNameVersion_programName :: String
ghcNameVersion_programName = String
"ghc"
, ghcNameVersion_projectVersion :: String
ghcNameVersion_projectVersion = String
cProjectVersion
}
, sFileSettings :: FileSettings
sFileSettings = FileSettings
{ fileSettings_ghcUsagePath :: String
fileSettings_ghcUsagePath = String
ghc_usage_msg_path
, fileSettings_ghciUsagePath :: String
fileSettings_ghciUsagePath = String
ghci_usage_msg_path
, fileSettings_toolDir :: Maybe String
fileSettings_toolDir = Maybe String
mtool_dir
, fileSettings_topDir :: String
fileSettings_topDir = String
top_dir
, fileSettings_globalPackageDatabase :: String
fileSettings_globalPackageDatabase = String
globalpkgdb_path
}
, sToolSettings :: ToolSettings
sToolSettings = ToolSettings
{ toolSettings_ldSupportsCompactUnwind :: Bool
toolSettings_ldSupportsCompactUnwind = Bool
ldSupportsCompactUnwind
, toolSettings_ldSupportsFilelist :: Bool
toolSettings_ldSupportsFilelist = Bool
ldSupportsFilelist
, toolSettings_ldSupportsSingleModule :: Bool
toolSettings_ldSupportsSingleModule = Bool
ldSupportsSingleModule
, toolSettings_ldIsGnuLd :: Bool
toolSettings_ldIsGnuLd = Bool
ldIsGnuLd
, toolSettings_ccSupportsNoPie :: Bool
toolSettings_ccSupportsNoPie = Bool
gccSupportsNoPie
, toolSettings_useInplaceMinGW :: Bool
toolSettings_useInplaceMinGW = Bool
useInplaceMinGW
, toolSettings_arSupportsDashL :: Bool
toolSettings_arSupportsDashL = Bool
arSupportsDashL
, toolSettings_pgm_L :: String
toolSettings_pgm_L = String
unlit_path
, toolSettings_pgm_P :: (String, [Option])
toolSettings_pgm_P = (String
cpp_prog, [Option]
cpp_args)
, toolSettings_pgm_F :: String
toolSettings_pgm_F = String
""
, toolSettings_pgm_c :: String
toolSettings_pgm_c = String
cc_prog
, toolSettings_pgm_cxx :: String
toolSettings_pgm_cxx = String
cxx_prog
, toolSettings_pgm_a :: (String, [Option])
toolSettings_pgm_a = (String
as_prog, [Option]
as_args)
, toolSettings_pgm_l :: (String, [Option])
toolSettings_pgm_l = (String
ld_prog, [Option]
ld_args)
, toolSettings_pgm_lm :: Maybe (String, [Option])
toolSettings_pgm_lm = Maybe (String, [Option])
ld_r
, toolSettings_pgm_dll :: (String, [Option])
toolSettings_pgm_dll = (String
mkdll_prog,[Option]
forall a. [a]
mkdll_args)
, toolSettings_pgm_T :: String
toolSettings_pgm_T = String
touch_path
, toolSettings_pgm_windres :: String
toolSettings_pgm_windres = String
windres_path
, toolSettings_pgm_ar :: String
toolSettings_pgm_ar = String
ar_path
, toolSettings_pgm_otool :: String
toolSettings_pgm_otool = String
otool_path
, toolSettings_pgm_install_name_tool :: String
toolSettings_pgm_install_name_tool = String
install_name_tool_path
, toolSettings_pgm_ranlib :: String
toolSettings_pgm_ranlib = String
ranlib_path
, toolSettings_pgm_lo :: (String, [Option])
toolSettings_pgm_lo = (String
lo_prog,[])
, toolSettings_pgm_lc :: (String, [Option])
toolSettings_pgm_lc = (String
lc_prog,[])
, toolSettings_pgm_lcc :: (String, [Option])
toolSettings_pgm_lcc = (String
lcc_prog,[])
, toolSettings_pgm_i :: String
toolSettings_pgm_i = String
iserv_prog
, toolSettings_opt_L :: [String]
toolSettings_opt_L = []
, toolSettings_opt_P :: [String]
toolSettings_opt_P = []
, toolSettings_opt_P_fingerprint :: Fingerprint
toolSettings_opt_P_fingerprint = Fingerprint
fingerprint0
, toolSettings_opt_F :: [String]
toolSettings_opt_F = []
, toolSettings_opt_c :: [String]
toolSettings_opt_c = [String]
cc_args
, toolSettings_opt_cxx :: [String]
toolSettings_opt_cxx = [String]
cxx_args
, toolSettings_opt_a :: [String]
toolSettings_opt_a = []
, toolSettings_opt_l :: [String]
toolSettings_opt_l = []
, toolSettings_opt_lm :: [String]
toolSettings_opt_lm = []
, toolSettings_opt_windres :: [String]
toolSettings_opt_windres = []
, toolSettings_opt_lcc :: [String]
toolSettings_opt_lcc = []
, toolSettings_opt_lo :: [String]
toolSettings_opt_lo = []
, toolSettings_opt_lc :: [String]
toolSettings_opt_lc = []
, toolSettings_opt_i :: [String]
toolSettings_opt_i = []
, toolSettings_extraGccViaCFlags :: [String]
toolSettings_extraGccViaCFlags = String -> [String]
words String
myExtraGccViaCFlags
}
, sTargetPlatform :: Platform
sTargetPlatform = Platform
platform
, sPlatformMisc :: PlatformMisc
sPlatformMisc = PlatformMisc
{ platformMisc_targetPlatformString :: String
platformMisc_targetPlatformString = String
targetPlatformString
, platformMisc_ghcWithInterpreter :: Bool
platformMisc_ghcWithInterpreter = Bool
ghcWithInterpreter
, platformMisc_libFFI :: Bool
platformMisc_libFFI = Bool
useLibFFI
, platformMisc_llvmTarget :: String
platformMisc_llvmTarget = String
llvmTarget
}
, sRawSettings :: [(String, String)]
sRawSettings = [(String, String)]
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
ArchOS
targetArchOS <- String -> Map String String -> Either String ArchOS
getTargetArchOS String
settingsFile Map String String
settings
PlatformWordSize
targetWordSize <- String -> Either String PlatformWordSize
forall a. (Show a, Read a) => String -> Either String a
readSetting String
"target word size"
Bool
targetWordBigEndian <- String -> Either String Bool
getBooleanSetting String
"target word big endian"
Bool
targetLeadingUnderscore <- String -> Either String Bool
getBooleanSetting String
"Leading underscore"
Bool
targetUnregisterised <- String -> Either String Bool
getBooleanSetting String
"Unregisterised"
Bool
targetHasGnuNonexecStack <- String -> Either String Bool
getBooleanSetting String
"target has GNU nonexec stack"
Bool
targetHasIdentDirective <- String -> Either String Bool
getBooleanSetting String
"target has .ident directive"
Bool
targetHasSubsectionsViaSymbols <- String -> Either String Bool
getBooleanSetting String
"target has subsections via symbols"
Bool
targetHasLibm <- String -> Either String Bool
getBooleanSetting String
"target has libm"
Bool
crossCompiling <- String -> Either String Bool
getBooleanSetting String
"cross compiling"
Bool
tablesNextToCode <- String -> Either String Bool
getBooleanSetting String
"Tables next to code"
Platform -> Either String Platform
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Platform -> Either String Platform)
-> Platform -> Either String Platform
forall a b. (a -> b) -> a -> b
$ Platform
{ platformArchOS :: ArchOS
platformArchOS = ArchOS
targetArchOS
, platformWordSize :: PlatformWordSize
platformWordSize = PlatformWordSize
targetWordSize
, platformByteOrder :: ByteOrder
platformByteOrder = if Bool
targetWordBigEndian then ByteOrder
BigEndian else ByteOrder
LittleEndian
, platformUnregisterised :: Bool
platformUnregisterised = Bool
targetUnregisterised
, platformHasGnuNonexecStack :: Bool
platformHasGnuNonexecStack = Bool
targetHasGnuNonexecStack
, platformHasIdentDirective :: Bool
platformHasIdentDirective = Bool
targetHasIdentDirective
, platformHasSubsectionsViaSymbols :: Bool
platformHasSubsectionsViaSymbols = Bool
targetHasSubsectionsViaSymbols
, platformIsCrossCompiling :: Bool
platformIsCrossCompiling = Bool
crossCompiling
, platformLeadingUnderscore :: Bool
platformLeadingUnderscore = Bool
targetLeadingUnderscore
, platformTablesNextToCode :: Bool
platformTablesNextToCode = Bool
tablesNextToCode
, platformHasLibm :: Bool
platformHasLibm = Bool
targetHasLibm
, platform_constants :: Maybe PlatformConstants
platform_constants = Maybe PlatformConstants
forall a. Maybe a
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