{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}

-- | Configuration options for building.


module Stack.Types.Config.Build
    (
      BuildOpts (..)
    , BuildCommand (..)
    , defaultBuildOpts
    , defaultBuildOptsCLI
    , BuildOptsCLI (..)
    , BuildOptsMonoid (..)
    , TestOpts (..)
    , defaultTestOpts
    , TestOptsMonoid (..)
    , HaddockOpts (..)
    , defaultHaddockOpts
    , HaddockOptsMonoid (..)
    , BenchmarkOpts (..)
    , defaultBenchmarkOpts
    , BenchmarkOptsMonoid (..)
    , FileWatchOpts (..)
    , BuildSubset (..)
    , ApplyCLIFlag (..)
    , boptsCLIFlagsByName
    , CabalVerbosity (..)
    , toFirstCabalVerbosity
    )
    where

import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import           Distribution.Parsec ( Parsec (..), simpleParsec )
import           Distribution.Verbosity ( Verbosity, normal, verbose )
import           Generics.Deriving.Monoid ( memptydefault, mappenddefault )
import           Pantry.Internal.AesonExtended
import           Stack.Prelude

-- | Build options that is interpreted by the build command.

--   This is built up from BuildOptsCLI and BuildOptsMonoid

data BuildOpts =
  BuildOpts {BuildOpts -> Bool
boptsLibProfile :: !Bool
            ,BuildOpts -> Bool
boptsExeProfile :: !Bool
            ,BuildOpts -> Bool
boptsLibStrip :: !Bool
            ,BuildOpts -> Bool
boptsExeStrip :: !Bool
            ,BuildOpts -> Bool
boptsHaddock :: !Bool
            -- ^ Build haddocks?

            ,BuildOpts -> HaddockOpts
boptsHaddockOpts :: !HaddockOpts
            -- ^ Options to pass to haddock

            ,BuildOpts -> Bool
boptsOpenHaddocks :: !Bool
            -- ^ Open haddocks in the browser?

            ,BuildOpts -> Maybe Bool
boptsHaddockDeps :: !(Maybe Bool)
            -- ^ Build haddocks for dependencies?

            ,BuildOpts -> Bool
boptsHaddockInternal :: !Bool
            -- ^ Build haddocks for all symbols and packages, like @cabal haddock --internal@

            ,BuildOpts -> Bool
boptsHaddockHyperlinkSource  :: !Bool
            -- ^ Build hyperlinked source if possible. Fallback to

            -- @hscolour@. Disable for no sources.

            ,BuildOpts -> Bool
boptsInstallExes :: !Bool
            -- ^ Install executables to user path after building?

            ,BuildOpts -> Bool
boptsInstallCompilerTool :: !Bool
            -- ^ Install executables to compiler tools path after building?

            ,BuildOpts -> Bool
boptsPreFetch :: !Bool
            -- ^ Fetch all packages immediately

            -- ^ Watch files for changes and automatically rebuild

            ,BuildOpts -> Maybe Bool
boptsKeepGoing :: !(Maybe Bool)
            -- ^ Keep building/running after failure

            ,BuildOpts -> Bool
boptsKeepTmpFiles :: !Bool
            -- ^ Keep intermediate files and build directories

            ,BuildOpts -> Bool
boptsForceDirty :: !Bool
            -- ^ Force treating all local packages as having dirty files


            ,BuildOpts -> Bool
boptsTests :: !Bool
            -- ^ Turn on tests for local targets

            ,BuildOpts -> TestOpts
boptsTestOpts :: !TestOpts
            -- ^ Additional test arguments


            ,BuildOpts -> Bool
boptsBenchmarks :: !Bool
            -- ^ Turn on benchmarks for local targets

            ,BuildOpts -> BenchmarkOpts
boptsBenchmarkOpts :: !BenchmarkOpts
            -- ^ Additional test arguments

            -- ^ Commands (with arguments) to run after a successful build

            -- ^ Only perform the configure step when building

            ,BuildOpts -> Bool
boptsReconfigure :: !Bool
            -- ^ Perform the configure step even if already configured

            ,BuildOpts -> CabalVerbosity
boptsCabalVerbose :: !CabalVerbosity
            -- ^ Ask Cabal to be verbose in its builds

            ,BuildOpts -> Bool
boptsSplitObjs :: !Bool
            -- ^ Whether to enable split-objs.

            ,BuildOpts -> [Text]
boptsSkipComponents :: ![Text]
            -- ^ Which components to skip when building

            ,BuildOpts -> Bool
boptsInterleavedOutput :: !Bool
            -- ^ Should we use the interleaved GHC output when building

            -- multiple packages?

            ,BuildOpts -> Maybe Text
boptsDdumpDir :: !(Maybe Text)
            }
  deriving (Int -> BuildOpts -> ShowS
[BuildOpts] -> ShowS
BuildOpts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildOpts] -> ShowS
$cshowList :: [BuildOpts] -> ShowS
show :: BuildOpts -> String
$cshow :: BuildOpts -> String
showsPrec :: Int -> BuildOpts -> ShowS
$cshowsPrec :: Int -> BuildOpts -> ShowS
Show)

