{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.Simple.Program.GHC (
GhcOptions(..),
GhcMode(..),
GhcOptimisation(..),
GhcDynLinkMode(..),
GhcProfAuto(..),
ghcInvocation,
renderGhcOptions,
runGHC,
packageDbArgsDb,
normaliseGhcArgs
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Backpack
import Distribution.Compat.Semigroup (First'(..), Last'(..), Option'(..))
import Distribution.Simple.GHC.ImplInfo
import Distribution.PackageDescription
import Distribution.ModuleName
import Distribution.Simple.Compiler
import Distribution.Simple.Flag
import Distribution.Simple.Program.Types
import Distribution.Simple.Program.Run
import Distribution.System
import Distribution.Pretty
import Distribution.Types.ComponentId
import Distribution.Types.ModuleRenaming
import Distribution.Verbosity
import Distribution.Version
import Distribution.Utils.NubList
import Language.Haskell.Extension
import Data.List (stripPrefix)
import qualified Data.Map as Map
import Data.Monoid (All(..), Any(..), Endo(..))
import qualified Data.Set as Set
normaliseGhcArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
normaliseGhcArgs :: Maybe Version -> PackageDescription -> [[Char]] -> [[Char]]
normaliseGhcArgs (Just Version
ghcVersion) PackageDescription{[Char]
[[Char]]
[([Char], [Char])]
[(CompilerFlavor, VersionRange)]
[SourceRepo]
[TestSuite]
[Library]
[ForeignLib]
[Executable]
[Benchmark]
Maybe BuildType
Maybe SetupBuildInfo
Maybe Library
Either License License
ShortText
CabalSpecVersion
PackageIdentifier
testedWith :: PackageDescription -> [(CompilerFlavor, VersionRange)]
testSuites :: PackageDescription -> [TestSuite]
synopsis :: PackageDescription -> ShortText
subLibraries :: PackageDescription -> [Library]
stability :: PackageDescription -> ShortText
specVersion :: PackageDescription -> CabalSpecVersion
sourceRepos :: PackageDescription -> [SourceRepo]
setupBuildInfo :: PackageDescription -> Maybe SetupBuildInfo
pkgUrl :: PackageDescription -> ShortText
package :: PackageDescription -> PackageIdentifier
maintainer :: PackageDescription -> ShortText
licenseRaw :: PackageDescription -> Either License License
licenseFiles :: PackageDescription -> [[Char]]
library :: PackageDescription -> Maybe Library
homepage :: PackageDescription -> ShortText
foreignLibs :: PackageDescription -> [ForeignLib]
extraTmpFiles :: PackageDescription -> [[Char]]
extraSrcFiles :: PackageDescription -> [[Char]]
extraDocFiles :: PackageDescription -> [[Char]]
executables :: PackageDescription -> [Executable]
description :: PackageDescription -> ShortText
dataFiles :: PackageDescription -> [[Char]]
dataDir :: PackageDescription -> [Char]
customFieldsPD :: PackageDescription -> [([Char], [Char])]
copyright :: PackageDescription -> ShortText
category :: PackageDescription -> ShortText
buildTypeRaw :: PackageDescription -> Maybe BuildType
bugReports :: PackageDescription -> ShortText
benchmarks :: PackageDescription -> [Benchmark]
author :: PackageDescription -> ShortText
extraDocFiles :: [[Char]]
extraTmpFiles :: [[Char]]
extraSrcFiles :: [[Char]]
dataDir :: [Char]
dataFiles :: [[Char]]
benchmarks :: [Benchmark]
testSuites :: [TestSuite]
foreignLibs :: [ForeignLib]
executables :: [Executable]
subLibraries :: [Library]
library :: Maybe Library
setupBuildInfo :: Maybe SetupBuildInfo
buildTypeRaw :: Maybe BuildType
customFieldsPD :: [([Char], [Char])]
category :: ShortText
description :: ShortText
synopsis :: ShortText
sourceRepos :: [SourceRepo]
bugReports :: ShortText
pkgUrl :: ShortText
homepage :: ShortText
testedWith :: [(CompilerFlavor, VersionRange)]
stability :: ShortText
author :: ShortText
maintainer :: ShortText
copyright :: ShortText
licenseFiles :: [[Char]]
licenseRaw :: Either License License
package :: PackageIdentifier
specVersion :: CabalSpecVersion
..} [[Char]]
ghcArgs
| Version
ghcVersion Version -> VersionRange -> Bool
`withinRange` VersionRange
supportedGHCVersions
= [[Char]] -> [[Char]]
argumentFilters ([[Char]] -> [[Char]])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Char] -> Bool
simpleFilters ([[Char]] -> [[Char]])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
filterRtsOpts ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [[Char]]
ghcArgs
where
supportedGHCVersions :: VersionRange
supportedGHCVersions :: VersionRange
supportedGHCVersions = VersionRange -> VersionRange -> VersionRange
intersectVersionRanges
(Version -> VersionRange
orLaterVersion ([Int] -> Version
mkVersion [Int
8,Int
0]))
(Version -> VersionRange
earlierVersion ([Int] -> Version
mkVersion [Int
9,Int
1]))
from :: Monoid m => [Int] -> m -> m
from :: forall m. Monoid m => [Int] -> m -> m
from [Int]
version m
flags
| Version
ghcVersion Version -> VersionRange -> Bool
`withinRange` Version -> VersionRange
orLaterVersion ([Int] -> Version
mkVersion [Int]
version) = m
flags
| Bool
otherwise = m
forall a. Monoid a => a
mempty
to :: Monoid m => [Int] -> m -> m
to :: forall m. Monoid m => [Int] -> m -> m
to [Int]
version m
flags
| Version
ghcVersion Version -> VersionRange -> Bool
`withinRange` Version -> VersionRange
earlierVersion ([Int] -> Version
mkVersion [Int]
version) = m
flags
| Bool
otherwise = m
forall a. Monoid a => a
mempty
checkGhcFlags :: forall m . Monoid m => ([String] -> m) -> m
checkGhcFlags :: forall m. Monoid m => ([[Char]] -> m) -> m
checkGhcFlags [[Char]] -> m
fun = [m] -> m
forall a. Monoid a => [a] -> a
mconcat
[ [[Char]] -> m
fun [[Char]]
ghcArgs
, (Library -> BuildInfo) -> [Library] -> m
forall a. (a -> BuildInfo) -> [a] -> m
checkComponentFlags Library -> BuildInfo
libBuildInfo [Library]
pkgLibs
, (Executable -> BuildInfo) -> [Executable] -> m
forall a. (a -> BuildInfo) -> [a] -> m
checkComponentFlags Executable -> BuildInfo
buildInfo [Executable]
executables
, (TestSuite -> BuildInfo) -> [TestSuite] -> m
forall a. (a -> BuildInfo) -> [a] -> m
checkComponentFlags TestSuite -> BuildInfo
testBuildInfo [TestSuite]
testSuites
, (Benchmark -> BuildInfo) -> [Benchmark] -> m
forall a. (a -> BuildInfo) -> [a] -> m
checkComponentFlags Benchmark -> BuildInfo
benchmarkBuildInfo [Benchmark]
benchmarks
]
where
pkgLibs :: [Library]
pkgLibs = Maybe Library -> [Library]
forall a. Maybe a -> [a]
maybeToList Maybe Library
library [Library] -> [Library] -> [Library]
forall a. [a] -> [a] -> [a]
++ [Library]
subLibraries
checkComponentFlags :: (a -> BuildInfo) -> [a] -> m
checkComponentFlags :: forall a. (a -> BuildInfo) -> [a] -> m
checkComponentFlags a -> BuildInfo
getInfo = (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (BuildInfo -> m
checkComponent (BuildInfo -> m) -> (a -> BuildInfo) -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> BuildInfo
getInfo)
where
checkComponent :: BuildInfo -> m
checkComponent :: BuildInfo -> m
checkComponent = ([[Char]] -> m) -> [[[Char]]] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap [[Char]] -> m
fun ([[[Char]]] -> m) -> (BuildInfo -> [[[Char]]]) -> BuildInfo -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(CompilerFlavor, [[Char]])] -> [[[Char]]]
filterGhcOptions ([(CompilerFlavor, [[Char]])] -> [[[Char]]])
-> (BuildInfo -> [(CompilerFlavor, [[Char]])])
-> BuildInfo
-> [[[Char]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildInfo -> [(CompilerFlavor, [[Char]])]
allGhcOptions
allGhcOptions :: BuildInfo -> [(CompilerFlavor, [String])]
allGhcOptions :: BuildInfo -> [(CompilerFlavor, [[Char]])]
allGhcOptions = ((BuildInfo -> PerCompilerFlavor [[Char]])
-> BuildInfo -> [(CompilerFlavor, [[Char]])])
-> [BuildInfo -> PerCompilerFlavor [[Char]]]
-> BuildInfo
-> [(CompilerFlavor, [[Char]])]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (PerCompilerFlavor [[Char]] -> [(CompilerFlavor, [[Char]])]
forall v. PerCompilerFlavor v -> [(CompilerFlavor, v)]
perCompilerFlavorToList (PerCompilerFlavor [[Char]] -> [(CompilerFlavor, [[Char]])])
-> (BuildInfo -> PerCompilerFlavor [[Char]])
-> BuildInfo
-> [(CompilerFlavor, [[Char]])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)
[BuildInfo -> PerCompilerFlavor [[Char]]
options, BuildInfo -> PerCompilerFlavor [[Char]]
profOptions, BuildInfo -> PerCompilerFlavor [[Char]]
sharedOptions, BuildInfo -> PerCompilerFlavor [[Char]]
staticOptions]
filterGhcOptions :: [(CompilerFlavor, [String])] -> [[String]]
filterGhcOptions :: [(CompilerFlavor, [[Char]])] -> [[[Char]]]
filterGhcOptions [(CompilerFlavor, [[Char]])]
l = [[[Char]]
opts | (CompilerFlavor
GHC, [[Char]]
opts) <- [(CompilerFlavor, [[Char]])]
l]
safeToFilterWarnings :: Bool
safeToFilterWarnings :: Bool
safeToFilterWarnings = All -> Bool
getAll (All -> Bool) -> All -> Bool
forall a b. (a -> b) -> a -> b
$ ([[Char]] -> All) -> All
forall m. Monoid m => ([[Char]] -> m) -> m
checkGhcFlags [[Char]] -> All
checkWarnings
where
checkWarnings :: [String] -> All
checkWarnings :: [[Char]] -> All
checkWarnings = Bool -> All
All (Bool -> All) -> ([[Char]] -> Bool) -> [[Char]] -> All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set [Char] -> Bool
forall a. Set a -> Bool
Set.null (Set [Char] -> Bool)
-> ([[Char]] -> Set [Char]) -> [[Char]] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Set [Char] -> Set [Char])
-> Set [Char] -> [[Char]] -> Set [Char]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr [Char] -> Set [Char] -> Set [Char]
alter Set [Char]
forall a. Set a
Set.empty
alter :: String -> Set String -> Set String
alter :: [Char] -> Set [Char] -> Set [Char]
alter [Char]
flag = Endo (Set [Char]) -> Set [Char] -> Set [Char]
forall a. Endo a -> a -> a
appEndo (Endo (Set [Char]) -> Set [Char] -> Set [Char])
-> Endo (Set [Char]) -> Set [Char] -> Set [Char]
forall a b. (a -> b) -> a -> b
$ [[Char] -> Endo (Set [Char])] -> [Char] -> Endo (Set [Char])
forall a. Monoid a => [a] -> a
mconcat
[ \[Char]
s -> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ if [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"-Werror" then [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => a -> Set a -> Set a
Set.insert [Char]
s else Set [Char] -> Set [Char]
forall a. a -> a
id
, \[Char]
s -> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ if [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"-Wwarn" then Set [Char] -> Set [Char] -> Set [Char]
forall a b. a -> b -> a
const Set [Char]
forall a. Set a
Set.empty else Set [Char] -> Set [Char]
forall a. a -> a
id
, \[Char]
s -> [Int] -> Endo (Set [Char]) -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] (Endo (Set [Char]) -> Endo (Set [Char]))
-> ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char])
-> Endo (Set [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$
if [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"-Werror=compat"
then Set [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => Set a -> Set a -> Set a
Set.union Set [Char]
compatWarningSet else Set [Char] -> Set [Char]
forall a. a -> a
id
, \[Char]
s -> [Int] -> Endo (Set [Char]) -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] (Endo (Set [Char]) -> Endo (Set [Char]))
-> ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char])
-> Endo (Set [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$
if [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"-Wno-error=compat"
then (Set [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set [Char]
compatWarningSet) else Set [Char] -> Set [Char]
forall a. a -> a
id
, \[Char]
s -> [Int] -> Endo (Set [Char]) -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] (Endo (Set [Char]) -> Endo (Set [Char]))
-> ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char])
-> Endo (Set [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$
if [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"-Wwarn=compat"
then (Set [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set [Char]
compatWarningSet) else Set [Char] -> Set [Char]
forall a. a -> a
id
, [Int]
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] (([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char]))
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ [Char]
-> ([Char] -> Set [Char] -> Set [Char])
-> [Char]
-> Endo (Set [Char])
markFlag [Char]
"-Werror=" [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => a -> Set a -> Set a
Set.insert
, [Int]
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] (([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char]))
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ [Char]
-> ([Char] -> Set [Char] -> Set [Char])
-> [Char]
-> Endo (Set [Char])
markFlag [Char]
"-Wwarn=" [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => a -> Set a -> Set a
Set.delete
, [Int]
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] (([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char]))
-> ([Char] -> Endo (Set [Char])) -> [Char] -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ [Char]
-> ([Char] -> Set [Char] -> Set [Char])
-> [Char]
-> Endo (Set [Char])
markFlag [Char]
"-Wno-error=" [Char] -> Set [Char] -> Set [Char]
forall a. Ord a => a -> Set a -> Set a
Set.delete
] [Char]
flag
markFlag
:: String
-> (String -> Set String -> Set String)
-> String
-> Endo (Set String)
markFlag :: [Char]
-> ([Char] -> Set [Char] -> Set [Char])
-> [Char]
-> Endo (Set [Char])
markFlag [Char]
name [Char] -> Set [Char] -> Set [Char]
update [Char]
flag = (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a. (a -> a) -> Endo a
Endo ((Set [Char] -> Set [Char]) -> Endo (Set [Char]))
-> (Set [Char] -> Set [Char]) -> Endo (Set [Char])
forall a b. (a -> b) -> a -> b
$ case [Char] -> [Char] -> Maybe [Char]
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix [Char]
name [Char]
flag of
Just [Char]
rest | Bool -> Bool
not ([Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
rest) Bool -> Bool -> Bool
&& [Char]
rest [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char]
"compat" -> [Char] -> Set [Char] -> Set [Char]
update [Char]
rest
Maybe [Char]
_ -> Set [Char] -> Set [Char]
forall a. a -> a
id
flagArgumentFilter :: [String] -> [String] -> [String]
flagArgumentFilter :: [[Char]] -> [[Char]] -> [[Char]]
flagArgumentFilter [[Char]]
flags = [[Char]] -> [[Char]]
go
where
makeFilter :: String -> String -> Option' (First' ([String] -> [String]))
makeFilter :: [Char] -> [Char] -> Option' (First' ([[Char]] -> [[Char]]))
makeFilter [Char]
flag [Char]
arg = Maybe (First' ([[Char]] -> [[Char]]))
-> Option' (First' ([[Char]] -> [[Char]]))
forall a. Maybe a -> Option' a
Option' (Maybe (First' ([[Char]] -> [[Char]]))
-> Option' (First' ([[Char]] -> [[Char]])))
-> Maybe (First' ([[Char]] -> [[Char]]))
-> Option' (First' ([[Char]] -> [[Char]]))
forall a b. (a -> b) -> a -> b
$ ([[Char]] -> [[Char]]) -> First' ([[Char]] -> [[Char]])
forall a. a -> First' a
First' (([[Char]] -> [[Char]]) -> First' ([[Char]] -> [[Char]]))
-> ([Char] -> [[Char]] -> [[Char]])
-> [Char]
-> First' ([[Char]] -> [[Char]])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]] -> [[Char]]
forall {a}. [Char] -> [a] -> [a]
filterRest ([Char] -> First' ([[Char]] -> [[Char]]))
-> Maybe [Char] -> Maybe (First' ([[Char]] -> [[Char]]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> [Char] -> Maybe [Char]
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix [Char]
flag [Char]
arg
where
filterRest :: [Char] -> [a] -> [a]
filterRest [Char]
leftOver = case [Char] -> [Char]
dropEq [Char]
leftOver of
[] -> Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
1
[Char]
_ -> [a] -> [a]
forall a. a -> a
id
checkFilter :: String -> Maybe ([String] -> [String])
checkFilter :: [Char] -> Maybe ([[Char]] -> [[Char]])
checkFilter = (First' ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]])
-> Maybe (First' ([[Char]] -> [[Char]]))
-> Maybe ([[Char]] -> [[Char]])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap First' ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a. First' a -> a
getFirst' (Maybe (First' ([[Char]] -> [[Char]]))
-> Maybe ([[Char]] -> [[Char]]))
-> ([Char] -> Maybe (First' ([[Char]] -> [[Char]])))
-> [Char]
-> Maybe ([[Char]] -> [[Char]])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option' (First' ([[Char]] -> [[Char]]))
-> Maybe (First' ([[Char]] -> [[Char]]))
forall a. Option' a -> Maybe a
getOption' (Option' (First' ([[Char]] -> [[Char]]))
-> Maybe (First' ([[Char]] -> [[Char]])))
-> ([Char] -> Option' (First' ([[Char]] -> [[Char]])))
-> [Char]
-> Maybe (First' ([[Char]] -> [[Char]]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [Char] -> Option' (First' ([[Char]] -> [[Char]])))
-> [[Char]] -> [Char] -> Option' (First' ([[Char]] -> [[Char]]))
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap [Char] -> [Char] -> Option' (First' ([[Char]] -> [[Char]]))
makeFilter [[Char]]
flags
go :: [String] -> [String]
go :: [[Char]] -> [[Char]]
go [] = []
go ([Char]
arg:[[Char]]
args) = case [Char] -> Maybe ([[Char]] -> [[Char]])
checkFilter [Char]
arg of
Just [[Char]] -> [[Char]]
f -> [[Char]] -> [[Char]]
go ([[Char]] -> [[Char]]
f [[Char]]
args)
Maybe ([[Char]] -> [[Char]])
Nothing -> [Char]
arg [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]] -> [[Char]]
go [[Char]]
args
argumentFilters :: [String] -> [String]
argumentFilters :: [[Char]] -> [[Char]]
argumentFilters = [[Char]] -> [[Char]] -> [[Char]]
flagArgumentFilter
[[Char]
"-ghci-script", [Char]
"-H", [Char]
"-interactive-print"]
filterRtsOpts :: [String] -> [String]
filterRtsOpts :: [[Char]] -> [[Char]]
filterRtsOpts = Bool -> [[Char]] -> [[Char]]
go Bool
False
where
go :: Bool -> [String] -> [String]
go :: Bool -> [[Char]] -> [[Char]]
go Bool
_ [] = []
go Bool
_ ([Char]
"+RTS":[[Char]]
opts) = Bool -> [[Char]] -> [[Char]]
go Bool
True [[Char]]
opts
go Bool
_ ([Char]
"-RTS":[[Char]]
opts) = Bool -> [[Char]] -> [[Char]]
go Bool
False [[Char]]
opts
go Bool
isRTSopts ([Char]
opt:[[Char]]
opts) = [[Char]] -> [[Char]]
addOpt ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ Bool -> [[Char]] -> [[Char]]
go Bool
isRTSopts [[Char]]
opts
where
addOpt :: [[Char]] -> [[Char]]
addOpt | Bool
isRTSopts = [[Char]] -> [[Char]]
forall a. a -> a
id
| Bool
otherwise = ([Char]
opt[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:)
simpleFilters :: String -> Bool
simpleFilters :: [Char] -> Bool
simpleFilters = Bool -> Bool
not (Bool -> Bool) -> ([Char] -> Bool) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Any -> Bool
getAny (Any -> Bool) -> ([Char] -> Any) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat
[ Set [Char] -> [Char] -> Any
flagIn Set [Char]
simpleFlags
, Bool -> Any
Any (Bool -> Any) -> ([Char] -> Bool) -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf [Char]
"-ddump-"
, Bool -> Any
Any (Bool -> Any) -> ([Char] -> Bool) -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf [Char]
"-dsuppress-"
, Bool -> Any
Any (Bool -> Any) -> ([Char] -> Bool) -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf [Char]
"-dno-suppress-"
, Set [Char] -> [Char] -> Any
flagIn (Set [Char] -> [Char] -> Any) -> Set [Char] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> Set [Char]
invertibleFlagSet [Char]
"-" [[Char]
"ignore-dot-ghci"]
, Set [Char] -> [Char] -> Any
flagIn (Set [Char] -> [Char] -> Any)
-> ([[[Char]]] -> Set [Char]) -> [[[Char]]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]] -> Set [Char]
invertibleFlagSet [Char]
"-f" ([[Char]] -> Set [Char])
-> ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> Set [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Char]]] -> [[Char]]
forall a. Monoid a => [a] -> a
mconcat ([[[Char]]] -> [Char] -> Any) -> [[[Char]]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
[ [ [Char]
"reverse-errors", [Char]
"warn-unused-binds", [Char]
"break-on-error"
, [Char]
"break-on-exception", [Char]
"print-bind-result"
, [Char]
"print-bind-contents", [Char]
"print-evld-with-show"
, [Char]
"implicit-import-qualified", [Char]
"error-spans"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
7,Int
8]
[ [Char]
"print-explicit-foralls"
, [Char]
"print-explicit-kinds"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
0]
[ [Char]
"print-explicit-coercions"
, [Char]
"print-explicit-runtime-reps"
, [Char]
"print-equality-relations"
, [Char]
"print-unicode-syntax"
, [Char]
"print-expanded-synonyms"
, [Char]
"print-potential-instances"
, [Char]
"print-typechecker-elaboration"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
2]
[ [Char]
"diagnostics-show-caret", [Char]
"local-ghci-history"
, [Char]
"show-warning-groups", [Char]
"hide-source-paths"
, [Char]
"show-hole-constraints"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] [[Char]
"show-loaded-modules"]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] [ [Char]
"ghci-leak-check", [Char]
"no-it" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
10]
[ [Char]
"defer-diagnostics"
, [Char]
"keep-going"
, [Char]
"print-axiom-incomps"
]
]
, Set [Char] -> [Char] -> Any
flagIn (Set [Char] -> [Char] -> Any)
-> ([[Char]] -> Set [Char]) -> [[Char]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]] -> Set [Char]
invertibleFlagSet [Char]
"-d" ([[Char]] -> [Char] -> Any) -> [[Char]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$ [ [Char]
"ppr-case-as-let", [Char]
"ppr-ticks" ]
, [Char] -> Any
isOptIntFlag
, [Char] -> Any
isIntFlag
, if Bool
safeToFilterWarnings
then [Char] -> Any
isWarning ([Char] -> Any) -> ([Char] -> Any) -> [Char] -> Any
forall a. Semigroup a => a -> a -> a
<> (Bool -> Any
Any (Bool -> Any) -> ([Char] -> Bool) -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char]
"-w"[Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
==))
else [Char] -> Any
forall a. Monoid a => a
mempty
, [Int] -> ([Char] -> Any) -> [Char] -> Any
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] (([Char] -> Any) -> [Char] -> Any)
-> ([Char] -> Any) -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
if Bool
safeToFilterHoles
then [Char] -> Any
isTypedHoleFlag
else [Char] -> Any
forall a. Monoid a => a
mempty
]
flagIn :: Set String -> String -> Any
flagIn :: Set [Char] -> [Char] -> Any
flagIn Set [Char]
set [Char]
flag = Bool -> Any
Any (Bool -> Any) -> Bool -> Any
forall a b. (a -> b) -> a -> b
$ [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member [Char]
flag Set [Char]
set
isWarning :: String -> Any
isWarning :: [Char] -> Any
isWarning = [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat ([[Char] -> Any] -> [Char] -> Any)
-> [[Char] -> Any] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$ ([Char] -> [Char] -> Any) -> [[Char]] -> [[Char] -> Any]
forall a b. (a -> b) -> [a] -> [b]
map ((Bool -> Any
Any (Bool -> Any) -> ([Char] -> Bool) -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) (([Char] -> Bool) -> [Char] -> Any)
-> ([Char] -> [Char] -> Bool) -> [Char] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf)
[[Char]
"-fwarn-", [Char]
"-fno-warn-", [Char]
"-W", [Char]
"-Wno-"]
simpleFlags :: Set String
simpleFlags :: Set [Char]
simpleFlags = [[Char]] -> Set [Char]
forall a. Ord a => [a] -> Set a
Set.fromList ([[Char]] -> Set [Char])
-> ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> Set [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Char]]] -> [[Char]]
forall a. Monoid a => [a] -> a
mconcat ([[[Char]]] -> Set [Char]) -> [[[Char]]] -> Set [Char]
forall a b. (a -> b) -> a -> b
$
[ [ [Char]
"-n", [Char]
"-#include", [Char]
"-Rghc-timing", [Char]
"-dstg-stats"
, [Char]
"-dth-dec-file", [Char]
"-dsource-stats", [Char]
"-dverbose-core2core"
, [Char]
"-dverbose-stg2stg", [Char]
"-dcore-lint", [Char]
"-dstg-lint", [Char]
"-dcmm-lint"
, [Char]
"-dasm-lint", [Char]
"-dannot-lint", [Char]
"-dshow-passes", [Char]
"-dfaststring-stats"
, [Char]
"-fno-max-relevant-binds", [Char]
"-recomp", [Char]
"-no-recomp", [Char]
"-fforce-recomp"
, [Char]
"-fno-force-recomp"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
2]
[ [Char]
"-fno-max-errors", [Char]
"-fdiagnostics-color=auto"
, [Char]
"-fdiagnostics-color=always", [Char]
"-fdiagnostics-color=never"
, [Char]
"-dppr-debug", [Char]
"-dno-debug-output"
]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] [ [Char]
"-ddebug-output" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
to [Int
8,Int
6] [ [Char]
"-fno-max-valid-substitutions" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6] [ [Char]
"-dhex-word-literals" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
8] [ [Char]
"-fshow-docs-of-hole-fits", [Char]
"-fno-show-docs-of-hole-fits" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
9,Int
0] [ [Char]
"-dlinear-core-lint" ]
]
isOptIntFlag :: String -> Any
isOptIntFlag :: [Char] -> Any
isOptIntFlag = [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat ([[Char] -> Any] -> [Char] -> Any)
-> ([[Char]] -> [[Char] -> Any]) -> [[Char]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [Char] -> Any) -> [[Char]] -> [[Char] -> Any]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> [Char] -> [Char] -> Any
dropIntFlag Bool
True) ([[Char]] -> [Char] -> Any) -> [[Char]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$ [[Char]
"-v", [Char]
"-j"]
isIntFlag :: String -> Any
isIntFlag :: [Char] -> Any
isIntFlag = [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat ([[Char] -> Any] -> [Char] -> Any)
-> ([[[Char]]] -> [[Char] -> Any]) -> [[[Char]]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [Char] -> Any) -> [[Char]] -> [[Char] -> Any]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> [Char] -> [Char] -> Any
dropIntFlag Bool
False) ([[Char]] -> [[Char] -> Any])
-> ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> [[Char] -> Any]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Char]]] -> [[Char]]
forall a. Monoid a => [a] -> a
mconcat ([[[Char]]] -> [Char] -> Any) -> [[[Char]]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
[ [ [Char]
"-fmax-relevant-binds", [Char]
"-ddpr-user-length", [Char]
"-ddpr-cols"
, [Char]
"-dtrace-level", [Char]
"-fghci-hist-size" ]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
2] [[Char]
"-fmax-uncovered-patterns", [Char]
"-fmax-errors"]
, [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
4] ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
to [Int
8,Int
6] [[Char]
"-fmax-valid-substitutions"]
]
dropIntFlag :: Bool -> String -> String -> Any
dropIntFlag :: Bool -> [Char] -> [Char] -> Any
dropIntFlag Bool
isOpt [Char]
flag [Char]
input = Bool -> Any
Any (Bool -> Any) -> Bool -> Any
forall a b. (a -> b) -> a -> b
$ case [Char] -> [Char] -> Maybe [Char]
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix [Char]
flag [Char]
input of
Maybe [Char]
Nothing -> Bool
False
Just [Char]
rest | Bool
isOpt Bool -> Bool -> Bool
&& [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
rest -> Bool
True
| Bool
otherwise -> case [Char] -> Maybe Int
parseInt [Char]
rest of
Just Int
_ -> Bool
True
Maybe Int
Nothing -> Bool
False
where
parseInt :: String -> Maybe Int
parseInt :: [Char] -> Maybe Int
parseInt = [Char] -> Maybe Int
forall a. Read a => [Char] -> Maybe a
readMaybe ([Char] -> Maybe Int) -> ([Char] -> [Char]) -> [Char] -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
dropEq
dropEq :: String -> String
dropEq :: [Char] -> [Char]
dropEq (Char
'=':[Char]
s) = [Char]
s
dropEq [Char]
s = [Char]
s
invertibleFlagSet :: String -> [String] -> Set String
invertibleFlagSet :: [Char] -> [[Char]] -> Set [Char]
invertibleFlagSet [Char]
prefix [[Char]]
flagNames =
[[Char]] -> Set [Char]
forall a. Ord a => [a] -> Set a
Set.fromList ([[Char]] -> Set [Char]) -> [[Char]] -> Set [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
(++) ([Char] -> [Char] -> [Char]) -> [[Char]] -> [[Char] -> [Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Char]
prefix, [Char]
prefix [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"no-"] [[Char] -> [Char]] -> [[Char]] -> [[Char]]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [[Char]]
flagNames
compatWarningSet :: Set String
compatWarningSet :: Set [Char]
compatWarningSet = [[Char]] -> Set [Char]
forall a. Ord a => [a] -> Set a
Set.fromList ([[Char]] -> Set [Char]) -> [[Char]] -> Set [Char]
forall a b. (a -> b) -> a -> b
$ [[[Char]]] -> [[Char]]
forall a. Monoid a => [a] -> a
mconcat
[ [Int] -> [[Char]] -> [[Char]]
forall m. Monoid m => [Int] -> m -> m
from [Int
8,Int
6]
[ [Char]
"missing-monadfail-instances", [Char]
"semigroup"
, [Char]
"noncanonical-monoid-instances", [Char]
"implicit-kind-vars" ]
]
safeToFilterHoles :: Bool
safeToFilterHoles :: Bool
safeToFilterHoles = All -> Bool
getAll (All -> Bool)
-> (([[Char]] -> All) -> All) -> ([[Char]] -> All) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]] -> All) -> All
forall m. Monoid m => ([[Char]] -> m) -> m
checkGhcFlags (([[Char]] -> All) -> Bool) -> ([[Char]] -> All) -> Bool
forall a b. (a -> b) -> a -> b
$
Bool -> All
All (Bool -> All) -> ([[Char]] -> Bool) -> [[Char]] -> All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool)
-> ([[Char]] -> Maybe Bool) -> [[Char]] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Last' Bool -> Bool) -> Maybe (Last' Bool) -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Last' Bool -> Bool
forall a. Last' a -> a
getLast' (Maybe (Last' Bool) -> Maybe Bool)
-> ([[Char]] -> Maybe (Last' Bool)) -> [[Char]] -> Maybe Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option' (Last' Bool) -> Maybe (Last' Bool)
forall a. Option' a -> Maybe a
getOption' (Option' (Last' Bool) -> Maybe (Last' Bool))
-> ([[Char]] -> Option' (Last' Bool))
-> [[Char]]
-> Maybe (Last' Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Option' (Last' Bool))
-> [[Char]] -> Option' (Last' Bool)
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap [Char] -> Option' (Last' Bool)
notDeferred
where
notDeferred :: String -> Option' (Last' Bool)
notDeferred :: [Char] -> Option' (Last' Bool)
notDeferred [Char]
"-fdefer-typed-holes" = Maybe (Last' Bool) -> Option' (Last' Bool)
forall a. Maybe a -> Option' a
Option' (Maybe (Last' Bool) -> Option' (Last' Bool))
-> (Bool -> Maybe (Last' Bool)) -> Bool -> Option' (Last' Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Last' Bool -> Maybe (Last' Bool)
forall a. a -> Maybe a
Just (Last' Bool -> Maybe (Last' Bool))
-> (Bool -> Last' Bool) -> Bool -> Maybe (Last' Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Last' Bool
forall a. a -> Last' a
Last' (Bool -> Option' (Last' Bool)) -> Bool -> Option' (Last' Bool)
forall a b. (a -> b) -> a -> b
$ Bool
False
notDeferred [Char]
"-fno-defer-typed-holes" = Maybe (Last' Bool) -> Option' (Last' Bool)
forall a. Maybe a -> Option' a
Option' (Maybe (Last' Bool) -> Option' (Last' Bool))
-> (Bool -> Maybe (Last' Bool)) -> Bool -> Option' (Last' Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Last' Bool -> Maybe (Last' Bool)
forall a. a -> Maybe a
Just (Last' Bool -> Maybe (Last' Bool))
-> (Bool -> Last' Bool) -> Bool -> Maybe (Last' Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Last' Bool
forall a. a -> Last' a
Last' (Bool -> Option' (Last' Bool)) -> Bool -> Option' (Last' Bool)
forall a b. (a -> b) -> a -> b
$ Bool
True
notDeferred [Char]
_ = Maybe (Last' Bool) -> Option' (Last' Bool)
forall a. Maybe a -> Option' a
Option' Maybe (Last' Bool)
forall a. Maybe a
Nothing
isTypedHoleFlag :: String -> Any
isTypedHoleFlag :: [Char] -> Any
isTypedHoleFlag = [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat
[ Set [Char] -> [Char] -> Any
flagIn (Set [Char] -> [Char] -> Any)
-> ([[Char]] -> Set [Char]) -> [[Char]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]] -> Set [Char]
invertibleFlagSet [Char]
"-f" ([[Char]] -> [Char] -> Any) -> [[Char]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
[ [Char]
"show-hole-constraints", [Char]
"show-valid-substitutions"
, [Char]
"show-valid-hole-fits", [Char]
"sort-valid-hole-fits"
, [Char]
"sort-by-size-hole-fits", [Char]
"sort-by-subsumption-hole-fits"
, [Char]
"abstract-refinement-hole-fits", [Char]
"show-provenance-of-hole-fits"
, [Char]
"show-hole-matches-of-hole-fits", [Char]
"show-type-of-hole-fits"
, [Char]
"show-type-app-of-hole-fits", [Char]
"show-type-app-vars-of-hole-fits"
, [Char]
"unclutter-valid-hole-fits"
]
, Set [Char] -> [Char] -> Any
flagIn (Set [Char] -> [Char] -> Any)
-> ([[Char]] -> Set [Char]) -> [[Char]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> Set [Char]
forall a. Ord a => [a] -> Set a
Set.fromList ([[Char]] -> [Char] -> Any) -> [[Char]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
[ [Char]
"-fno-max-valid-hole-fits", [Char]
"-fno-max-refinement-hole-fits"
, [Char]
"-fno-refinement-level-hole-fits" ]
, [[Char] -> Any] -> [Char] -> Any
forall a. Monoid a => [a] -> a
mconcat ([[Char] -> Any] -> [Char] -> Any)
-> ([[Char]] -> [[Char] -> Any]) -> [[Char]] -> [Char] -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [Char] -> Any) -> [[Char]] -> [[Char] -> Any]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> [Char] -> [Char] -> Any
dropIntFlag Bool
False) ([[Char]] -> [Char] -> Any) -> [[Char]] -> [Char] -> Any
forall a b. (a -> b) -> a -> b
$
[ [Char]
"-fmax-valid-hole-fits", [Char]
"-fmax-refinement-hole-fits"
, [Char]
"-frefinement-level-hole-fits" ]
]
normaliseGhcArgs Maybe Version
_ PackageDescription
_ [[Char]]
args = [[Char]]
args
data GhcOptions = GhcOptions {
GhcOptions -> Flag GhcMode
ghcOptMode :: Flag GhcMode,
:: [String],
:: [String],
GhcOptions -> NubListR [Char]
ghcOptInputFiles :: NubListR FilePath,
GhcOptions -> NubListR ModuleName
ghcOptInputModules :: NubListR ModuleName,
GhcOptions -> Flag [Char]
ghcOptOutputFile :: Flag FilePath,
GhcOptions -> Flag [Char]
ghcOptOutputDynFile :: Flag FilePath,
GhcOptions -> Flag Bool
ghcOptSourcePathClear :: Flag Bool,
GhcOptions -> NubListR [Char]
ghcOptSourcePath :: NubListR FilePath,
GhcOptions -> Flag [Char]
ghcOptThisUnitId :: Flag String,
GhcOptions -> Flag ComponentId
ghcOptThisComponentId :: Flag ComponentId,
GhcOptions -> [(ModuleName, OpenModule)]
ghcOptInstantiatedWith :: [(ModuleName, OpenModule)],
GhcOptions -> Flag Bool
ghcOptNoCode :: Flag Bool,
GhcOptions -> PackageDBStack
ghcOptPackageDBs :: PackageDBStack,
GhcOptions -> NubListR (OpenUnitId, ModuleRenaming)
ghcOptPackages ::
NubListR (OpenUnitId, ModuleRenaming),
GhcOptions -> Flag Bool
ghcOptHideAllPackages :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptWarnMissingHomeModules :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptNoAutoLinkPackages :: Flag Bool,
GhcOptions -> [[Char]]
ghcOptLinkLibs :: [FilePath],
GhcOptions -> NubListR [Char]
ghcOptLinkLibPath :: NubListR FilePath,
GhcOptions -> [[Char]]
ghcOptLinkOptions :: [String],
GhcOptions -> NubListR [Char]
ghcOptLinkFrameworks :: NubListR String,
GhcOptions -> NubListR [Char]
ghcOptLinkFrameworkDirs :: NubListR String,
GhcOptions -> Flag Bool
ghcOptNoLink :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptLinkNoHsMain :: Flag Bool,
GhcOptions -> NubListR [Char]
ghcOptLinkModDefFiles :: NubListR FilePath,
GhcOptions -> [[Char]]
ghcOptCcOptions :: [String],
GhcOptions -> [[Char]]
ghcOptCxxOptions :: [String],
GhcOptions -> [[Char]]
ghcOptAsmOptions :: [String],
GhcOptions -> [[Char]]
ghcOptCppOptions :: [String],
GhcOptions -> NubListR [Char]
ghcOptCppIncludePath :: NubListR FilePath,
GhcOptions -> NubListR [Char]
ghcOptCppIncludes :: NubListR FilePath,
GhcOptions -> NubListR [Char]
ghcOptFfiIncludes :: NubListR FilePath,
GhcOptions -> Flag Language
ghcOptLanguage :: Flag Language,
GhcOptions -> NubListR Extension
ghcOptExtensions :: NubListR Extension,
GhcOptions -> Map Extension (Maybe [Char])
ghcOptExtensionMap :: Map Extension (Maybe CompilerFlag),
GhcOptions -> Flag GhcOptimisation
ghcOptOptimisation :: Flag GhcOptimisation,
GhcOptions -> Flag DebugInfoLevel
ghcOptDebugInfo :: Flag DebugInfoLevel,
GhcOptions -> Flag Bool
ghcOptProfilingMode :: Flag Bool,
GhcOptions -> Flag GhcProfAuto
ghcOptProfilingAuto :: Flag GhcProfAuto,
GhcOptions -> Flag Bool
ghcOptSplitSections :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptSplitObjs :: Flag Bool,
GhcOptions -> Flag (Maybe Int)
ghcOptNumJobs :: Flag (Maybe Int),
GhcOptions -> Flag [Char]
ghcOptHPCDir :: Flag FilePath,
GhcOptions -> [[Char]]
ghcOptGHCiScripts :: [FilePath],
GhcOptions -> Flag [Char]
ghcOptHiSuffix :: Flag String,
GhcOptions -> Flag [Char]
ghcOptObjSuffix :: Flag String,
GhcOptions -> Flag [Char]
ghcOptDynHiSuffix :: Flag String,
GhcOptions -> Flag [Char]
ghcOptDynObjSuffix :: Flag String,
GhcOptions -> Flag [Char]
ghcOptHiDir :: Flag FilePath,
GhcOptions -> Flag [Char]
ghcOptObjDir :: Flag FilePath,
GhcOptions -> Flag [Char]
ghcOptOutputDir :: Flag FilePath,
GhcOptions -> Flag [Char]
ghcOptStubDir :: Flag FilePath,
GhcOptions -> Flag GhcDynLinkMode
ghcOptDynLinkMode :: Flag GhcDynLinkMode,
GhcOptions -> Flag Bool
ghcOptStaticLib :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptShared :: Flag Bool,
GhcOptions -> Flag Bool
ghcOptFPic :: Flag Bool,
GhcOptions -> Flag [Char]
ghcOptDylibName :: Flag String,
GhcOptions -> NubListR [Char]
ghcOptRPaths :: NubListR FilePath,
GhcOptions -> Flag Verbosity
ghcOptVerbosity :: Flag Verbosity,
:: NubListR FilePath,
GhcOptions -> Flag Bool
ghcOptCabal :: Flag Bool
} deriving (Int -> GhcOptions -> [Char] -> [Char]
[GhcOptions] -> [Char] -> [Char]
GhcOptions -> [Char]
(Int -> GhcOptions -> [Char] -> [Char])
-> (GhcOptions -> [Char])
-> ([GhcOptions] -> [Char] -> [Char])
-> Show GhcOptions
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [GhcOptions] -> [Char] -> [Char]
$cshowList :: [GhcOptions] -> [Char] -> [Char]
show :: GhcOptions -> [Char]
$cshow :: GhcOptions -> [Char]
showsPrec :: Int -> GhcOptions -> [Char] -> [Char]
$cshowsPrec :: Int -> GhcOptions -> [Char] -> [Char]
Show, (forall x. GhcOptions -> Rep GhcOptions x)
-> (forall x. Rep GhcOptions x -> GhcOptions) -> Generic GhcOptions
forall x. Rep GhcOptions x -> GhcOptions
forall x. GhcOptions -> Rep GhcOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhcOptions x -> GhcOptions
$cfrom :: forall x. GhcOptions -> Rep GhcOptions x
Generic)
data GhcMode = GhcModeCompile
| GhcModeLink
| GhcModeMake
| GhcModeInteractive
| GhcModeAbiHash
deriving (Int -> GhcMode -> [Char] -> [Char]
[GhcMode] -> [Char] -> [Char]
GhcMode -> [Char]
(Int -> GhcMode -> [Char] -> [Char])
-> (GhcMode -> [Char])
-> ([GhcMode] -> [Char] -> [Char])
-> Show GhcMode
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [GhcMode] -> [Char] -> [Char]
$cshowList :: [GhcMode] -> [Char] -> [Char]
show :: GhcMode -> [Char]
$cshow :: GhcMode -> [Char]
showsPrec :: Int -> GhcMode -> [Char] -> [Char]
$cshowsPrec :: Int -> GhcMode -> [Char] -> [Char]
Show, GhcMode -> GhcMode -> Bool
(GhcMode -> GhcMode -> Bool)
-> (GhcMode -> GhcMode -> Bool) -> Eq GhcMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcMode -> GhcMode -> Bool
$c/= :: GhcMode -> GhcMode -> Bool
== :: GhcMode -> GhcMode -> Bool
$c== :: GhcMode -> GhcMode -> Bool
Eq)
data GhcOptimisation = GhcNoOptimisation
| GhcNormalOptimisation
| GhcMaximumOptimisation
| GhcSpecialOptimisation String
deriving (Int -> GhcOptimisation -> [Char] -> [Char]
[GhcOptimisation] -> [Char] -> [Char]
GhcOptimisation -> [Char]
(Int -> GhcOptimisation -> [Char] -> [Char])
-> (GhcOptimisation -> [Char])
-> ([GhcOptimisation] -> [Char] -> [Char])
-> Show GhcOptimisation
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [GhcOptimisation] -> [Char] -> [Char]
$cshowList :: [GhcOptimisation] -> [Char] -> [Char]
show :: GhcOptimisation -> [Char]
$cshow :: GhcOptimisation -> [Char]
showsPrec :: Int -> GhcOptimisation -> [Char] -> [Char]
$cshowsPrec :: Int -> GhcOptimisation -> [Char] -> [Char]
Show, GhcOptimisation -> GhcOptimisation -> Bool
(GhcOptimisation -> GhcOptimisation -> Bool)
-> (GhcOptimisation -> GhcOptimisation -> Bool)
-> Eq GhcOptimisation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcOptimisation -> GhcOptimisation -> Bool
$c/= :: GhcOptimisation -> GhcOptimisation -> Bool
== :: GhcOptimisation -> GhcOptimisation -> Bool
$c== :: GhcOptimisation -> GhcOptimisation -> Bool
Eq)
data GhcDynLinkMode = GhcStaticOnly
| GhcDynamicOnly
| GhcStaticAndDynamic
deriving (Int -> GhcDynLinkMode -> [Char] -> [Char]
[GhcDynLinkMode] -> [Char] -> [Char]
GhcDynLinkMode -> [Char]
(Int -> GhcDynLinkMode -> [Char] -> [Char])
-> (GhcDynLinkMode -> [Char])
-> ([GhcDynLinkMode] -> [Char] -> [Char])
-> Show GhcDynLinkMode
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [GhcDynLinkMode] -> [Char] -> [Char]
$cshowList :: [GhcDynLinkMode] -> [Char] -> [Char]
show :: GhcDynLinkMode -> [Char]
$cshow :: GhcDynLinkMode -> [Char]
showsPrec :: Int -> GhcDynLinkMode -> [Char] -> [Char]
$cshowsPrec :: Int -> GhcDynLinkMode -> [Char] -> [Char]
Show, GhcDynLinkMode -> GhcDynLinkMode -> Bool
(GhcDynLinkMode -> GhcDynLinkMode -> Bool)
-> (GhcDynLinkMode -> GhcDynLinkMode -> Bool) -> Eq GhcDynLinkMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcDynLinkMode -> GhcDynLinkMode -> Bool
$c/= :: GhcDynLinkMode -> GhcDynLinkMode -> Bool
== :: GhcDynLinkMode -> GhcDynLinkMode -> Bool
$c== :: GhcDynLinkMode -> GhcDynLinkMode -> Bool
Eq)
data GhcProfAuto = GhcProfAutoAll
| GhcProfAutoToplevel
| GhcProfAutoExported
deriving (Int -> GhcProfAuto -> [Char] -> [Char]
[GhcProfAuto] -> [Char] -> [Char]
GhcProfAuto -> [Char]
(Int -> GhcProfAuto -> [Char] -> [Char])
-> (GhcProfAuto -> [Char])
-> ([GhcProfAuto] -> [Char] -> [Char])
-> Show GhcProfAuto
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [GhcProfAuto] -> [Char] -> [Char]
$cshowList :: [GhcProfAuto] -> [Char] -> [Char]
show :: GhcProfAuto -> [Char]
$cshow :: GhcProfAuto -> [Char]
showsPrec :: Int -> GhcProfAuto -> [Char] -> [Char]
$cshowsPrec :: Int -> GhcProfAuto -> [Char] -> [Char]
Show, GhcProfAuto -> GhcProfAuto -> Bool
(GhcProfAuto -> GhcProfAuto -> Bool)
-> (GhcProfAuto -> GhcProfAuto -> Bool) -> Eq GhcProfAuto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcProfAuto -> GhcProfAuto -> Bool
$c/= :: GhcProfAuto -> GhcProfAuto -> Bool
== :: GhcProfAuto -> GhcProfAuto -> Bool
$c== :: GhcProfAuto -> GhcProfAuto -> Bool
Eq)
runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> GhcOptions
-> IO ()
runGHC :: Verbosity
-> ConfiguredProgram -> Compiler -> Platform -> GhcOptions -> IO ()
runGHC Verbosity
verbosity ConfiguredProgram
ghcProg Compiler
comp Platform
platform GhcOptions
opts = do
Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation Verbosity
verbosity (ConfiguredProgram
-> Compiler -> Platform -> GhcOptions -> ProgramInvocation
ghcInvocation ConfiguredProgram
ghcProg Compiler
comp Platform
platform GhcOptions
opts)
ghcInvocation :: ConfiguredProgram -> Compiler -> Platform -> GhcOptions
-> ProgramInvocation
ghcInvocation :: ConfiguredProgram
-> Compiler -> Platform -> GhcOptions -> ProgramInvocation
ghcInvocation ConfiguredProgram
prog Compiler
comp Platform
platform GhcOptions
opts =
(ConfiguredProgram -> [[Char]] -> ProgramInvocation
programInvocation ConfiguredProgram
prog (Compiler -> Platform -> GhcOptions -> [[Char]]
renderGhcOptions Compiler
comp Platform
platform GhcOptions
opts)) {
progInvokePathEnv :: [[Char]]
progInvokePathEnv = NubListR [Char] -> [[Char]]
forall a. NubListR a -> [a]
fromNubListR (GhcOptions -> NubListR [Char]
ghcOptExtraPath GhcOptions
opts)
}
renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String]
renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [[Char]]
renderGhcOptions Compiler
comp _platform :: Platform
_platform@(Platform Arch
_arch OS
os) GhcOptions
opts
| Compiler -> CompilerFlavor
compilerFlavor Compiler
comp CompilerFlavor -> [CompilerFlavor] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [CompilerFlavor
GHC, CompilerFlavor
GHCJS] =
[Char] -> [[Char]]
forall a. HasCallStack => [Char] -> a
error ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [Char]
"Distribution.Simple.Program.GHC.renderGhcOptions: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"compiler flavor must be 'GHC' or 'GHCJS'!"
| Bool
otherwise =
[[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ case Flag GhcMode -> Maybe GhcMode
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag GhcMode
ghcOptMode GhcOptions
opts) of
Maybe GhcMode
Nothing -> []
Just GhcMode
GhcModeCompile -> [[Char]
"-c"]
Just GhcMode
GhcModeLink -> []
Just GhcMode
GhcModeMake -> [[Char]
"--make"]
Just GhcMode
GhcModeInteractive -> [[Char]
"--interactive"]
Just GhcMode
GhcModeAbiHash -> [[Char]
"--abi-hash"]
, GhcOptions -> [[Char]]
ghcOptExtraDefault GhcOptions
opts
, [ [Char]
"-no-link" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptNoLink ]
, [[Char]] -> (Verbosity -> [[Char]]) -> Maybe Verbosity -> [[Char]]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Verbosity -> [[Char]]
verbosityOpts (Flag Verbosity -> Maybe Verbosity
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag Verbosity
ghcOptVerbosity GhcOptions
opts))
, [ [Char]
"-fbuilding-cabal-package" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptCabal ]
, case Flag GhcOptimisation -> Maybe GhcOptimisation
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag GhcOptimisation
ghcOptOptimisation GhcOptions
opts) of
Maybe GhcOptimisation
Nothing -> []
Just GhcOptimisation
GhcNoOptimisation -> [[Char]
"-O0"]
Just GhcOptimisation
GhcNormalOptimisation -> [[Char]
"-O"]
Just GhcOptimisation
GhcMaximumOptimisation -> [[Char]
"-O2"]
Just (GhcSpecialOptimisation [Char]
s) -> [[Char]
"-O" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
s]
, case Flag DebugInfoLevel -> Maybe DebugInfoLevel
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag DebugInfoLevel
ghcOptDebugInfo GhcOptions
opts) of
Maybe DebugInfoLevel
Nothing -> []
Just DebugInfoLevel
NoDebugInfo -> []
Just DebugInfoLevel
MinimalDebugInfo -> [[Char]
"-g1"]
Just DebugInfoLevel
NormalDebugInfo -> [[Char]
"-g2"]
Just DebugInfoLevel
MaximalDebugInfo -> [[Char]
"-g3"]
, [ [Char]
"-prof" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptProfilingMode ]
, case Flag GhcProfAuto -> Maybe GhcProfAuto
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag GhcProfAuto
ghcOptProfilingAuto GhcOptions
opts) of
Maybe GhcProfAuto
_ | Bool -> Bool
not ((GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptProfilingMode)
-> []
Maybe GhcProfAuto
Nothing -> []
Just GhcProfAuto
GhcProfAutoAll
| GhcImplInfo -> Bool
flagProfAuto GhcImplInfo
implInfo -> [[Char]
"-fprof-auto"]
| Bool
otherwise -> [[Char]
"-auto-all"]
Just GhcProfAuto
GhcProfAutoToplevel
| GhcImplInfo -> Bool
flagProfAuto GhcImplInfo
implInfo -> [[Char]
"-fprof-auto-top"]
| Bool
otherwise -> [[Char]
"-auto-all"]
Just GhcProfAuto
GhcProfAutoExported
| GhcImplInfo -> Bool
flagProfAuto GhcImplInfo
implInfo -> [[Char]
"-fprof-auto-exported"]
| Bool
otherwise -> [[Char]
"-auto"]
, [ [Char]
"-split-sections" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptSplitSections ]
, [ [Char]
"-split-objs" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptSplitObjs ]
, case Flag [Char] -> Maybe [Char]
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag [Char]
ghcOptHPCDir GhcOptions
opts) of
Maybe [Char]
Nothing -> []
Just [Char]
hpcdir -> [[Char]
"-fhpc", [Char]
"-hpcdir", [Char]
hpcdir]
, if Compiler -> Bool
parmakeSupported Compiler
comp
then case GhcOptions -> Flag (Maybe Int)
ghcOptNumJobs GhcOptions
opts of
Flag (Maybe Int)
NoFlag -> []
Flag Maybe Int
n -> [[Char]
"-j" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> (Int -> [Char]) -> Maybe Int -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" Int -> [Char]
forall a. Show a => a -> [Char]
show Maybe Int
n]
else []
, [ [Char]
"-staticlib" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptStaticLib ]
, [ [Char]
"-shared" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptShared ]
, case Flag GhcDynLinkMode -> Maybe GhcDynLinkMode
forall a. Flag a -> Maybe a
flagToMaybe (GhcOptions -> Flag GhcDynLinkMode
ghcOptDynLinkMode GhcOptions
opts) of
Maybe GhcDynLinkMode
Nothing -> []
Just GhcDynLinkMode
GhcStaticOnly -> [[Char]
"-static"]
Just GhcDynLinkMode
GhcDynamicOnly -> [[Char]
"-dynamic"]
Just GhcDynLinkMode
GhcStaticAndDynamic -> [[Char]
"-static", [Char]
"-dynamic-too"]
, [ [Char]
"-fPIC" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptFPic ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-dylib-install-name", [Char]
libname] | [Char]
libname <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptDylibName ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-osuf", [Char]
suf] | [Char]
suf <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptObjSuffix ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-hisuf", [Char]
suf] | [Char]
suf <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptHiSuffix ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-dynosuf", [Char]
suf] | [Char]
suf <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptDynObjSuffix ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-dynhisuf",[Char]
suf] | [Char]
suf <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptDynHiSuffix ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-outputdir", [Char]
dir] | [Char]
dir <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptOutputDir ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-odir", [Char]
dir] | [Char]
dir <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptObjDir ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-hidir", [Char]
dir] | [Char]
dir <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptHiDir ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-stubdir", [Char]
dir] | [Char]
dir <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptStubDir ]
, [ [Char]
"-i" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptSourcePathClear ]
, [ [Char]
"-i" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir | [Char]
dir <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptSourcePath ]
, [ [Char]
"-I" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir | [Char]
dir <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptCppIncludePath ]
, [ [Char]
"-optP" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt | [Char]
opt <- GhcOptions -> [[Char]]
ghcOptCppOptions GhcOptions
opts]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ [Char]
"-optP-include", [Char]
"-optP" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
inc]
| [Char]
inc <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptCppIncludes ]
, [ [Char]
"-optc" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt | [Char]
opt <- GhcOptions -> [[Char]]
ghcOptCcOptions GhcOptions
opts]
,
let cxxflag :: [Char]
cxxflag = case CompilerFlavor -> Compiler -> Maybe Version
compilerCompatVersion CompilerFlavor
GHC Compiler
comp of
Just Version
v | Version
v Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
8, Int
10] -> [Char]
"-optcxx"
Maybe Version
_ -> [Char]
"-optc"
in [ [Char]
cxxflag [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt | [Char]
opt <- GhcOptions -> [[Char]]
ghcOptCxxOptions GhcOptions
opts]
, [ [Char]
"-opta" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt | [Char]
opt <- GhcOptions -> [[Char]]
ghcOptAsmOptions GhcOptions
opts]
, [ [Char]
"-optl" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt | [Char]
opt <- GhcOptions -> [[Char]]
ghcOptLinkOptions GhcOptions
opts]
, [[Char]
"-l" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
lib | [Char]
lib <- GhcOptions -> [[Char]]
ghcOptLinkLibs GhcOptions
opts]
, [[Char]
"-L" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir | [Char]
dir <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptLinkLibPath ]
, if Bool
isOSX
then [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-framework", [Char]
fmwk]
| [Char]
fmwk <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptLinkFrameworks ]
else []
, if Bool
isOSX
then [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-framework-path", [Char]
path]
| [Char]
path <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptLinkFrameworkDirs ]
else []
, [ [Char]
"-no-hs-main" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptLinkNoHsMain ]
, [ [Char]
"-dynload deploy" | Bool -> Bool
not ([[Char]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ((GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptRPaths)) ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ [Char]
"-optl-Wl,-rpath," [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir]
| [Char]
dir <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptRPaths ]
, [ [Char]
modDefFile | [Char]
modDefFile <- (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptLinkModDefFiles ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ case () of
()
_ | Compiler -> Bool
unitIdSupported Compiler
comp -> [Char]
"-this-unit-id"
| Compiler -> Bool
packageKeySupported Compiler
comp -> [Char]
"-this-package-key"
| Bool
otherwise -> [Char]
"-package-name"
, [Char]
this_arg ]
| [Char]
this_arg <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptThisUnitId ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-this-component-id", ComponentId -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow ComponentId
this_cid ]
| ComponentId
this_cid <- (GhcOptions -> Flag ComponentId) -> [ComponentId]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag ComponentId
ghcOptThisComponentId ]
, if [(ModuleName, OpenModule)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (GhcOptions -> [(ModuleName, OpenModule)]
ghcOptInstantiatedWith GhcOptions
opts)
then []
else [Char]
"-instantiated-with"
[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
"," (((ModuleName, OpenModule) -> [Char])
-> [(ModuleName, OpenModule)] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
n,OpenModule
m) -> ModuleName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow ModuleName
n [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"="
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ OpenModule -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow OpenModule
m)
(GhcOptions -> [(ModuleName, OpenModule)]
ghcOptInstantiatedWith GhcOptions
opts))
[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: []
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [[Char]
"-fno-code", [Char]
"-fwrite-interface"] | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptNoCode ]
, [ [Char]
"-hide-all-packages" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptHideAllPackages ]
, [ [Char]
"-Wmissing-home-modules" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptWarnMissingHomeModules ]
, [ [Char]
"-no-auto-link-packages" | (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
ghcOptNoAutoLinkPackages ]
, GhcImplInfo -> PackageDBStack -> [[Char]]
packageDbArgs GhcImplInfo
implInfo (GhcOptions -> PackageDBStack
ghcOptPackageDBs GhcOptions
opts)
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ let space :: [Char] -> [Char]
space [Char]
"" = [Char]
""
space [Char]
xs = Char
' ' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
xs
in [ [[Char]
"-package-id", OpenUnitId -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow OpenUnitId
ipkgid [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
space (ModuleRenaming -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow ModuleRenaming
rns)]
| (OpenUnitId
ipkgid,ModuleRenaming
rns) <- (GhcOptions -> NubListR (OpenUnitId, ModuleRenaming))
-> [(OpenUnitId, ModuleRenaming)]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR (OpenUnitId, ModuleRenaming)
ghcOptPackages ]
, if GhcImplInfo -> Bool
supportsHaskell2010 GhcImplInfo
implInfo
then [ [Char]
"-X" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Language -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Language
lang | Language
lang <- (GhcOptions -> Flag Language) -> [Language]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag Language
ghcOptLanguage ]
else []
, [ [Char]
ext'
| Extension
ext <- (GhcOptions -> NubListR Extension) -> [Extension]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR Extension
ghcOptExtensions
, [Char]
ext' <- case Extension -> Map Extension (Maybe [Char]) -> Maybe (Maybe [Char])
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Extension
ext (GhcOptions -> Map Extension (Maybe [Char])
ghcOptExtensionMap GhcOptions
opts) of
Just (Just [Char]
arg) -> [[Char]
arg]
Just Maybe [Char]
Nothing -> []
Maybe (Maybe [Char])
Nothing ->
[Char] -> [[Char]]
forall a. HasCallStack => [Char] -> a
error ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [Char]
"Distribution.Simple.Program.GHC.renderGhcOptions: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Extension -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Extension
ext [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" not present in ghcOptExtensionMap."
]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ [Char]
"-ghci-script", [Char]
script ] | [Char]
script <- GhcOptions -> [[Char]]
ghcOptGHCiScripts GhcOptions
opts
, GhcImplInfo -> Bool
flagGhciScript GhcImplInfo
implInfo ]
, (GhcOptions -> NubListR [Char]) -> [[Char]]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR [Char]
ghcOptInputFiles
, [ ModuleName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow ModuleName
modu | ModuleName
modu <- (GhcOptions -> NubListR ModuleName) -> [ModuleName]
forall {a}. (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR ModuleName
ghcOptInputModules ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ [Char]
"-o", [Char]
out] | [Char]
out <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptOutputFile ]
, [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [ [Char]
"-dyno", [Char]
out] | [Char]
out <- (GhcOptions -> Flag [Char]) -> [[Char]]
forall {a}. (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag [Char]
ghcOptOutputDynFile ]
, GhcOptions -> [[Char]]
ghcOptExtra GhcOptions
opts
]
where
implInfo :: GhcImplInfo
implInfo = Compiler -> GhcImplInfo
getImplInfo Compiler
comp
isOSX :: Bool
isOSX = OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSX
flag :: (GhcOptions -> Flag a) -> [a]
flag GhcOptions -> Flag a
flg = Flag a -> [a]
forall a. Flag a -> [a]
flagToList (GhcOptions -> Flag a
flg GhcOptions
opts)
flags :: (GhcOptions -> NubListR a) -> [a]
flags GhcOptions -> NubListR a
flg = NubListR a -> [a]
forall a. NubListR a -> [a]
fromNubListR (NubListR a -> [a])
-> (GhcOptions -> NubListR a) -> GhcOptions -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GhcOptions -> NubListR a
flg (GhcOptions -> [a]) -> GhcOptions -> [a]
forall a b. (a -> b) -> a -> b
$ GhcOptions
opts
flagBool :: (GhcOptions -> Flag Bool) -> Bool
flagBool GhcOptions -> Flag Bool
flg = Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (GhcOptions -> Flag Bool
flg GhcOptions
opts)
verbosityOpts :: Verbosity -> [String]
verbosityOpts :: Verbosity -> [[Char]]
verbosityOpts Verbosity
verbosity
| Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
deafening = [[Char]
"-v"]
| Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
normal = []
| Bool
otherwise = [[Char]
"-w", [Char]
"-v0"]
packageDbArgsConf :: PackageDBStack -> [String]
packageDbArgsConf :: PackageDBStack -> [[Char]]
packageDbArgsConf PackageDBStack
dbstack = case PackageDBStack
dbstack of
(PackageDB
GlobalPackageDB:PackageDB
UserPackageDB:PackageDBStack
dbs) -> (PackageDB -> [[Char]]) -> PackageDBStack -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PackageDB -> [[Char]]
specific PackageDBStack
dbs
(PackageDB
GlobalPackageDB:PackageDBStack
dbs) -> ([Char]
"-no-user-package-conf")
[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: (PackageDB -> [[Char]]) -> PackageDBStack -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PackageDB -> [[Char]]
specific PackageDBStack
dbs
PackageDBStack
_ -> [[Char]]
forall {a}. a
ierror
where
specific :: PackageDB -> [[Char]]
specific (SpecificPackageDB [Char]
db) = [ [Char]
"-package-conf", [Char]
db ]
specific PackageDB
_ = [[Char]]
forall {a}. a
ierror
ierror :: a
ierror = [Char] -> a
forall a. HasCallStack => [Char] -> a
error ([Char] -> a) -> [Char] -> a
forall a b. (a -> b) -> a -> b
$ [Char]
"internal error: unexpected package db stack: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ PackageDBStack -> [Char]
forall a. Show a => a -> [Char]
show PackageDBStack
dbstack
packageDbArgsDb :: PackageDBStack -> [String]
packageDbArgsDb :: PackageDBStack -> [[Char]]
packageDbArgsDb PackageDBStack
dbstack = case PackageDBStack
dbstack of
(PackageDB
GlobalPackageDB:PackageDB
UserPackageDB:PackageDBStack
dbs)
| (PackageDB -> Bool) -> PackageDBStack -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all PackageDB -> Bool
isSpecific PackageDBStack
dbs -> (PackageDB -> [[Char]]) -> PackageDBStack -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PackageDB -> [[Char]]
single PackageDBStack
dbs
(PackageDB
GlobalPackageDB:PackageDBStack
dbs)
| (PackageDB -> Bool) -> PackageDBStack -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all PackageDB -> Bool
isSpecific PackageDBStack
dbs -> [Char]
"-no-user-package-db"
[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: (PackageDB -> [[Char]]) -> PackageDBStack -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PackageDB -> [[Char]]
single PackageDBStack
dbs
PackageDBStack
dbs -> [Char]
"-clear-package-db"
[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: (PackageDB -> [[Char]]) -> PackageDBStack -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PackageDB -> [[Char]]
single PackageDBStack
dbs
where
single :: PackageDB -> [[Char]]
single (SpecificPackageDB [Char]
db) = [ [Char]
"-package-db", [Char]
db ]
single PackageDB
GlobalPackageDB = [ [Char]
"-global-package-db" ]
single PackageDB
UserPackageDB = [ [Char]
"-user-package-db" ]
isSpecific :: PackageDB -> Bool
isSpecific (SpecificPackageDB [Char]
_) = Bool
True
isSpecific PackageDB
_ = Bool
False
packageDbArgs :: GhcImplInfo -> PackageDBStack -> [String]
packageDbArgs :: GhcImplInfo -> PackageDBStack -> [[Char]]
packageDbArgs GhcImplInfo
implInfo
| GhcImplInfo -> Bool
flagPackageConf GhcImplInfo
implInfo = PackageDBStack -> [[Char]]
packageDbArgsConf
| Bool
otherwise = PackageDBStack -> [[Char]]
packageDbArgsDb
instance Monoid GhcOptions where
mempty :: GhcOptions
mempty = GhcOptions
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
mappend :: GhcOptions -> GhcOptions -> GhcOptions
mappend = GhcOptions -> GhcOptions -> GhcOptions
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup GhcOptions where
<> :: GhcOptions -> GhcOptions -> GhcOptions
(<>) = GhcOptions -> GhcOptions -> GhcOptions
forall a. (Generic a, GSemigroup (Rep a)) => a -> a -> a
gmappend