defaultBuildOpts :: BuildOpts
defaultBuildOpts :: BuildOpts
defaultBuildOpts = BuildOpts
    { boptsLibProfile :: Bool
boptsLibProfile = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidLibProfile
    , boptsExeProfile :: Bool
boptsExeProfile = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidExeProfile
    , boptsLibStrip :: Bool
boptsLibStrip = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue BuildOptsMonoid -> FirstTrue
buildMonoidLibStrip
    , boptsExeStrip :: Bool
boptsExeStrip = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue BuildOptsMonoid -> FirstTrue
buildMonoidExeStrip
    , boptsHaddock :: Bool
boptsHaddock = Bool
False
    , boptsHaddockOpts :: HaddockOpts
boptsHaddockOpts = HaddockOpts
defaultHaddockOpts
    , boptsOpenHaddocks :: Bool
boptsOpenHaddocks = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidOpenHaddocks
    , boptsHaddockDeps :: Maybe Bool
boptsHaddockDeps = forall a. Maybe a
Nothing
    , boptsHaddockInternal :: Bool
boptsHaddockInternal = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidHaddockInternal
    , boptsHaddockHyperlinkSource :: Bool
boptsHaddockHyperlinkSource = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue BuildOptsMonoid -> FirstTrue
buildMonoidHaddockHyperlinkSource
    , boptsInstallExes :: Bool
boptsInstallExes = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidInstallExes
    , boptsInstallCompilerTool :: Bool
boptsInstallCompilerTool = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidInstallCompilerTool
    , boptsPreFetch :: Bool
boptsPreFetch = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidPreFetch
    , boptsKeepGoing :: Maybe Bool
boptsKeepGoing = forall a. Maybe a
Nothing
    , boptsKeepTmpFiles :: Bool
boptsKeepTmpFiles = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidKeepTmpFiles
    , boptsForceDirty :: Bool
boptsForceDirty = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidForceDirty
    , boptsTests :: Bool
boptsTests = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidTests
    , boptsTestOpts :: TestOpts
boptsTestOpts = TestOpts
defaultTestOpts
    , boptsBenchmarks :: Bool
boptsBenchmarks = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidBenchmarks
    , boptsBenchmarkOpts :: BenchmarkOpts
boptsBenchmarkOpts = BenchmarkOpts
defaultBenchmarkOpts
    , boptsReconfigure :: Bool
boptsReconfigure = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidReconfigure
    , boptsCabalVerbose :: CabalVerbosity
boptsCabalVerbose = Verbosity -> CabalVerbosity
CabalVerbosity Verbosity
normal
    , boptsSplitObjs :: Bool
boptsSplitObjs = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse BuildOptsMonoid -> FirstFalse
buildMonoidSplitObjs
    , boptsSkipComponents :: [Text]
boptsSkipComponents = []
    , boptsInterleavedOutput :: Bool
boptsInterleavedOutput = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue BuildOptsMonoid -> FirstTrue
buildMonoidInterleavedOutput
    , boptsDdumpDir :: Maybe Text
boptsDdumpDir = forall a. Maybe a
Nothing
    }

defaultBuildOptsCLI ::BuildOptsCLI
defaultBuildOptsCLI :: BuildOptsCLI
defaultBuildOptsCLI = BuildOptsCLI
    { boptsCLITargets :: [Text]
boptsCLITargets = []
    , boptsCLIDryrun :: Bool
boptsCLIDryrun = Bool
False
    , boptsCLIFlags :: Map ApplyCLIFlag (Map FlagName Bool)
boptsCLIFlags = forall k a. Map k a
Map.empty
    , boptsCLIGhcOptions :: [Text]
boptsCLIGhcOptions = []
    , boptsCLIBuildSubset :: BuildSubset
boptsCLIBuildSubset = BuildSubset
BSAll
    , boptsCLIFileWatch :: FileWatchOpts
boptsCLIFileWatch = FileWatchOpts
NoFileWatch
    , boptsCLIWatchAll :: Bool
boptsCLIWatchAll = Bool
False
    , boptsCLIExec :: [(String, [String])]
boptsCLIExec = []
    , boptsCLIOnlyConfigure :: Bool
boptsCLIOnlyConfigure = Bool
False
    , boptsCLICommand :: BuildCommand
boptsCLICommand = BuildCommand
Build
    , boptsCLIInitialBuildSteps :: Bool
boptsCLIInitialBuildSteps = Bool
False
    }

-- | How to apply a CLI flag

data ApplyCLIFlag
  = ACFAllProjectPackages
  -- ^ Apply to all project packages which have such a flag name available.

  | ACFByName !PackageName
  -- ^ Apply to the specified package only.

  deriving (Int -> ApplyCLIFlag -> ShowS
[ApplyCLIFlag] -> ShowS
ApplyCLIFlag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplyCLIFlag] -> ShowS
$cshowList :: [ApplyCLIFlag] -> ShowS
show :: ApplyCLIFlag -> String
$cshow :: ApplyCLIFlag -> String
showsPrec :: Int -> ApplyCLIFlag -> ShowS
$cshowsPrec :: Int -> ApplyCLIFlag -> ShowS
Show, ApplyCLIFlag -> ApplyCLIFlag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c/= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
== :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c== :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
Eq, Eq ApplyCLIFlag
ApplyCLIFlag -> ApplyCLIFlag -> Bool
ApplyCLIFlag -> ApplyCLIFlag -> Ordering
ApplyCLIFlag -> ApplyCLIFlag -> ApplyCLIFlag
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplyCLIFlag -> ApplyCLIFlag -> ApplyCLIFlag
$cmin :: ApplyCLIFlag -> ApplyCLIFlag -> ApplyCLIFlag
max :: ApplyCLIFlag -> ApplyCLIFlag -> ApplyCLIFlag
$cmax :: ApplyCLIFlag -> ApplyCLIFlag -> ApplyCLIFlag
>= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c>= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
> :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c> :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
<= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c<= :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
< :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
$c< :: ApplyCLIFlag -> ApplyCLIFlag -> Bool
compare :: ApplyCLIFlag -> ApplyCLIFlag -> Ordering
$ccompare :: ApplyCLIFlag -> ApplyCLIFlag -> Ordering
Ord)

-- | Only flags set via 'ACFByName'

boptsCLIFlagsByName :: BuildOptsCLI -> Map PackageName (Map FlagName Bool)
boptsCLIFlagsByName :: BuildOptsCLI -> Map PackageName (Map FlagName Bool)
boptsCLIFlagsByName =
  forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe forall {b}. (ApplyCLIFlag, b) -> Maybe (PackageName, b)
go forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall k a. Map k a -> [(k, a)]
Map.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  BuildOptsCLI -> Map ApplyCLIFlag (Map FlagName Bool)
boptsCLIFlags
  where
    go :: (ApplyCLIFlag, b) -> Maybe (PackageName, b)
go (ApplyCLIFlag
ACFAllProjectPackages, b
_) = forall a. Maybe a
Nothing
    go (ACFByName PackageName
name, b
flags) = forall a. a -> Maybe a
Just (PackageName
name, b
flags)

-- | Build options that may only be specified from the CLI

data BuildOptsCLI = BuildOptsCLI
    { BuildOptsCLI -> [Text]
boptsCLITargets :: ![Text]
    , BuildOptsCLI -> Bool
boptsCLIDryrun :: !Bool
    , BuildOptsCLI -> [Text]
boptsCLIGhcOptions :: ![Text]
    , BuildOptsCLI -> Map ApplyCLIFlag (Map FlagName Bool)
boptsCLIFlags :: !(Map ApplyCLIFlag (Map FlagName Bool))
    , BuildOptsCLI -> BuildSubset
boptsCLIBuildSubset :: !BuildSubset
    , BuildOptsCLI -> FileWatchOpts
boptsCLIFileWatch :: !FileWatchOpts
    , BuildOptsCLI -> Bool
boptsCLIWatchAll :: !Bool
    , BuildOptsCLI -> [(String, [String])]
boptsCLIExec :: ![(String, [String])]
    , BuildOptsCLI -> Bool
boptsCLIOnlyConfigure :: !Bool
    , BuildOptsCLI -> BuildCommand
boptsCLICommand :: !BuildCommand
    , BuildOptsCLI -> Bool
boptsCLIInitialBuildSteps :: !Bool
    } deriving Int -> BuildOptsCLI -> ShowS
[BuildOptsCLI] -> ShowS
BuildOptsCLI -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildOptsCLI] -> ShowS
$cshowList :: [BuildOptsCLI] -> ShowS
show :: BuildOptsCLI -> String
$cshow :: BuildOptsCLI -> String
showsPrec :: Int -> BuildOptsCLI -> ShowS
$cshowsPrec :: Int -> BuildOptsCLI -> ShowS
Show

-- | Command sum type for conditional arguments.

data BuildCommand
    = Build
    | Test
    | Haddock
    | Bench
    | Install
    deriving (BuildCommand -> BuildCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildCommand -> BuildCommand -> Bool
$c/= :: BuildCommand -> BuildCommand -> Bool
== :: BuildCommand -> BuildCommand -> Bool
$c== :: BuildCommand -> BuildCommand -> Bool
Eq, Int -> BuildCommand -> ShowS
[BuildCommand] -> ShowS
BuildCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildCommand] -> ShowS
$cshowList :: [BuildCommand] -> ShowS
show :: BuildCommand -> String
$cshow :: BuildCommand -> String
showsPrec :: Int -> BuildCommand -> ShowS
$cshowsPrec :: Int -> BuildCommand -> ShowS
Show)

-- | Build options that may be specified in the stack.yaml or from the CLI

data BuildOptsMonoid = BuildOptsMonoid
    { BuildOptsMonoid -> Any
buildMonoidTrace :: !Any
    , BuildOptsMonoid -> Any
buildMonoidProfile :: !Any
    , BuildOptsMonoid -> Any
buildMonoidNoStrip :: !Any
    , BuildOptsMonoid -> FirstFalse
buildMonoidLibProfile :: !FirstFalse
    , BuildOptsMonoid -> FirstFalse
buildMonoidExeProfile :: !FirstFalse
    , BuildOptsMonoid -> FirstTrue
buildMonoidLibStrip :: !FirstTrue
    , BuildOptsMonoid -> FirstTrue
buildMonoidExeStrip :: !FirstTrue
    , BuildOptsMonoid -> FirstFalse
buildMonoidHaddock :: !FirstFalse
    , BuildOptsMonoid -> HaddockOptsMonoid
buildMonoidHaddockOpts :: !HaddockOptsMonoid
    , BuildOptsMonoid -> FirstFalse
buildMonoidOpenHaddocks :: !FirstFalse
    , BuildOptsMonoid -> First Bool
buildMonoidHaddockDeps :: !(First Bool)
    , BuildOptsMonoid -> FirstFalse
buildMonoidHaddockInternal :: !FirstFalse
    , BuildOptsMonoid -> FirstTrue
buildMonoidHaddockHyperlinkSource :: !FirstTrue
    , BuildOptsMonoid -> FirstFalse
buildMonoidInstallExes :: !FirstFalse
    , BuildOptsMonoid -> FirstFalse
buildMonoidInstallCompilerTool :: !FirstFalse
    , BuildOptsMonoid -> FirstFalse
buildMonoidPreFetch :: !FirstFalse
    , BuildOptsMonoid -> First Bool
buildMonoidKeepGoing :: !(First Bool)
    , BuildOptsMonoid -> FirstFalse
buildMonoidKeepTmpFiles :: !FirstFalse
    , BuildOptsMonoid -> FirstFalse
buildMonoidForceDirty :: !FirstFalse
    , BuildOptsMonoid -> FirstFalse
buildMonoidTests :: !FirstFalse
    , BuildOptsMonoid -> TestOptsMonoid
buildMonoidTestOpts :: !TestOptsMonoid
    , BuildOptsMonoid -> FirstFalse
buildMonoidBenchmarks :: !FirstFalse
    , BuildOptsMonoid -> BenchmarkOptsMonoid
buildMonoidBenchmarkOpts :: !BenchmarkOptsMonoid
    , BuildOptsMonoid -> FirstFalse
buildMonoidReconfigure :: !FirstFalse
    , BuildOptsMonoid -> First CabalVerbosity
buildMonoidCabalVerbose :: !(First CabalVerbosity)
    , BuildOptsMonoid -> FirstFalse
buildMonoidSplitObjs :: !FirstFalse
    , BuildOptsMonoid -> [Text]
buildMonoidSkipComponents :: ![Text]
    , BuildOptsMonoid -> FirstTrue
buildMonoidInterleavedOutput :: !FirstTrue
    , BuildOptsMonoid -> First Text
buildMonoidDdumpDir :: !(First Text)
    } deriving (Int -> BuildOptsMonoid -> ShowS
[BuildOptsMonoid] -> ShowS
BuildOptsMonoid -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildOptsMonoid] -> ShowS
$cshowList :: [BuildOptsMonoid] -> ShowS
show :: BuildOptsMonoid -> String
$cshow :: BuildOptsMonoid -> String
showsPrec :: Int -> BuildOptsMonoid -> ShowS
$cshowsPrec :: Int -> BuildOptsMonoid -> ShowS
Show, forall x. Rep BuildOptsMonoid x -> BuildOptsMonoid
forall x. BuildOptsMonoid -> Rep BuildOptsMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildOptsMonoid x -> BuildOptsMonoid
$cfrom :: forall x. BuildOptsMonoid -> Rep BuildOptsMonoid x
Generic)

instance FromJSON (WithJSONWarnings BuildOptsMonoid) where
  parseJSON :: Value -> Parser (WithJSONWarnings BuildOptsMonoid)
parseJSON = forall a.
String
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings String
"BuildOptsMonoid"
    (\Object
o -> do let buildMonoidTrace :: Any
buildMonoidTrace = Bool -> Any
Any Bool
False
                  buildMonoidProfile :: Any
buildMonoidProfile = Bool -> Any
Any Bool
False
                  buildMonoidNoStrip :: Any
buildMonoidNoStrip = Bool -> Any
Any Bool
False
              FirstFalse
buildMonoidLibProfile <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidLibProfileArgName
              FirstFalse
buildMonoidExeProfile <-Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidExeProfileArgName
              FirstTrue
buildMonoidLibStrip <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidLibStripArgName
              FirstTrue
buildMonoidExeStrip <-Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidExeStripArgName
              FirstFalse
buildMonoidHaddock <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidHaddockArgName
              HaddockOptsMonoid
buildMonoidHaddockOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidHaddockOptsArgName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
              FirstFalse
buildMonoidOpenHaddocks <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidOpenHaddocksArgName
              First Bool
buildMonoidHaddockDeps <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidHaddockDepsArgName
              FirstFalse
buildMonoidHaddockInternal <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidHaddockInternalArgName
              FirstTrue
buildMonoidHaddockHyperlinkSource <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidHaddockHyperlinkSourceArgName
              FirstFalse
buildMonoidInstallExes <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidInstallExesArgName
              FirstFalse
buildMonoidInstallCompilerTool <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidInstallCompilerToolArgName
              FirstFalse
buildMonoidPreFetch <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidPreFetchArgName
              First Bool
buildMonoidKeepGoing <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidKeepGoingArgName
              FirstFalse
buildMonoidKeepTmpFiles <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidKeepTmpFilesArgName
              FirstFalse
buildMonoidForceDirty <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidForceDirtyArgName
              FirstFalse
buildMonoidTests <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidTestsArgName
              TestOptsMonoid
buildMonoidTestOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidTestOptsArgName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
              FirstFalse
buildMonoidBenchmarks <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidBenchmarksArgName
              BenchmarkOptsMonoid
buildMonoidBenchmarkOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidBenchmarkOptsArgName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
              FirstFalse
buildMonoidReconfigure <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidReconfigureArgName
              First CabalVerbosity
cabalVerbosity <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidCabalVerbosityArgName
              FirstFalse
cabalVerbose <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidCabalVerboseArgName
              let buildMonoidCabalVerbose :: First CabalVerbosity
buildMonoidCabalVerbose = First CabalVerbosity
cabalVerbosity forall a. Semigroup a => a -> a -> a
<> FirstFalse -> First CabalVerbosity
toFirstCabalVerbosity FirstFalse
cabalVerbose
              FirstFalse
buildMonoidSplitObjs <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidSplitObjsName
              [Text]
buildMonoidSkipComponents <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidSkipComponentsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
              FirstTrue
buildMonoidInterleavedOutput <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidInterleavedOutputName
              First Text
buildMonoidDdumpDir <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
buildMonoidDdumpDirName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
              forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildOptsMonoid{[Text]
Any
First Bool
First Text
First CabalVerbosity
FirstFalse
FirstTrue
BenchmarkOptsMonoid
HaddockOptsMonoid
TestOptsMonoid
buildMonoidDdumpDir :: First Text
buildMonoidInterleavedOutput :: FirstTrue
buildMonoidSkipComponents :: [Text]
buildMonoidSplitObjs :: FirstFalse
buildMonoidCabalVerbose :: First CabalVerbosity
buildMonoidReconfigure :: FirstFalse
buildMonoidBenchmarkOpts :: BenchmarkOptsMonoid
buildMonoidBenchmarks :: FirstFalse
buildMonoidTestOpts :: TestOptsMonoid
buildMonoidTests :: FirstFalse
buildMonoidForceDirty :: FirstFalse
buildMonoidKeepTmpFiles :: FirstFalse
buildMonoidKeepGoing :: First Bool
buildMonoidPreFetch :: FirstFalse
buildMonoidInstallCompilerTool :: FirstFalse
buildMonoidInstallExes :: FirstFalse
buildMonoidHaddockHyperlinkSource :: FirstTrue
buildMonoidHaddockInternal :: FirstFalse
buildMonoidHaddockDeps :: First Bool
buildMonoidOpenHaddocks :: FirstFalse
buildMonoidHaddockOpts :: HaddockOptsMonoid
buildMonoidHaddock :: FirstFalse
buildMonoidExeStrip :: FirstTrue
buildMonoidLibStrip :: FirstTrue
buildMonoidExeProfile :: FirstFalse
buildMonoidLibProfile :: FirstFalse
buildMonoidNoStrip :: Any
buildMonoidProfile :: Any
buildMonoidTrace :: Any
buildMonoidDdumpDir :: First Text
buildMonoidSkipComponents :: [Text]
buildMonoidCabalVerbose :: First CabalVerbosity
buildMonoidBenchmarkOpts :: BenchmarkOptsMonoid
buildMonoidTestOpts :: TestOptsMonoid
buildMonoidKeepGoing :: First Bool
buildMonoidHaddockDeps :: First Bool
buildMonoidHaddockOpts :: HaddockOptsMonoid
buildMonoidHaddock :: FirstFalse
buildMonoidNoStrip :: Any
buildMonoidProfile :: Any
buildMonoidTrace :: Any
buildMonoidInterleavedOutput :: FirstTrue
buildMonoidSplitObjs :: FirstFalse
buildMonoidReconfigure :: FirstFalse
buildMonoidBenchmarks :: FirstFalse
buildMonoidTests :: FirstFalse
buildMonoidForceDirty :: FirstFalse
buildMonoidKeepTmpFiles :: FirstFalse
buildMonoidPreFetch :: FirstFalse
buildMonoidInstallCompilerTool :: FirstFalse
buildMonoidInstallExes :: FirstFalse
buildMonoidHaddockHyperlinkSource :: FirstTrue
buildMonoidHaddockInternal :: FirstFalse
buildMonoidOpenHaddocks :: FirstFalse
buildMonoidExeStrip :: FirstTrue
buildMonoidLibStrip :: FirstTrue
buildMonoidExeProfile :: FirstFalse
buildMonoidLibProfile :: FirstFalse
..})

buildMonoidLibProfileArgName :: Text
buildMonoidLibProfileArgName :: Text
buildMonoidLibProfileArgName = Text
"library-profiling"

buildMonoidExeProfileArgName :: Text
buildMonoidExeProfileArgName :: Text
buildMonoidExeProfileArgName = Text
"executable-profiling"

buildMonoidLibStripArgName :: Text
buildMonoidLibStripArgName :: Text
buildMonoidLibStripArgName = Text
"library-stripping"

buildMonoidExeStripArgName :: Text
buildMonoidExeStripArgName :: Text
buildMonoidExeStripArgName = Text
"executable-stripping"

buildMonoidHaddockArgName :: Text
buildMonoidHaddockArgName :: Text
buildMonoidHaddockArgName = Text
"haddock"

buildMonoidHaddockOptsArgName :: Text
buildMonoidHaddockOptsArgName :: Text
buildMonoidHaddockOptsArgName = Text
"haddock-arguments"

buildMonoidOpenHaddocksArgName :: Text
buildMonoidOpenHaddocksArgName :: Text
buildMonoidOpenHaddocksArgName = Text
"open-haddocks"

buildMonoidHaddockDepsArgName :: Text
buildMonoidHaddockDepsArgName :: Text
buildMonoidHaddockDepsArgName = Text
"haddock-deps"

buildMonoidHaddockInternalArgName :: Text
buildMonoidHaddockInternalArgName :: Text
buildMonoidHaddockInternalArgName = Text
"haddock-internal"

buildMonoidHaddockHyperlinkSourceArgName :: Text
buildMonoidHaddockHyperlinkSourceArgName :: Text
buildMonoidHaddockHyperlinkSourceArgName = Text
"haddock-hyperlink-source"

buildMonoidInstallExesArgName :: Text
buildMonoidInstallExesArgName :: Text
buildMonoidInstallExesArgName = Text
"copy-bins"

buildMonoidInstallCompilerToolArgName :: Text
buildMonoidInstallCompilerToolArgName :: Text
buildMonoidInstallCompilerToolArgName = Text
"copy-compiler-tool"

buildMonoidPreFetchArgName :: Text
buildMonoidPreFetchArgName :: Text
buildMonoidPreFetchArgName = Text
"prefetch"

buildMonoidKeepGoingArgName :: Text
buildMonoidKeepGoingArgName :: Text
buildMonoidKeepGoingArgName = Text
"keep-going"

buildMonoidKeepTmpFilesArgName :: Text
buildMonoidKeepTmpFilesArgName :: Text
buildMonoidKeepTmpFilesArgName = Text
"keep-tmp-files"

buildMonoidForceDirtyArgName :: Text
buildMonoidForceDirtyArgName :: Text
buildMonoidForceDirtyArgName = Text
"force-dirty"

buildMonoidTestsArgName :: Text
buildMonoidTestsArgName :: Text
buildMonoidTestsArgName = Text
"test"

buildMonoidTestOptsArgName :: Text
buildMonoidTestOptsArgName :: Text
buildMonoidTestOptsArgName = Text
"test-arguments"

buildMonoidBenchmarksArgName :: Text
buildMonoidBenchmarksArgName :: Text
buildMonoidBenchmarksArgName = Text
"bench"

buildMonoidBenchmarkOptsArgName :: Text
buildMonoidBenchmarkOptsArgName :: Text
buildMonoidBenchmarkOptsArgName = Text
"benchmark-opts"

buildMonoidReconfigureArgName :: Text
buildMonoidReconfigureArgName :: Text
buildMonoidReconfigureArgName = Text
"reconfigure"

buildMonoidCabalVerbosityArgName :: Text
buildMonoidCabalVerbosityArgName :: Text
buildMonoidCabalVerbosityArgName = Text
"cabal-verbosity"

buildMonoidCabalVerboseArgName :: Text
buildMonoidCabalVerboseArgName :: Text
buildMonoidCabalVerboseArgName = Text
"cabal-verbose"

buildMonoidSplitObjsName :: Text
buildMonoidSplitObjsName :: Text
buildMonoidSplitObjsName = Text
"split-objs"

buildMonoidSkipComponentsName :: Text
buildMonoidSkipComponentsName :: Text
buildMonoidSkipComponentsName = Text
"skip-components"

buildMonoidInterleavedOutputName :: Text
buildMonoidInterleavedOutputName :: Text
buildMonoidInterleavedOutputName = Text
"interleaved-output"

buildMonoidDdumpDirName :: Text
buildMonoidDdumpDirName :: Text
buildMonoidDdumpDirName = Text
"ddump-dir"

instance Semigroup BuildOptsMonoid where
    <> :: BuildOptsMonoid -> BuildOptsMonoid -> BuildOptsMonoid
(<>) = forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault

instance Monoid BuildOptsMonoid where
    mempty :: BuildOptsMonoid
mempty = forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
    mappend :: BuildOptsMonoid -> BuildOptsMonoid -> BuildOptsMonoid
mappend = forall a. Semigroup a => a -> a -> a
(<>)

-- | Which subset of packages to build

data BuildSubset
    = BSAll
    | BSOnlySnapshot
    -- ^ Only install packages in the snapshot database, skipping

    -- packages intended for the local database.

    | BSOnlyDependencies
    | BSOnlyLocals
    -- ^ Refuse to build anything in the snapshot database, see

    -- https://github.com/commercialhaskell/stack/issues/5272

    deriving (Int -> BuildSubset -> ShowS
[BuildSubset] -> ShowS
BuildSubset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildSubset] -> ShowS
$cshowList :: [BuildSubset] -> ShowS
show :: BuildSubset -> String
$cshow :: BuildSubset -> String
showsPrec :: Int -> BuildSubset -> ShowS
$cshowsPrec :: Int -> BuildSubset -> ShowS
Show, BuildSubset -> BuildSubset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildSubset -> BuildSubset -> Bool
$c/= :: BuildSubset -> BuildSubset -> Bool
== :: BuildSubset -> BuildSubset -> Bool
$c== :: BuildSubset -> BuildSubset -> Bool
Eq)

-- | Options for the 'FinalAction' 'DoTests'

data TestOpts =
  TestOpts {TestOpts -> Bool
toRerunTests :: !Bool -- ^ Whether successful tests will be run gain

           ,TestOpts -> [String]
toAdditionalArgs :: ![String] -- ^ Arguments passed to the test program

           ,TestOpts -> Bool
toCoverage :: !Bool -- ^ Generate a code coverage report

           ,TestOpts -> Bool
toDisableRun :: !Bool -- ^ Disable running of tests

           ,TestOpts -> Maybe Int
toMaximumTimeSeconds :: !(Maybe Int) -- ^ test suite timeout in seconds

           ,TestOpts -> Bool
toAllowStdin :: !Bool -- ^ Whether to allow standard input

           } deriving (TestOpts -> TestOpts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestOpts -> TestOpts -> Bool
$c/= :: TestOpts -> TestOpts -> Bool
== :: TestOpts -> TestOpts -> Bool
$c== :: TestOpts -> TestOpts -> Bool
Eq,Int -> TestOpts -> ShowS
[TestOpts] -> ShowS
TestOpts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestOpts] -> ShowS
$cshowList :: [TestOpts] -> ShowS
show :: TestOpts -> String
$cshow :: TestOpts -> String
showsPrec :: Int -> TestOpts -> ShowS
$cshowsPrec :: Int -> TestOpts -> ShowS
Show)

defaultTestOpts :: TestOpts
defaultTestOpts :: TestOpts
defaultTestOpts = TestOpts
    { toRerunTests :: Bool
toRerunTests = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue TestOptsMonoid -> FirstTrue
toMonoidRerunTests
    , toAdditionalArgs :: [String]
toAdditionalArgs = []
    , toCoverage :: Bool
toCoverage = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse TestOptsMonoid -> FirstFalse
toMonoidCoverage
    , toDisableRun :: Bool
toDisableRun = forall a. (a -> FirstFalse) -> Bool
defaultFirstFalse TestOptsMonoid -> FirstFalse
toMonoidDisableRun
    , toMaximumTimeSeconds :: Maybe Int
toMaximumTimeSeconds = forall a. Maybe a
Nothing
    , toAllowStdin :: Bool
toAllowStdin = forall a. (a -> FirstTrue) -> Bool
defaultFirstTrue TestOptsMonoid -> FirstTrue
toMonoidAllowStdin
    }

data TestOptsMonoid =
  TestOptsMonoid
    { TestOptsMonoid -> FirstTrue
toMonoidRerunTests :: !FirstTrue
    , TestOptsMonoid -> [String]
toMonoidAdditionalArgs :: ![String]
    , TestOptsMonoid -> FirstFalse
toMonoidCoverage :: !FirstFalse
    , TestOptsMonoid -> FirstFalse
toMonoidDisableRun :: !FirstFalse
    , TestOptsMonoid -> First (Maybe Int)
toMonoidMaximumTimeSeconds :: !(First (Maybe Int))
    , TestOptsMonoid -> FirstTrue
toMonoidAllowStdin :: !FirstTrue
    } deriving (Int -> TestOptsMonoid -> ShowS
[TestOptsMonoid] -> ShowS
TestOptsMonoid -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestOptsMonoid] -> ShowS
$cshowList :: [TestOptsMonoid] -> ShowS
show :: TestOptsMonoid -> String
$cshow :: TestOptsMonoid -> String
showsPrec :: Int -> TestOptsMonoid -> ShowS
$cshowsPrec :: Int -> TestOptsMonoid -> ShowS
Show, forall x. Rep TestOptsMonoid x -> TestOptsMonoid
forall x. TestOptsMonoid -> Rep TestOptsMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestOptsMonoid x -> TestOptsMonoid
$cfrom :: forall x. TestOptsMonoid -> Rep TestOptsMonoid x
Generic)

instance FromJSON (WithJSONWarnings TestOptsMonoid) where
  parseJSON :: Value -> Parser (WithJSONWarnings TestOptsMonoid)
parseJSON = forall a.
String
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings String
"TestOptsMonoid"
    (\Object
o -> do FirstTrue
toMonoidRerunTests <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidRerunTestsArgName
              [String]
toMonoidAdditionalArgs <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidAdditionalArgsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
              FirstFalse
toMonoidCoverage <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidCoverageArgName
              FirstFalse
toMonoidDisableRun <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidDisableRunArgName
              First (Maybe Int)
toMonoidMaximumTimeSeconds <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidMaximumTimeSecondsArgName
              FirstTrue
toMonoidAllowStdin <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
toMonoidTestsAllowStdinName
              forall (f :: * -> *) a. Applicative f => a -> f a
pure TestOptsMonoid{[String]
First (Maybe Int)
FirstFalse
FirstTrue
toMonoidAllowStdin :: FirstTrue
toMonoidMaximumTimeSeconds :: First (Maybe Int)
toMonoidDisableRun :: FirstFalse
toMonoidCoverage :: FirstFalse
toMonoidAdditionalArgs :: [String]
toMonoidRerunTests :: FirstTrue
toMonoidMaximumTimeSeconds :: First (Maybe Int)
toMonoidAdditionalArgs :: [String]
toMonoidAllowStdin :: FirstTrue
toMonoidDisableRun :: FirstFalse
toMonoidCoverage :: FirstFalse
toMonoidRerunTests :: FirstTrue
..})

toMonoidRerunTestsArgName :: Text
toMonoidRerunTestsArgName :: Text
toMonoidRerunTestsArgName = Text
"rerun-tests"

toMonoidAdditionalArgsName :: Text
toMonoidAdditionalArgsName :: Text
toMonoidAdditionalArgsName = Text
"additional-args"

toMonoidCoverageArgName :: Text
toMonoidCoverageArgName :: Text
toMonoidCoverageArgName = Text
"coverage"

toMonoidDisableRunArgName :: Text
toMonoidDisableRunArgName :: Text
toMonoidDisableRunArgName = Text
"no-run-tests"

toMonoidMaximumTimeSecondsArgName :: Text
toMonoidMaximumTimeSecondsArgName :: Text
toMonoidMaximumTimeSecondsArgName = Text
"test-suite-timeout"

toMonoidTestsAllowStdinName :: Text
toMonoidTestsAllowStdinName :: Text
toMonoidTestsAllowStdinName = Text
"tests-allow-stdin"

instance Semigroup TestOptsMonoid where
  <> :: TestOptsMonoid -> TestOptsMonoid -> TestOptsMonoid
(<>) = forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault

instance Monoid TestOptsMonoid where
  mempty :: TestOptsMonoid
mempty = forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
  mappend :: TestOptsMonoid -> TestOptsMonoid -> TestOptsMonoid
mappend = forall a. Semigroup a => a -> a -> a
(<>)



-- | Haddock Options

newtype HaddockOpts =
  HaddockOpts { HaddockOpts -> [String]
hoAdditionalArgs :: [String] -- ^ Arguments passed to haddock program

              } deriving (HaddockOpts -> HaddockOpts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HaddockOpts -> HaddockOpts -> Bool
$c/= :: HaddockOpts -> HaddockOpts -> Bool
== :: HaddockOpts -> HaddockOpts -> Bool
$c== :: HaddockOpts -> HaddockOpts -> Bool
Eq,Int -> HaddockOpts -> ShowS
[HaddockOpts] -> ShowS
HaddockOpts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HaddockOpts] -> ShowS
$cshowList :: [HaddockOpts] -> ShowS
show :: HaddockOpts -> String
$cshow :: HaddockOpts -> String
showsPrec :: Int -> HaddockOpts -> ShowS
$cshowsPrec :: Int -> HaddockOpts -> ShowS
Show)

newtype HaddockOptsMonoid =
  HaddockOptsMonoid {HaddockOptsMonoid -> [String]
hoMonoidAdditionalArgs :: [String]
                    } deriving (Int -> HaddockOptsMonoid -> ShowS
[HaddockOptsMonoid] -> ShowS
HaddockOptsMonoid -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HaddockOptsMonoid] -> ShowS
$cshowList :: [HaddockOptsMonoid] -> ShowS
show :: HaddockOptsMonoid -> String
$cshow :: HaddockOptsMonoid -> String
showsPrec :: Int -> HaddockOptsMonoid -> ShowS
$cshowsPrec :: Int -> HaddockOptsMonoid -> ShowS
Show, forall x. Rep HaddockOptsMonoid x -> HaddockOptsMonoid
forall x. HaddockOptsMonoid -> Rep HaddockOptsMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HaddockOptsMonoid x -> HaddockOptsMonoid
$cfrom :: forall x. HaddockOptsMonoid -> Rep HaddockOptsMonoid x
Generic)

defaultHaddockOpts :: HaddockOpts
defaultHaddockOpts :: HaddockOpts
defaultHaddockOpts = HaddockOpts {hoAdditionalArgs :: [String]
hoAdditionalArgs = []}

instance FromJSON (WithJSONWarnings HaddockOptsMonoid) where
  parseJSON :: Value -> Parser (WithJSONWarnings HaddockOptsMonoid)
parseJSON = forall a.
String
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings String
"HaddockOptsMonoid"
    (\Object
o -> do [String]
hoMonoidAdditionalArgs <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
hoMonoidAdditionalArgsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
              forall (f :: * -> *) a. Applicative f => a -> f a
pure HaddockOptsMonoid{[String]
hoMonoidAdditionalArgs :: [String]
hoMonoidAdditionalArgs :: [String]
..})

instance Semigroup HaddockOptsMonoid where
  <> :: HaddockOptsMonoid -> HaddockOptsMonoid -> HaddockOptsMonoid
(<>) = forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault

instance Monoid HaddockOptsMonoid where
  mempty :: HaddockOptsMonoid
mempty = forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
  mappend :: HaddockOptsMonoid -> HaddockOptsMonoid -> HaddockOptsMonoid
mappend = forall a. Semigroup a => a -> a -> a
(<>)

hoMonoidAdditionalArgsName :: Text
hoMonoidAdditionalArgsName :: Text
hoMonoidAdditionalArgsName = Text
"haddock-args"


-- | Options for the 'FinalAction' 'DoBenchmarks'

data BenchmarkOpts =
  BenchmarkOpts
    { BenchmarkOpts -> Maybe String
beoAdditionalArgs :: !(Maybe String) -- ^ Arguments passed to the benchmark program

    , BenchmarkOpts -> Bool
beoDisableRun :: !Bool -- ^ Disable running of benchmarks

    } deriving (BenchmarkOpts -> BenchmarkOpts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BenchmarkOpts -> BenchmarkOpts -> Bool
$c/= :: BenchmarkOpts -> BenchmarkOpts -> Bool
== :: BenchmarkOpts -> BenchmarkOpts -> Bool
$c== :: BenchmarkOpts -> BenchmarkOpts -> Bool
Eq,Int -> BenchmarkOpts -> ShowS
[BenchmarkOpts] -> ShowS
BenchmarkOpts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BenchmarkOpts] -> ShowS
$cshowList :: [BenchmarkOpts] -> ShowS
show :: BenchmarkOpts -> String
$cshow :: BenchmarkOpts -> String
showsPrec :: Int -> BenchmarkOpts -> ShowS
$cshowsPrec :: Int -> BenchmarkOpts -> ShowS
Show)

defaultBenchmarkOpts :: BenchmarkOpts
defaultBenchmarkOpts :: BenchmarkOpts
defaultBenchmarkOpts = BenchmarkOpts
    { beoAdditionalArgs :: Maybe String
beoAdditionalArgs = forall a. Maybe a
Nothing
    , beoDisableRun :: Bool
beoDisableRun = Bool
False
    }

data BenchmarkOptsMonoid =
  BenchmarkOptsMonoid
     { BenchmarkOptsMonoid -> First String
beoMonoidAdditionalArgs :: !(First String)
     , BenchmarkOptsMonoid -> First Bool
beoMonoidDisableRun :: !(First Bool)
     } deriving (Int -> BenchmarkOptsMonoid -> ShowS
[BenchmarkOptsMonoid] -> ShowS
BenchmarkOptsMonoid -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BenchmarkOptsMonoid] -> ShowS
$cshowList :: [BenchmarkOptsMonoid] -> ShowS
show :: BenchmarkOptsMonoid -> String
$cshow :: BenchmarkOptsMonoid -> String
showsPrec :: Int -> BenchmarkOptsMonoid -> ShowS
$cshowsPrec :: Int -> BenchmarkOptsMonoid -> ShowS
Show, forall x. Rep BenchmarkOptsMonoid x -> BenchmarkOptsMonoid
forall x. BenchmarkOptsMonoid -> Rep BenchmarkOptsMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BenchmarkOptsMonoid x -> BenchmarkOptsMonoid
$cfrom :: forall x. BenchmarkOptsMonoid -> Rep BenchmarkOptsMonoid x
Generic)

instance FromJSON (WithJSONWarnings BenchmarkOptsMonoid) where
  parseJSON :: Value -> Parser (WithJSONWarnings BenchmarkOptsMonoid)
parseJSON = forall a.
String
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings String
"BenchmarkOptsMonoid"
    (\Object
o -> do First String
beoMonoidAdditionalArgs <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
beoMonoidAdditionalArgsArgName
              First Bool
beoMonoidDisableRun <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
beoMonoidDisableRunArgName
              forall (f :: * -> *) a. Applicative f => a -> f a
pure BenchmarkOptsMonoid{First Bool
First String
beoMonoidDisableRun :: First Bool
beoMonoidAdditionalArgs :: First String
beoMonoidDisableRun :: First Bool
beoMonoidAdditionalArgs :: First String
..})

beoMonoidAdditionalArgsArgName :: Text
beoMonoidAdditionalArgsArgName :: Text
beoMonoidAdditionalArgsArgName = Text
"benchmark-arguments"

beoMonoidDisableRunArgName :: Text
beoMonoidDisableRunArgName :: Text
beoMonoidDisableRunArgName = Text
"no-run-benchmarks"

instance Semigroup BenchmarkOptsMonoid where
  <> :: BenchmarkOptsMonoid -> BenchmarkOptsMonoid -> BenchmarkOptsMonoid
(<>) = forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault

instance Monoid BenchmarkOptsMonoid where
  mempty :: BenchmarkOptsMonoid
mempty = forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
  mappend :: BenchmarkOptsMonoid -> BenchmarkOptsMonoid -> BenchmarkOptsMonoid
mappend = forall a. Semigroup a => a -> a -> a
(<>)

data FileWatchOpts
  = NoFileWatch
  | FileWatch
  | FileWatchPoll
  deriving (Int -> FileWatchOpts -> ShowS
[FileWatchOpts] -> ShowS
FileWatchOpts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileWatchOpts] -> ShowS
$cshowList :: [FileWatchOpts] -> ShowS
show :: FileWatchOpts -> String
$cshow :: FileWatchOpts -> String
showsPrec :: Int -> FileWatchOpts -> ShowS
$cshowsPrec :: Int -> FileWatchOpts -> ShowS
Show,FileWatchOpts -> FileWatchOpts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileWatchOpts -> FileWatchOpts -> Bool
$c/= :: FileWatchOpts -> FileWatchOpts -> Bool
== :: FileWatchOpts -> FileWatchOpts -> Bool
$c== :: FileWatchOpts -> FileWatchOpts -> Bool
Eq)

newtype CabalVerbosity = CabalVerbosity Verbosity
  deriving (CabalVerbosity -> CabalVerbosity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalVerbosity -> CabalVerbosity -> Bool
$c/= :: CabalVerbosity -> CabalVerbosity -> Bool
== :: CabalVerbosity -> CabalVerbosity -> Bool
$c== :: CabalVerbosity -> CabalVerbosity -> Bool
Eq, Int -> CabalVerbosity -> ShowS
[CabalVerbosity] -> ShowS
CabalVerbosity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CabalVerbosity] -> ShowS
$cshowList :: [CabalVerbosity] -> ShowS
show :: CabalVerbosity -> String
$cshow :: CabalVerbosity -> String
showsPrec :: Int -> CabalVerbosity -> ShowS
$cshowsPrec :: Int -> CabalVerbosity -> ShowS
Show)

toFirstCabalVerbosity :: FirstFalse -> First CabalVerbosity
toFirstCabalVerbosity :: FirstFalse -> First CabalVerbosity
toFirstCabalVerbosity FirstFalse
vf = forall a. Maybe a -> First a
First forall a b. (a -> b) -> a -> b
$ FirstFalse -> Maybe Bool
getFirstFalse FirstFalse
vf forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Bool
p ->
  if Bool
p then CabalVerbosity
verboseLevel else CabalVerbosity
normalLevel
 where
  verboseLevel :: CabalVerbosity
verboseLevel = Verbosity -> CabalVerbosity
CabalVerbosity Verbosity
verbose
  normalLevel :: CabalVerbosity
normalLevel  = Verbosity -> CabalVerbosity
CabalVerbosity Verbosity
normal

instance FromJSON CabalVerbosity where

  parseJSON :: Value -> Parser CabalVerbosity
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"CabalVerbosity" forall a b. (a -> b) -> a -> b
$ \Text
t ->
    let s :: String
s = Text -> String
T.unpack Text
t
        errMsg :: Parser a
errMsg = forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unrecognised Cabal verbosity: " forall a. [a] -> [a] -> [a]
++ String
s
    in  forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall {a}. Parser a
errMsg forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Parsec a => String -> Maybe a
simpleParsec String
s)

instance Parsec CabalVerbosity where
  parsec :: forall (m :: * -> *). CabalParsing m => m CabalVerbosity
parsec = Verbosity -> CabalVerbosity
CabalVerbosity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec