{-# LANGUAGE NoImplicitPrelude     #-}
{-# LANGUAGE ConstraintKinds       #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DefaultSignatures     #-}
{-# LANGUAGE DeriveDataTypeable    #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE MultiWayIf            #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE QuasiQuotes           #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE ViewPatterns          #-}

-- | The Config type.


module Stack.Types.Config
  (
  -- * Main configuration types and classes

  -- ** HasPlatform & HasStackRoot

    HasPlatform (..)
  , PlatformVariant (..)
  -- ** Runner

  , HasRunner (..)
  , Runner (..)
  , ColorWhen (..)
  , terminalL
  , reExecL
  -- ** Config & HasConfig

  , Config (..)
  , HasConfig (..)
  , askLatestSnapshotUrl
  , configProjectRoot
  -- ** BuildConfig & HasBuildConfig

  , BuildConfig (..)
  , ProjectPackage (..)
  , DepPackage (..)
  , ppRoot
  , ppVersion
  , ppComponents
  , ppGPD
  , stackYamlL
  , projectRootL
  , HasBuildConfig (..)
  -- ** Storage databases

  , UserStorage (..)
  , ProjectStorage (..)
  -- ** GHCVariant & HasGHCVariant

  , GHCVariant (..)
  , ghcVariantName
  , ghcVariantSuffix
  , parseGHCVariant
  , HasGHCVariant (..)
  , snapshotsDir
  -- ** EnvConfig & HasEnvConfig

  , EnvConfig (..)
  , HasSourceMap (..)
  , HasEnvConfig (..)
  , getCompilerPath
  -- * Details

  -- ** ApplyGhcOptions

  , ApplyGhcOptions (..)
  -- ** AllowNewerDeps

  , AllowNewerDeps (..)
  -- ** CabalConfigKey

  , CabalConfigKey (..)
  -- ** ConfigException

  , HpackExecutable (..)
  , ConfigException (..)
  , ConfigPrettyException (..)
  , ParseAbsolutePathException (..)
  , packageIndicesWarning
  -- ** ConfigMonoid

  , ConfigMonoid (..)
  , configMonoidInstallGHCName
  , configMonoidSystemGHCName
  , parseConfigMonoid
  -- ** DumpLogs

  , DumpLogs (..)
  -- ** EnvSettings

  , EnvSettings (..)
  , minimalEnvSettings
  , defaultEnvSettings
  , plainEnvSettings
  -- ** GlobalOpts & GlobalOptsMonoid

  , GlobalOpts (..)
  , GlobalOptsMonoid (..)
  , rslInLogL
  , StackYamlLoc (..)
  , stackYamlLocL
  , LockFileBehavior (..)
  , readLockFileBehavior
  , lockFileBehaviorL
  , defaultLogLevel
  -- ** Project & ProjectAndConfigMonoid

  , Project (..)
  , ProjectConfig (..)
  , Curator (..)
  , ProjectAndConfigMonoid (..)
  , parseProjectAndConfigMonoid
  -- ** PvpBounds

  , PvpBounds (..)
  , PvpBoundsType (..)
  , parsePvpBounds
  -- ** ColorWhen

  , readColorWhen
  -- ** Styles

  , readStyles
  -- ** SCM

  , SCM(..)
  -- * Paths

  , bindirSuffix
  , GlobalInfoSource (..)
  , getProjectWorkDir
  , docDirSuffix
  , extraBinDirs
  , hpcReportDir
  , installationRootDeps
  , installationRootLocal
  , bindirCompilerTools
  , hoogleRoot
  , hoogleDatabasePath
  , packageDatabaseDeps
  , packageDatabaseExtra
  , packageDatabaseLocal
  , platformOnlyRelDir
  , platformGhcRelDir
  , platformGhcVerOnlyRelDir
  , useShaPathOnWindows
  , shaPath
  , shaPathForBytes
  , workDirL
  , ghcInstallHook
  -- * Command-related types

  , AddCommand
  -- ** Eval

  , EvalOpts (..)
  -- ** Exec

  , ExecOpts (..)
  , SpecialExecCmd (..)
  , ExecOptsExtra (..)
  -- ** Setup

  , DownloadInfo (..)
  , VersionedDownloadInfo (..)
  , GHCDownloadInfo (..)
  , SetupInfo (..)
  -- ** Docker entrypoint

  , DockerEntrypoint (..)
  , DockerUser (..)
  , module X
  -- * Lens helpers

  , wantedCompilerVersionL
  , actualCompilerVersionL
  , HasCompiler (..)
  , DumpPackage (..)
  , CompilerPaths (..)
  , GhcPkgExe (..)
  , getGhcPkgExe
  , cpWhich
  , ExtraDirs (..)
  , buildOptsL
  , globalOptsL
  , buildOptsInstallExesL
  , buildOptsMonoidHaddockL
  , buildOptsMonoidTestsL
  , buildOptsMonoidBenchmarksL
  , buildOptsMonoidInstallExesL
  , buildOptsHaddockL
  , globalOptsBuildOptsMonoidL
  , stackRootL
  , stackGlobalConfigL
  , cabalVersionL
  , whichCompilerL
  , envOverrideSettingsL
  , shouldForceGhcColorFlag
  , appropriateGhcColorFlag
  -- * Helper logging functions

  , prettyStackDevL
  -- * Lens reexport

  , view
  , to
  ) where

import           Control.Monad.Writer ( Writer, tell )
import           Control.Monad.Trans.Except ( ExceptT )
import           Crypto.Hash ( hashWith, SHA1 (..) )
import           Pantry.Internal.AesonExtended
                   ( ToJSON, toJSON, FromJSON, FromJSONKey (..), parseJSON
                   , withText, object, (.=), (..:), (...:), (..:?), (..!=)
                   , Value(Bool), withObjectWarnings, WarningParser, Object
                   , jsonSubWarnings, jsonSubWarningsT, jsonSubWarningsTT
                   , WithJSONWarnings (..)
                   , FromJSONKeyFunction (FromJSONKeyTextParser)
                   )
import           Data.Attoparsec.Args ( parseArgs, EscapingMode (Escaping) )
import qualified Data.ByteArray.Encoding as Mem ( convertToBase, Base(Base16) )
import qualified Data.ByteString.Char8 as S8
import           Data.Coerce ( coerce )
import           Data.List ( stripPrefix )
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import qualified Data.Map.Strict as M
import qualified Data.Monoid as Monoid
import           Data.Monoid.Map ( MonoidMap (..) )
import qualified Data.Set as Set
import qualified Data.Text as T
import           Data.Yaml ( ParseException )
import qualified Data.Yaml as Yaml
import qualified Distribution.License as C
import           Distribution.ModuleName ( ModuleName )
import           Distribution.PackageDescription ( GenericPackageDescription )
import qualified Distribution.PackageDescription as C
import           Distribution.System ( Platform, Arch )
import qualified Distribution.Text
import           Distribution.Version ( anyVersion, mkVersion )
import           Generics.Deriving.Monoid ( memptydefault, mappenddefault )
import           Lens.Micro
import           Options.Applicative ( ReadM )
import qualified Options.Applicative as OA
import qualified Options.Applicative.Types as OA
import           Pantry.Internal ( Storage )
import           Path
import qualified RIO.List as List
import           Stack.Constants
import           Stack.Prelude
import           Stack.Types.Compiler
import           Stack.Types.CompilerBuild
import           Stack.Types.Docker
import           Stack.Types.GhcPkgId
import           Stack.Types.NamedComponent
import           Stack.Types.Nix
import           Stack.Types.Resolver
import           Stack.Types.SourceMap
import           Stack.Types.TemplateName
import           Stack.Types.Version
                   ( IntersectingVersionRange (..), VersionCheck (..)
                   , VersionRange, stackVersion, versionRangeText
                   )
import qualified System.FilePath as FilePath
import           System.PosixCompat.Types ( UserID, GroupID, FileMode )
import           RIO.Process ( ProcessContext, HasProcessContext (..) )
import           Casa.Client ( CasaRepoPrefix )

-- Re-exports

import           Stack.Types.Config.Build as X

-- | Type representing exceptions thrown by functions exported by the

-- "Stack.Config" module.

data ConfigException
  = ParseCustomSnapshotException Text ParseException
  | NoProjectConfigFound (Path Abs Dir) (Maybe Text)
  | UnexpectedArchiveContents [Path Abs Dir] [Path Abs File]
  | UnableToExtractArchive Text (Path Abs File)
  | BadStackVersionException VersionRange
  | NoSuchDirectory FilePath
  | ParseGHCVariantException String
  | BadStackRoot (Path Abs Dir)
  | Won'tCreateStackRootInDirectoryOwnedByDifferentUser (Path Abs Dir) (Path Abs Dir) -- ^ @$STACK_ROOT@, parent dir

  | UserDoesn'tOwnDirectory (Path Abs Dir)
  | ManualGHCVariantSettingsAreIncompatibleWithSystemGHC
  | NixRequiresSystemGhc
  | NoResolverWhenUsingNoProject
  | DuplicateLocalPackageNames ![(PackageName, [PackageLocation])]
  | NoLTSWithMajorVersion Int
  | NoLTSFound
  | MultiplePackageIndices [PackageIndexConfig]
  deriving (Int -> ConfigException -> ShowS
[ConfigException] -> ShowS
ConfigException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ConfigException] -> ShowS
$cshowList :: [ConfigException] -> ShowS
show :: ConfigException -> [Char]
$cshow :: ConfigException -> [Char]
showsPrec :: Int -> ConfigException -> ShowS
$cshowsPrec :: Int -> ConfigException -> ShowS
Show, Typeable)

instance Exception ConfigException where
    displayException :: ConfigException -> [Char]
displayException (ParseCustomSnapshotException Text
url ParseException
exception) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-8981]\n"
        , [Char]
"Could not parse '"
        , Text -> [Char]
T.unpack Text
url
        , [Char]
"':\n"
        , ParseException -> [Char]
Yaml.prettyPrintParseException ParseException
exception
        , [Char]
"\nSee https://docs.haskellstack.org/en/stable/custom_snapshot/"
        ]
    displayException (NoProjectConfigFound Path Abs Dir
dir Maybe Text
mcmd) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-2206]\n"
        , [Char]
"Unable to find a stack.yaml file in the current directory ("
        , forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
dir
        , [Char]
") or its ancestors"
        , case Maybe Text
mcmd of
            Maybe Text
Nothing -> [Char]
""
            Just Text
cmd -> [Char]
"\nRecommended action: stack " forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack Text
cmd
        ]
    displayException (UnexpectedArchiveContents [Path Abs Dir]
dirs [Path Abs File]
files) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-4964]\n"
        , [Char]
"When unpacking an archive specified in your stack.yaml file, "
        , [Char]
"did not find expected contents. Expected: a single directory. Found: "
        , forall a. Show a => a -> [Char]
show ( forall a b. (a -> b) -> [a] -> [b]
map (forall b t. Path b t -> [Char]
toFilePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. Path b Dir -> Path Rel Dir
dirname) [Path Abs Dir]
dirs
               , forall a b. (a -> b) -> [a] -> [b]
map (forall b t. Path b t -> [Char]
toFilePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. Path b File -> Path Rel File
filename) [Path Abs File]
files
               )
        ]
    displayException (UnableToExtractArchive Text
url Path Abs File
file) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-2040]\n"
        , [Char]
"Archive extraction failed. Tarballs and zip archives are supported, \
          \couldn't handle the following URL, "
        , Text -> [Char]
T.unpack Text
url
        , [Char]
" downloaded to the file "
        , forall b t. Path b t -> [Char]
toFilePath forall a b. (a -> b) -> a -> b
$ forall b. Path b File -> Path Rel File
filename Path Abs File
file
        ]
    displayException (BadStackVersionException VersionRange
requiredRange) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-1641]\n"
        , [Char]
"The version of Stack you are using ("
        , forall a. Show a => a -> [Char]
show Version
stackVersion
        , [Char]
") is outside the required\n"
        ,[Char]
"version range specified in stack.yaml ("
        , Text -> [Char]
T.unpack (VersionRange -> Text
versionRangeText VersionRange
requiredRange)
        , [Char]
").\n"
        , [Char]
"You can upgrade Stack by running:\n\n"
        , [Char]
"stack upgrade"
        ]
    displayException (NoSuchDirectory [Char]
dir) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-8773]\n"
        , [Char]
"No directory could be located matching the supplied path: "
        , [Char]
dir
        ]
    displayException (ParseGHCVariantException [Char]
v) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-3938]\n"
        , [Char]
"Invalid ghc-variant value: "
        , [Char]
v
        ]
    displayException (BadStackRoot Path Abs Dir
stackRoot) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-8530]\n"
        , [Char]
"Invalid Stack root: '"
        , forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
stackRoot
        , [Char]
"'. Please provide a valid absolute path."
        ]
    displayException (Won'tCreateStackRootInDirectoryOwnedByDifferentUser Path Abs Dir
envStackRoot Path Abs Dir
parentDir) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-7613]\n"
        , [Char]
"Preventing creation of Stack root '"
        , forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
envStackRoot
        , [Char]
"'. Parent directory '"
        , forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
parentDir
        , [Char]
"' is owned by someone else."
        ]
    displayException (UserDoesn'tOwnDirectory Path Abs Dir
dir) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-8707]\n"
        , [Char]
"You are not the owner of '"
        , forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
dir
        , [Char]
"'. Aborting to protect file permissions."
        , [Char]
"\nRetry with '--"
        , Text -> [Char]
T.unpack Text
configMonoidAllowDifferentUserName
        , [Char]
"' to disable this precaution."
        ]
    displayException ConfigException
ManualGHCVariantSettingsAreIncompatibleWithSystemGHC = Text -> [Char]
T.unpack forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
        [ Text
"Error: [S-3605]\n"
        , Text
"Stack can only control the "
        , Text
configMonoidGHCVariantName
        , Text
" of its own GHC installations. Please use '--no-"
        , Text
configMonoidSystemGHCName
        , Text
"'."
        ]
    displayException ConfigException
NixRequiresSystemGhc = Text -> [Char]
T.unpack forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
        [ Text
"Error: [S-6816]\n"
        , Text
"Stack's Nix integration is incompatible with '--no-system-ghc'. "
        , Text
"Please use '--"
        , Text
configMonoidSystemGHCName
        , Text
"' or disable the Nix integration."
        ]
    displayException ConfigException
NoResolverWhenUsingNoProject =
        [Char]
"Error: [S-5027]\n"
        forall a. [a] -> [a] -> [a]
++ [Char]
"When using the script command, you must provide a resolver argument"
    displayException (DuplicateLocalPackageNames [(PackageName, [PackageLocation])]
pairs) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        forall a b. (a -> b) -> a -> b
$ [Char]
"Error: [S-5470]\n"
        forall a. a -> [a] -> [a]
: [Char]
"The same package name is used in multiple local packages\n"
        forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall {a}. Show a => (PackageName, [a]) -> [Char]
go [(PackageName, [PackageLocation])]
pairs
      where
        go :: (PackageName, [a]) -> [Char]
go (PackageName
name, [a]
dirs) = [[Char]] -> [Char]
unlines
            forall a b. (a -> b) -> a -> b
$ [Char]
""
            forall a. a -> [a] -> [a]
: (PackageName -> [Char]
packageNameString PackageName
name forall a. [a] -> [a] -> [a]
++ [Char]
" used in:")
            forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> [Char]
goLoc [a]
dirs
        goLoc :: a -> [Char]
goLoc a
loc = [Char]
"- " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show a
loc
    displayException (NoLTSWithMajorVersion Int
n) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-3803]\n"
        , [Char]
"No LTS release found with major version "
        , forall a. Show a => a -> [Char]
show Int
n
        , [Char]
"."
        ]
    displayException ConfigException
NoLTSFound =
        [Char]
"Error: [S-5472]\n"
        forall a. [a] -> [a] -> [a]
++ [Char]
"No LTS releases found."
    displayException (MultiplePackageIndices [PackageIndexConfig]
pics) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-3251]\n"
        , [Char]
"When using the 'package-indices' key to override the default "
        , [Char]
"package index, you must provide exactly one value, received: "
        , forall a. Show a => a -> [Char]
show [PackageIndexConfig]
pics
        , [Char]
"\n"
        , [Char]
packageIndicesWarning
        ]

-- | Type representing \'pretty\' exceptions thrown by functions exported by the

-- "Stack.Config" module.

data ConfigPrettyException
    = ParseConfigFileException !(Path Abs File) !ParseException
    | NoMatchingSnapshot !(NonEmpty SnapName)
    | ResolverMismatch !RawSnapshotLocation String
    | ResolverPartial !RawSnapshotLocation !String
    deriving (Int -> ConfigPrettyException -> ShowS
[ConfigPrettyException] -> ShowS
ConfigPrettyException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ConfigPrettyException] -> ShowS
$cshowList :: [ConfigPrettyException] -> ShowS
show :: ConfigPrettyException -> [Char]
$cshow :: ConfigPrettyException -> [Char]
showsPrec :: Int -> ConfigPrettyException -> ShowS
$cshowsPrec :: Int -> ConfigPrettyException -> ShowS
Show, Typeable)

instance Pretty ConfigPrettyException where
    pretty :: ConfigPrettyException -> StyleDoc
pretty (ParseConfigFileException Path Abs File
configFile ParseException
exception) =
        StyleDoc
"[S-6602]"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
             [ [Char] -> StyleDoc
flow [Char]
"Stack could not load and parse"
             , Style -> StyleDoc -> StyleDoc
style Style
File (forall a. Pretty a => a -> StyleDoc
pretty Path Abs File
configFile)
             , [Char] -> StyleDoc
flow [Char]
"as a YAML configuraton file."
             ]
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> [Char] -> StyleDoc
flow [Char]
"While loading and parsing, Stack encountered the following \
                \error:"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> [Char] -> StyleDoc
string (ParseException -> [Char]
Yaml.prettyPrintParseException ParseException
exception)
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
             [ [Char] -> StyleDoc
flow [Char]
"For help about the content of Stack's YAML configuration \
                    \files, see (for the most recent release of Stack)"
             ,    Style -> StyleDoc -> StyleDoc
style
                    Style
Url
                    StyleDoc
"http://docs.haskellstack.org/en/stable/yaml_configuration/"
               forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
             ]
    pretty (NoMatchingSnapshot NonEmpty SnapName
names) =
        StyleDoc
"[S-1833]"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> [Char] -> StyleDoc
flow [Char]
"None of the following snapshots provides a compiler matching \
                \your package(s):"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
bulletedList (forall a b. (a -> b) -> [a] -> [b]
map (forall a. IsString a => [Char] -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> [Char]
show) (forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty SnapName
names))
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
resolveOptions
    pretty (ResolverMismatch RawSnapshotLocation
resolver [Char]
errDesc) =
        StyleDoc
"[S-6395]"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
             [ StyleDoc
"Snapshot"
             , Style -> StyleDoc -> StyleDoc
style Style
Url (forall a. Pretty a => a -> StyleDoc
pretty forall a b. (a -> b) -> a -> b
$ RawSnapshotLocation -> PrettyRawSnapshotLocation
PrettyRawSnapshotLocation RawSnapshotLocation
resolver)
             , [Char] -> StyleDoc
flow [Char]
"does not have a matching compiler to build some or all of \
                    \your package(s)."
             ]
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> Int -> StyleDoc -> StyleDoc
indent Int
4 ([Char] -> StyleDoc
string [Char]
errDesc)
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
resolveOptions
    pretty (ResolverPartial RawSnapshotLocation
resolver [Char]
errDesc) =
        StyleDoc
"[S-2422]"
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
             [ StyleDoc
"Snapshot"
             , Style -> StyleDoc -> StyleDoc
style Style
Url (forall a. Pretty a => a -> StyleDoc
pretty forall a b. (a -> b) -> a -> b
$ RawSnapshotLocation -> PrettyRawSnapshotLocation
PrettyRawSnapshotLocation RawSnapshotLocation
resolver)
             , [Char] -> StyleDoc
flow [Char]
"does not have all the packages to match your requirements."
             ]
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
        forall a. Semigroup a => a -> a -> a
<> Int -> StyleDoc -> StyleDoc
indent Int
4 ([Char] -> StyleDoc
string [Char]
errDesc)
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
        forall a. Semigroup a => a -> a -> a
<> StyleDoc
resolveOptions

instance Exception ConfigPrettyException

data ParseAbsolutePathException
    = ParseAbsolutePathException String String
    deriving (Int -> ParseAbsolutePathException -> ShowS
[ParseAbsolutePathException] -> ShowS
ParseAbsolutePathException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ParseAbsolutePathException] -> ShowS
$cshowList :: [ParseAbsolutePathException] -> ShowS
show :: ParseAbsolutePathException -> [Char]
$cshow :: ParseAbsolutePathException -> [Char]
showsPrec :: Int -> ParseAbsolutePathException -> ShowS
$cshowsPrec :: Int -> ParseAbsolutePathException -> ShowS
Show, Typeable)

instance Exception ParseAbsolutePathException where
    displayException :: ParseAbsolutePathException -> [Char]
displayException (ParseAbsolutePathException [Char]
envVar [Char]
dir) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [Char]
"Error: [S-9437]\n"
        , [Char]
"Failed to parse "
        , [Char]
envVar
        , [Char]
" environment variable (expected absolute directory): "
        , [Char]
dir
        ]

-- | The base environment that almost everything in Stack runs in,

-- based off of parsing command line options in 'GlobalOpts'. Provides

-- logging and process execution.

data Runner = Runner
  { Runner -> GlobalOpts
runnerGlobalOpts :: !GlobalOpts
  , Runner -> Bool
runnerUseColor   :: !Bool
  , Runner -> LogFunc
runnerLogFunc    :: !LogFunc
  , Runner -> Int
runnerTermWidth  :: !Int
  , Runner -> ProcessContext
runnerProcessContext :: !ProcessContext
  }

data ColorWhen = ColorNever | ColorAlways | ColorAuto
    deriving (ColorWhen -> ColorWhen -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorWhen -> ColorWhen -> Bool
$c/= :: ColorWhen -> ColorWhen -> Bool
== :: ColorWhen -> ColorWhen -> Bool
$c== :: ColorWhen -> ColorWhen -> Bool
Eq, Int -> ColorWhen -> ShowS
[ColorWhen] -> ShowS
ColorWhen -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ColorWhen] -> ShowS
$cshowList :: [ColorWhen] -> ShowS
show :: ColorWhen -> [Char]
$cshow :: ColorWhen -> [Char]
showsPrec :: Int -> ColorWhen -> ShowS
$cshowsPrec :: Int -> ColorWhen -> ShowS
Show, forall x. Rep ColorWhen x -> ColorWhen
forall x. ColorWhen -> Rep ColorWhen x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColorWhen x -> ColorWhen
$cfrom :: forall x. ColorWhen -> Rep ColorWhen x
Generic)

instance FromJSON ColorWhen where
    parseJSON :: Value -> Parser ColorWhen
parseJSON Value
v = do
        [Char]
s <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
        case [Char]
s of
            [Char]
"never"  -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorNever
            [Char]
"always" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorAlways
            [Char]
"auto"   -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorAuto
            [Char]
_ -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"Unknown color use: " forall a. Semigroup a => a -> a -> a
<> [Char]
s forall a. Semigroup a => a -> a -> a
<> [Char]
". Expected values of " forall a. Semigroup a => a -> a -> a
<>
                       [Char]
"option are 'never', 'always', or 'auto'.")

-- | The top-level Stackage configuration.

data Config =
  Config {Config -> Path Rel Dir
configWorkDir             :: !(Path Rel Dir)
         -- ^ this allows to override .stack-work directory

         ,Config -> Path Abs File
configUserConfigPath      :: !(Path Abs File)
         -- ^ Path to user configuration file (usually ~/.stack/config.yaml)

         ,Config -> BuildOpts
configBuild               :: !BuildOpts
         -- ^ Build configuration

         ,Config -> DockerOpts
configDocker              :: !DockerOpts
         -- ^ Docker configuration

         ,Config -> NixOpts
configNix                 :: !NixOpts
         -- ^ Execution environment (e.g nix-shell) configuration

         ,Config -> EnvSettings -> IO ProcessContext
configProcessContextSettings :: !(EnvSettings -> IO ProcessContext)
         -- ^ Environment variables to be passed to external tools

         ,Config -> Path Abs Dir
configLocalProgramsBase   :: !(Path Abs Dir)
         -- ^ Non-platform-specific path containing local installations

         ,Config -> Path Abs Dir
configLocalPrograms       :: !(Path Abs Dir)
         -- ^ Path containing local installations (mainly GHC)

         ,Config -> Bool
configHideTHLoading       :: !Bool
         -- ^ Hide the Template Haskell "Loading package ..." messages from the

         -- console

         ,Config -> Bool
configPrefixTimestamps    :: !Bool
         -- ^ Prefix build output with timestamps for each line.

         ,Config -> Platform
configPlatform            :: !Platform
         -- ^ The platform we're building for, used in many directory names

         ,Config -> PlatformVariant
configPlatformVariant     :: !PlatformVariant
         -- ^ Variant of the platform, also used in directory names

         ,Config -> Maybe GHCVariant
configGHCVariant          :: !(Maybe GHCVariant)
         -- ^ The variant of GHC requested by the user.

         ,Config -> Maybe CompilerBuild
configGHCBuild            :: !(Maybe CompilerBuild)
         -- ^ Override build of the compiler distribution (e.g. standard, gmp4, tinfo6)

         ,Config -> Text
configLatestSnapshot      :: !Text
         -- ^ URL of a JSON file providing the latest LTS and Nightly snapshots.

         ,Config -> Bool
configSystemGHC           :: !Bool
         -- ^ Should we use the system-installed GHC (on the PATH) if

         -- available? Can be overridden by command line options.

         ,Config -> Bool
configInstallGHC          :: !Bool
         -- ^ Should we automatically install GHC if missing or the wrong

         -- version is available? Can be overridden by command line options.

         ,Config -> Bool
configSkipGHCCheck        :: !Bool
         -- ^ Don't bother checking the GHC version or architecture.

         ,Config -> Bool
configSkipMsys            :: !Bool
         -- ^ On Windows: don't use a sandboxed MSYS

         ,Config -> VersionCheck
configCompilerCheck       :: !VersionCheck
         -- ^ Specifies which versions of the compiler are acceptable.

         ,Config -> CompilerRepository
configCompilerRepository  :: !CompilerRepository
         -- ^ Specifies the repository containing the compiler sources

         ,Config -> Path Abs Dir
configLocalBin            :: !(Path Abs Dir)
         -- ^ Directory we should install executables into

         ,Config -> VersionRange
configRequireStackVersion :: !VersionRange
         -- ^ Require a version of Stack within this range.

         ,Config -> Int
configJobs                :: !Int
         -- ^ How many concurrent jobs to run, defaults to number of capabilities

         ,Config -> Maybe (Path Abs File)
configOverrideGccPath     :: !(Maybe (Path Abs File))
         -- ^ Optional gcc override path

         ,Config -> [[Char]]
configExtraIncludeDirs    :: ![FilePath]
         -- ^ --extra-include-dirs arguments

         ,Config -> [[Char]]
configExtraLibDirs        :: ![FilePath]
         -- ^ --extra-lib-dirs arguments

         ,Config -> [Text]
configCustomPreprocessorExts :: ![Text]
         -- ^ List of custom preprocessors to complete the hard coded ones

         ,Config -> Bool
configConcurrentTests     :: !Bool
         -- ^ Run test suites concurrently

         ,Config -> Map Text Text
configTemplateParams      :: !(Map Text Text)
         -- ^ Parameters for templates.

         ,Config -> Maybe SCM
configScmInit             :: !(Maybe SCM)
         -- ^ Initialize SCM (e.g. git) when creating new projects.

         ,Config -> Map PackageName [Text]
configGhcOptionsByName    :: !(Map PackageName [Text])
         -- ^ Additional GHC options to apply to specific packages.

         ,Config -> Map ApplyGhcOptions [Text]
configGhcOptionsByCat     :: !(Map ApplyGhcOptions [Text])
         -- ^ Additional GHC options to apply to categories of packages

         ,Config -> Map CabalConfigKey [Text]
configCabalConfigOpts     :: !(Map CabalConfigKey [Text])
         -- ^ Additional options to be passed to ./Setup.hs configure

         ,Config -> [[Char]]
configSetupInfoLocations  :: ![String]
         -- ^ URLs or paths to stack-setup.yaml files, for finding tools.

         -- If none present, the default setup-info is used.

         ,Config -> SetupInfo
configSetupInfoInline     :: !SetupInfo
         -- ^ Additional SetupInfo to use to find tools.

         ,Config -> PvpBounds
configPvpBounds           :: !PvpBounds
         -- ^ How PVP upper bounds should be added to packages

         ,Config -> Bool
configModifyCodePage      :: !Bool
         -- ^ Force the code page to UTF-8 on Windows

         ,Config -> Bool
configRebuildGhcOptions   :: !Bool
         -- ^ Rebuild on GHC options changes

         ,Config -> ApplyGhcOptions
configApplyGhcOptions     :: !ApplyGhcOptions
         -- ^ Which packages to ghc-options on the command line apply to?

         ,Config -> Bool
configAllowNewer          :: !Bool
         -- ^ Ignore version ranges in .cabal files. Funny naming chosen to

         -- match cabal.

         ,Config -> Maybe [PackageName]
configAllowNewerDeps      :: !(Maybe [PackageName])
         -- ^ Ignore dependency upper and lower bounds only for specified

         -- packages. No effect unless allow-newer is enabled.

         ,Config -> Maybe TemplateName
configDefaultTemplate     :: !(Maybe TemplateName)
         -- ^ The default template to use when none is specified.

         -- (If Nothing, the 'default' default template is used.)

         ,Config -> Bool
configAllowDifferentUser  :: !Bool
         -- ^ Allow users other than the Stack root owner to use the Stack

         -- installation.

         ,Config -> DumpLogs
configDumpLogs            :: !DumpLogs
         -- ^ Dump logs of local non-dependencies when doing a build.

         ,Config -> ProjectConfig (Project, Path Abs File)
configProject             :: !(ProjectConfig (Project, Path Abs File))
         -- ^ Project information and stack.yaml file location

         ,Config -> Bool
configAllowLocals         :: !Bool
         -- ^ Are we allowed to build local packages? The script

         -- command disallows this.

         ,Config -> Bool
configSaveHackageCreds    :: !Bool
         -- ^ Should we save Hackage credentials to a file?

         ,Config -> Text
configHackageBaseUrl      :: !Text
         -- ^ Hackage base URL used when uploading packages

         ,Config -> Runner
configRunner              :: !Runner
         ,Config -> PantryConfig
configPantryConfig        :: !PantryConfig
         ,Config -> Path Abs Dir
configStackRoot           :: !(Path Abs Dir)
         ,Config -> Maybe AbstractResolver
configResolver            :: !(Maybe AbstractResolver)
         -- ^ Any resolver override from the command line

         ,Config -> UserStorage
configUserStorage         :: !UserStorage
         -- ^ Database connection pool for user Stack database

         ,Config -> Bool
configHideSourcePaths     :: !Bool
         -- ^ Enable GHC hiding source paths?

         ,Config -> Bool
configRecommendUpgrade    :: !Bool
         -- ^ Recommend a Stack upgrade?

         ,Config -> Bool
configNoRunCompile   :: !Bool
         -- ^ Use --no-run and --compile options when using `stack script`

         ,Config -> Bool
configStackDeveloperMode  :: !Bool
         -- ^ Turn on Stack developer mode for additional messages?

         }

-- | A bit of type safety to ensure we're talking to the right database.

newtype UserStorage = UserStorage
  { UserStorage -> Storage
unUserStorage :: Storage
  }

-- | A bit of type safety to ensure we're talking to the right database.

newtype ProjectStorage = ProjectStorage
  { ProjectStorage -> Storage
unProjectStorage :: Storage
  }

-- | The project root directory, if in a project.

configProjectRoot :: Config -> Maybe (Path Abs Dir)
configProjectRoot :: Config -> Maybe (Path Abs Dir)
configProjectRoot Config
c =
  case Config -> ProjectConfig (Project, Path Abs File)
configProject Config
c of
    PCProject (Project
_, Path Abs File
fp) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
fp
    ProjectConfig (Project, Path Abs File)
PCGlobalProject -> forall a. Maybe a
Nothing
    PCNoProject [PackageIdentifierRevision]
_deps -> forall a. Maybe a
Nothing

-- | Which packages do configure opts apply to?

data CabalConfigKey
  = CCKTargets -- ^ See AGOTargets

  | CCKLocals -- ^ See AGOLocals

  | CCKEverything -- ^ See AGOEverything

  | CCKPackage !PackageName -- ^ A specific package

  deriving (Int -> CabalConfigKey -> ShowS
[CabalConfigKey] -> ShowS
CabalConfigKey -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CabalConfigKey] -> ShowS
$cshowList :: [CabalConfigKey] -> ShowS
show :: CabalConfigKey -> [Char]
$cshow :: CabalConfigKey -> [Char]
showsPrec :: Int -> CabalConfigKey -> ShowS
$cshowsPrec :: Int -> CabalConfigKey -> ShowS
Show, ReadPrec [CabalConfigKey]
ReadPrec CabalConfigKey
Int -> ReadS CabalConfigKey
ReadS [CabalConfigKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CabalConfigKey]
$creadListPrec :: ReadPrec [CabalConfigKey]
readPrec :: ReadPrec CabalConfigKey
$creadPrec :: ReadPrec CabalConfigKey
readList :: ReadS [CabalConfigKey]
$creadList :: ReadS [CabalConfigKey]
readsPrec :: Int -> ReadS CabalConfigKey
$creadsPrec :: Int -> ReadS CabalConfigKey
Read, CabalConfigKey -> CabalConfigKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalConfigKey -> CabalConfigKey -> Bool
$c/= :: CabalConfigKey -> CabalConfigKey -> Bool
== :: CabalConfigKey -> CabalConfigKey -> Bool
$c== :: CabalConfigKey -> CabalConfigKey -> Bool
Eq, Eq CabalConfigKey
CabalConfigKey -> CabalConfigKey -> Bool
CabalConfigKey -> CabalConfigKey -> Ordering
CabalConfigKey -> CabalConfigKey -> CabalConfigKey
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 :: CabalConfigKey -> CabalConfigKey -> CabalConfigKey
$cmin :: CabalConfigKey -> CabalConfigKey -> CabalConfigKey
max :: CabalConfigKey -> CabalConfigKey -> CabalConfigKey
$cmax :: CabalConfigKey -> CabalConfigKey -> CabalConfigKey
>= :: CabalConfigKey -> CabalConfigKey -> Bool
$c>= :: CabalConfigKey -> CabalConfigKey -> Bool
> :: CabalConfigKey -> CabalConfigKey -> Bool
$c> :: CabalConfigKey -> CabalConfigKey -> Bool
<= :: CabalConfigKey -> CabalConfigKey -> Bool
$c<= :: CabalConfigKey -> CabalConfigKey -> Bool
< :: CabalConfigKey -> CabalConfigKey -> Bool
$c< :: CabalConfigKey -> CabalConfigKey -> Bool
compare :: CabalConfigKey -> CabalConfigKey -> Ordering
$ccompare :: CabalConfigKey -> CabalConfigKey -> Ordering
Ord)
instance FromJSON CabalConfigKey where
  parseJSON :: Value -> Parser CabalConfigKey
parseJSON = forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText [Char]
"CabalConfigKey" forall (m :: * -> *).
(Monad m, MonadFail m) =>
Text -> m CabalConfigKey
parseCabalConfigKey
instance FromJSONKey CabalConfigKey where
  fromJSONKey :: FromJSONKeyFunction CabalConfigKey
fromJSONKey = forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser forall (m :: * -> *).
(Monad m, MonadFail m) =>
Text -> m CabalConfigKey
parseCabalConfigKey

parseCabalConfigKey :: (Monad m, MonadFail m) => Text -> m CabalConfigKey
parseCabalConfigKey :: forall (m :: * -> *).
(Monad m, MonadFail m) =>
Text -> m CabalConfigKey
parseCabalConfigKey Text
"$targets" = forall (f :: * -> *) a. Applicative f => a -> f a
pure CabalConfigKey
CCKTargets
parseCabalConfigKey Text
"$locals" = forall (f :: * -> *) a. Applicative f => a -> f a
pure CabalConfigKey
CCKLocals
parseCabalConfigKey Text
"$everything" = forall (f :: * -> *) a. Applicative f => a -> f a
pure CabalConfigKey
CCKEverything
parseCabalConfigKey Text
name =
  case [Char] -> Maybe PackageName
parsePackageName forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
name of
    Maybe PackageName
Nothing -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid CabalConfigKey: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
name
    Just PackageName
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PackageName -> CabalConfigKey
CCKPackage PackageName
x

-- | Which packages do ghc-options on the command line apply to?

data ApplyGhcOptions = AGOTargets -- ^ all local targets

                     | AGOLocals -- ^ all local packages, even non-targets

                     | AGOEverything -- ^ every package

  deriving (Int -> ApplyGhcOptions -> ShowS
[ApplyGhcOptions] -> ShowS
ApplyGhcOptions -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ApplyGhcOptions] -> ShowS
$cshowList :: [ApplyGhcOptions] -> ShowS
show :: ApplyGhcOptions -> [Char]
$cshow :: ApplyGhcOptions -> [Char]
showsPrec :: Int -> ApplyGhcOptions -> ShowS
$cshowsPrec :: Int -> ApplyGhcOptions -> ShowS
Show, ReadPrec [ApplyGhcOptions]
ReadPrec ApplyGhcOptions
Int -> ReadS ApplyGhcOptions
ReadS [ApplyGhcOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplyGhcOptions]
$creadListPrec :: ReadPrec [ApplyGhcOptions]
readPrec :: ReadPrec ApplyGhcOptions
$creadPrec :: ReadPrec ApplyGhcOptions
readList :: ReadS [ApplyGhcOptions]
$creadList :: ReadS [ApplyGhcOptions]
readsPrec :: Int -> ReadS ApplyGhcOptions
$creadsPrec :: Int -> ReadS ApplyGhcOptions
Read, ApplyGhcOptions -> ApplyGhcOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c/= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
== :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c== :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
Eq, Eq ApplyGhcOptions
ApplyGhcOptions -> ApplyGhcOptions -> Bool
ApplyGhcOptions -> ApplyGhcOptions -> Ordering
ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
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 :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
$cmin :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
max :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
$cmax :: ApplyGhcOptions -> ApplyGhcOptions -> ApplyGhcOptions
>= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c>= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
> :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c> :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
<= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c<= :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
< :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
$c< :: ApplyGhcOptions -> ApplyGhcOptions -> Bool
compare :: ApplyGhcOptions -> ApplyGhcOptions -> Ordering
$ccompare :: ApplyGhcOptions -> ApplyGhcOptions -> Ordering
Ord, Int -> ApplyGhcOptions
ApplyGhcOptions -> Int
ApplyGhcOptions -> [ApplyGhcOptions]
ApplyGhcOptions -> ApplyGhcOptions
ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromThenTo :: ApplyGhcOptions
-> ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFromTo :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromTo :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFromThen :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFromThen :: ApplyGhcOptions -> ApplyGhcOptions -> [ApplyGhcOptions]
enumFrom :: ApplyGhcOptions -> [ApplyGhcOptions]
$cenumFrom :: ApplyGhcOptions -> [ApplyGhcOptions]
fromEnum :: ApplyGhcOptions -> Int
$cfromEnum :: ApplyGhcOptions -> Int
toEnum :: Int -> ApplyGhcOptions
$ctoEnum :: Int -> ApplyGhcOptions
pred :: ApplyGhcOptions -> ApplyGhcOptions
$cpred :: ApplyGhcOptions -> ApplyGhcOptions
succ :: ApplyGhcOptions -> ApplyGhcOptions
$csucc :: ApplyGhcOptions -> ApplyGhcOptions
Enum, ApplyGhcOptions
forall a. a -> a -> Bounded a
maxBound :: ApplyGhcOptions
$cmaxBound :: ApplyGhcOptions
minBound :: ApplyGhcOptions
$cminBound :: ApplyGhcOptions
Bounded)

instance FromJSON ApplyGhcOptions where
    parseJSON :: Value -> Parser ApplyGhcOptions
parseJSON = forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText [Char]
"ApplyGhcOptions" forall a b. (a -> b) -> a -> b
$ \Text
t ->
        case Text
t of
            Text
"targets" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOTargets
            Text
"locals" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOLocals
            Text
"everything" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ApplyGhcOptions
AGOEverything
            Text
_ -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid ApplyGhcOptions: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
t

newtype AllowNewerDeps = AllowNewerDeps [PackageName]
  deriving (Int -> AllowNewerDeps -> ShowS
[AllowNewerDeps] -> ShowS
AllowNewerDeps -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [AllowNewerDeps] -> ShowS
$cshowList :: [AllowNewerDeps] -> ShowS
show :: AllowNewerDeps -> [Char]
$cshow :: AllowNewerDeps -> [Char]
showsPrec :: Int -> AllowNewerDeps -> ShowS
$cshowsPrec :: Int -> AllowNewerDeps -> ShowS
Show, ReadPrec [AllowNewerDeps]
ReadPrec AllowNewerDeps
Int -> ReadS AllowNewerDeps
ReadS [AllowNewerDeps]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AllowNewerDeps]
$creadListPrec :: ReadPrec [AllowNewerDeps]
readPrec :: ReadPrec AllowNewerDeps
$creadPrec :: ReadPrec AllowNewerDeps
readList :: ReadS [AllowNewerDeps]
$creadList :: ReadS [AllowNewerDeps]
readsPrec :: Int -> ReadS AllowNewerDeps
$creadsPrec :: Int -> ReadS AllowNewerDeps
Read, AllowNewerDeps -> AllowNewerDeps -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c/= :: AllowNewerDeps -> AllowNewerDeps -> Bool
== :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c== :: AllowNewerDeps -> AllowNewerDeps -> Bool
Eq, Eq AllowNewerDeps
AllowNewerDeps -> AllowNewerDeps -> Bool
AllowNewerDeps -> AllowNewerDeps -> Ordering
AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps
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 :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps
$cmin :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps
max :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps
$cmax :: AllowNewerDeps -> AllowNewerDeps -> AllowNewerDeps
>= :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c>= :: AllowNewerDeps -> AllowNewerDeps -> Bool
> :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c> :: AllowNewerDeps -> AllowNewerDeps -> Bool
<= :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c<= :: AllowNewerDeps -> AllowNewerDeps -> Bool
< :: AllowNewerDeps -> AllowNewerDeps -> Bool
$c< :: AllowNewerDeps -> AllowNewerDeps -> Bool
compare :: AllowNewerDeps -> AllowNewerDeps -> Ordering
$ccompare :: AllowNewerDeps -> AllowNewerDeps -> Ordering
Ord, forall x. Rep AllowNewerDeps x -> AllowNewerDeps
forall x. AllowNewerDeps -> Rep AllowNewerDeps x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AllowNewerDeps x -> AllowNewerDeps
$cfrom :: forall x. AllowNewerDeps -> Rep AllowNewerDeps x
Generic)

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

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

instance FromJSON AllowNewerDeps where
  parseJSON :: Value -> Parser AllowNewerDeps
parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([PackageName] -> AllowNewerDeps
AllowNewerDeps forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> PackageName
C.mkPackageName) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => Value -> Parser a
parseJSON

-- | Which build log files to dump

data DumpLogs
  = DumpNoLogs -- ^ don't dump any logfiles

  | DumpWarningLogs -- ^ dump logfiles containing warnings

  | DumpAllLogs -- ^ dump all logfiles

  deriving (Int -> DumpLogs -> ShowS
[DumpLogs] -> ShowS
DumpLogs -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DumpLogs] -> ShowS
$cshowList :: [DumpLogs] -> ShowS
show :: DumpLogs -> [Char]
$cshow :: DumpLogs -> [Char]
showsPrec :: Int -> DumpLogs -> ShowS
$cshowsPrec :: Int -> DumpLogs -> ShowS
Show, ReadPrec [DumpLogs]
ReadPrec DumpLogs
Int -> ReadS DumpLogs
ReadS [DumpLogs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DumpLogs]
$creadListPrec :: ReadPrec [DumpLogs]
readPrec :: ReadPrec DumpLogs
$creadPrec :: ReadPrec DumpLogs
readList :: ReadS [DumpLogs]
$creadList :: ReadS [DumpLogs]
readsPrec :: Int -> ReadS DumpLogs
$creadsPrec :: Int -> ReadS DumpLogs
Read, DumpLogs -> DumpLogs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DumpLogs -> DumpLogs -> Bool
$c/= :: DumpLogs -> DumpLogs -> Bool
== :: DumpLogs -> DumpLogs -> Bool
$c== :: DumpLogs -> DumpLogs -> Bool
Eq, Eq DumpLogs
DumpLogs -> DumpLogs -> Bool
DumpLogs -> DumpLogs -> Ordering
DumpLogs -> DumpLogs -> DumpLogs
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 :: DumpLogs -> DumpLogs -> DumpLogs
$cmin :: DumpLogs -> DumpLogs -> DumpLogs
max :: DumpLogs -> DumpLogs -> DumpLogs
$cmax :: DumpLogs -> DumpLogs -> DumpLogs
>= :: DumpLogs -> DumpLogs -> Bool
$c>= :: DumpLogs -> DumpLogs -> Bool
> :: DumpLogs -> DumpLogs -> Bool
$c> :: DumpLogs -> DumpLogs -> Bool
<= :: DumpLogs -> DumpLogs -> Bool
$c<= :: DumpLogs -> DumpLogs -> Bool
< :: DumpLogs -> DumpLogs -> Bool
$c< :: DumpLogs -> DumpLogs -> Bool
compare :: DumpLogs -> DumpLogs -> Ordering
$ccompare :: DumpLogs -> DumpLogs -> Ordering
Ord, Int -> DumpLogs
DumpLogs -> Int
DumpLogs -> [DumpLogs]
DumpLogs -> DumpLogs
DumpLogs -> DumpLogs -> [DumpLogs]
DumpLogs -> DumpLogs -> DumpLogs -> [DumpLogs]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DumpLogs -> DumpLogs -> DumpLogs -> [DumpLogs]
$cenumFromThenTo :: DumpLogs -> DumpLogs -> DumpLogs -> [DumpLogs]
enumFromTo :: DumpLogs -> DumpLogs -> [DumpLogs]
$cenumFromTo :: DumpLogs -> DumpLogs -> [DumpLogs]
enumFromThen :: DumpLogs -> DumpLogs -> [DumpLogs]
$cenumFromThen :: DumpLogs -> DumpLogs -> [DumpLogs]
enumFrom :: DumpLogs -> [DumpLogs]
$cenumFrom :: DumpLogs -> [DumpLogs]
fromEnum :: DumpLogs -> Int
$cfromEnum :: DumpLogs -> Int
toEnum :: Int -> DumpLogs
$ctoEnum :: Int -> DumpLogs
pred :: DumpLogs -> DumpLogs
$cpred :: DumpLogs -> DumpLogs
succ :: DumpLogs -> DumpLogs
$csucc :: DumpLogs -> DumpLogs
Enum, DumpLogs
forall a. a -> a -> Bounded a
maxBound :: DumpLogs
$cmaxBound :: DumpLogs
minBound :: DumpLogs
$cminBound :: DumpLogs
Bounded)

instance FromJSON DumpLogs where
  parseJSON :: Value -> Parser DumpLogs
parseJSON (Bool Bool
True) = forall (f :: * -> *) a. Applicative f => a -> f a
pure DumpLogs
DumpAllLogs
  parseJSON (Bool Bool
False) = forall (f :: * -> *) a. Applicative f => a -> f a
pure DumpLogs
DumpNoLogs
  parseJSON Value
v =
    forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText
      [Char]
"DumpLogs"
      (\Text
t ->
          if | Text
t forall a. Eq a => a -> a -> Bool
== Text
"none" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DumpLogs
DumpNoLogs
             | Text
t forall a. Eq a => a -> a -> Bool
== Text
"warning" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DumpLogs
DumpWarningLogs
             | Text
t forall a. Eq a => a -> a -> Bool
== Text
"all" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DumpLogs
DumpAllLogs
             | Bool
otherwise -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"Invalid DumpLogs: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
t))
      Value
v

-- | Controls which version of the environment is used

data EnvSettings = EnvSettings
    { EnvSettings -> Bool
esIncludeLocals :: !Bool
    -- ^ include local project bin directory, GHC_PACKAGE_PATH, etc

    , EnvSettings -> Bool
esIncludeGhcPackagePath :: !Bool
    -- ^ include the GHC_PACKAGE_PATH variable

    , EnvSettings -> Bool
esStackExe :: !Bool
    -- ^ set the STACK_EXE variable to the current executable name

    , EnvSettings -> Bool
esLocaleUtf8 :: !Bool
    -- ^ set the locale to C.UTF-8

    , EnvSettings -> Bool
esKeepGhcRts :: !Bool
    -- ^ if True, keep GHCRTS variable in environment

    }
    deriving (Int -> EnvSettings -> ShowS
[EnvSettings] -> ShowS
EnvSettings -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EnvSettings] -> ShowS
$cshowList :: [EnvSettings] -> ShowS
show :: EnvSettings -> [Char]
$cshow :: EnvSettings -> [Char]
showsPrec :: Int -> EnvSettings -> ShowS
$cshowsPrec :: Int -> EnvSettings -> ShowS
Show, EnvSettings -> EnvSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnvSettings -> EnvSettings -> Bool
$c/= :: EnvSettings -> EnvSettings -> Bool
== :: EnvSettings -> EnvSettings -> Bool
$c== :: EnvSettings -> EnvSettings -> Bool
Eq, Eq EnvSettings
EnvSettings -> EnvSettings -> Bool
EnvSettings -> EnvSettings -> Ordering
EnvSettings -> EnvSettings -> EnvSettings
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 :: EnvSettings -> EnvSettings -> EnvSettings
$cmin :: EnvSettings -> EnvSettings -> EnvSettings
max :: EnvSettings -> EnvSettings -> EnvSettings
$cmax :: EnvSettings -> EnvSettings -> EnvSettings
>= :: EnvSettings -> EnvSettings -> Bool
$c>= :: EnvSettings -> EnvSettings -> Bool
> :: EnvSettings -> EnvSettings -> Bool
$c> :: EnvSettings -> EnvSettings -> Bool
<= :: EnvSettings -> EnvSettings -> Bool
$c<= :: EnvSettings -> EnvSettings -> Bool
< :: EnvSettings -> EnvSettings -> Bool
$c< :: EnvSettings -> EnvSettings -> Bool
compare :: EnvSettings -> EnvSettings -> Ordering
$ccompare :: EnvSettings -> EnvSettings -> Ordering
Ord)

type AddCommand =
  ExceptT (RIO Runner ())
          (Writer (OA.Mod OA.CommandFields (RIO Runner (), GlobalOptsMonoid)))
          ()

data ExecOpts = ExecOpts
    { ExecOpts -> SpecialExecCmd
eoCmd :: !SpecialExecCmd
    , ExecOpts -> [[Char]]
eoArgs :: ![String]
    , ExecOpts -> ExecOptsExtra
eoExtra :: !ExecOptsExtra
    } deriving (Int -> ExecOpts -> ShowS
[ExecOpts] -> ShowS
ExecOpts -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ExecOpts] -> ShowS
$cshowList :: [ExecOpts] -> ShowS
show :: ExecOpts -> [Char]
$cshow :: ExecOpts -> [Char]
showsPrec :: Int -> ExecOpts -> ShowS
$cshowsPrec :: Int -> ExecOpts -> ShowS
Show)

data SpecialExecCmd
    = ExecCmd String
    | ExecRun
    | ExecGhc
    | ExecRunGhc
    deriving (Int -> SpecialExecCmd -> ShowS
[SpecialExecCmd] -> ShowS
SpecialExecCmd -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SpecialExecCmd] -> ShowS
$cshowList :: [SpecialExecCmd] -> ShowS
show :: SpecialExecCmd -> [Char]
$cshow :: SpecialExecCmd -> [Char]
showsPrec :: Int -> SpecialExecCmd -> ShowS
$cshowsPrec :: Int -> SpecialExecCmd -> ShowS
Show, SpecialExecCmd -> SpecialExecCmd -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecialExecCmd -> SpecialExecCmd -> Bool
$c/= :: SpecialExecCmd -> SpecialExecCmd -> Bool
== :: SpecialExecCmd -> SpecialExecCmd -> Bool
$c== :: SpecialExecCmd -> SpecialExecCmd -> Bool
Eq)

data ExecOptsExtra = ExecOptsExtra
  { ExecOptsExtra -> EnvSettings
eoEnvSettings :: !EnvSettings
  , ExecOptsExtra -> [[Char]]
eoPackages :: ![String]
  , ExecOptsExtra -> [[Char]]
eoRtsOptions :: ![String]
  , ExecOptsExtra -> Maybe [Char]
eoCwd :: !(Maybe FilePath)
  }
  deriving (Int -> ExecOptsExtra -> ShowS
[ExecOptsExtra] -> ShowS
ExecOptsExtra -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ExecOptsExtra] -> ShowS
$cshowList :: [ExecOptsExtra] -> ShowS
show :: ExecOptsExtra -> [Char]
$cshow :: ExecOptsExtra -> [Char]
showsPrec :: Int -> ExecOptsExtra -> ShowS
$cshowsPrec :: Int -> ExecOptsExtra -> ShowS
Show)

data EvalOpts = EvalOpts
    { EvalOpts -> [Char]
evalArg :: !String
    , EvalOpts -> ExecOptsExtra
evalExtra :: !ExecOptsExtra
    } deriving (Int -> EvalOpts -> ShowS
[EvalOpts] -> ShowS
EvalOpts -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EvalOpts] -> ShowS
$cshowList :: [EvalOpts] -> ShowS
show :: EvalOpts -> [Char]
$cshow :: EvalOpts -> [Char]
showsPrec :: Int -> EvalOpts -> ShowS
$cshowsPrec :: Int -> EvalOpts -> ShowS
Show)

-- | Parsed global command-line options.

data GlobalOpts = GlobalOpts
    { GlobalOpts -> Maybe [Char]
globalReExecVersion :: !(Maybe String) -- ^ Expected re-exec in container version

    , GlobalOpts -> Maybe DockerEntrypoint
globalDockerEntrypoint :: !(Maybe DockerEntrypoint)
      -- ^ Data used when Stack is acting as a Docker entrypoint (internal use only)

    , GlobalOpts -> LogLevel
globalLogLevel     :: !LogLevel -- ^ Log level

    , GlobalOpts -> Bool
globalTimeInLog    :: !Bool -- ^ Whether to include timings in logs.

    , GlobalOpts -> Bool
globalRSLInLog     :: !Bool -- ^ Whether to include raw snapshot layer (RSL) in logs.

    , GlobalOpts -> ConfigMonoid
globalConfigMonoid :: !ConfigMonoid -- ^ Config monoid, for passing into 'loadConfig'

    , GlobalOpts -> Maybe AbstractResolver
globalResolver     :: !(Maybe AbstractResolver) -- ^ Resolver override

    , GlobalOpts -> Maybe WantedCompiler
globalCompiler     :: !(Maybe WantedCompiler) -- ^ Compiler override

    , GlobalOpts -> Bool
globalTerminal     :: !Bool -- ^ We're in a terminal?

    , GlobalOpts -> StylesUpdate
globalStylesUpdate :: !StylesUpdate -- ^ SGR (Ansi) codes for styles

    , GlobalOpts -> Maybe Int
globalTermWidth    :: !(Maybe Int) -- ^ Terminal width override

    , GlobalOpts -> StackYamlLoc
globalStackYaml    :: !StackYamlLoc -- ^ Override project stack.yaml

    , GlobalOpts -> LockFileBehavior
globalLockFileBehavior :: !LockFileBehavior
    } deriving (Int -> GlobalOpts -> ShowS
[GlobalOpts] -> ShowS
GlobalOpts -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GlobalOpts] -> ShowS
$cshowList :: [GlobalOpts] -> ShowS
show :: GlobalOpts -> [Char]
$cshow :: GlobalOpts -> [Char]
showsPrec :: Int -> GlobalOpts -> ShowS
$cshowsPrec :: Int -> GlobalOpts -> ShowS
Show)

rslInLogL :: HasRunner env => SimpleGetter env Bool
rslInLogL :: forall env. HasRunner env => SimpleGetter env Bool
rslInLogL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to GlobalOpts -> Bool
globalRSLInLog

-- | Location for the project's stack.yaml file.

data StackYamlLoc
    = SYLDefault
    -- ^ Use the standard parent-directory-checking logic

    | SYLOverride !(Path Abs File)
    -- ^ Use a specific stack.yaml file provided

    | SYLNoProject ![PackageIdentifierRevision]
    -- ^ Do not load up a project, just user configuration. Include

    -- the given extra dependencies with the resolver.

    | SYLGlobalProject
    -- ^ Do not look for a project configuration, and use the implicit global.

    deriving Int -> StackYamlLoc -> ShowS
[StackYamlLoc] -> ShowS
StackYamlLoc -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [StackYamlLoc] -> ShowS
$cshowList :: [StackYamlLoc] -> ShowS
show :: StackYamlLoc -> [Char]
$cshow :: StackYamlLoc -> [Char]
showsPrec :: Int -> StackYamlLoc -> ShowS
$cshowsPrec :: Int -> StackYamlLoc -> ShowS
Show

stackYamlLocL :: HasRunner env => Lens' env StackYamlLoc
stackYamlLocL :: forall env. HasRunner env => Lens' env StackYamlLoc
stackYamlLocL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GlobalOpts -> StackYamlLoc
globalStackYaml (\GlobalOpts
x StackYamlLoc
y -> GlobalOpts
x { globalStackYaml :: StackYamlLoc
globalStackYaml = StackYamlLoc
y })

-- | How to interact with lock files

data LockFileBehavior
  = LFBReadWrite
  -- ^ Read and write lock files

  | LFBReadOnly
  -- ^ Read lock files, but do not write them

  | LFBIgnore
  -- ^ Entirely ignore lock files

  | LFBErrorOnWrite
  -- ^ Error out on trying to write a lock file. This can be used to

  -- ensure that lock files in a repository already ensure

  -- reproducible builds.

  deriving (Int -> LockFileBehavior -> ShowS
[LockFileBehavior] -> ShowS
LockFileBehavior -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [LockFileBehavior] -> ShowS
$cshowList :: [LockFileBehavior] -> ShowS
show :: LockFileBehavior -> [Char]
$cshow :: LockFileBehavior -> [Char]
showsPrec :: Int -> LockFileBehavior -> ShowS
$cshowsPrec :: Int -> LockFileBehavior -> ShowS
Show, Int -> LockFileBehavior
LockFileBehavior -> Int
LockFileBehavior -> [LockFileBehavior]
LockFileBehavior -> LockFileBehavior
LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
LockFileBehavior
-> LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LockFileBehavior
-> LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
$cenumFromThenTo :: LockFileBehavior
-> LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
enumFromTo :: LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
$cenumFromTo :: LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
enumFromThen :: LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
$cenumFromThen :: LockFileBehavior -> LockFileBehavior -> [LockFileBehavior]
enumFrom :: LockFileBehavior -> [LockFileBehavior]
$cenumFrom :: LockFileBehavior -> [LockFileBehavior]
fromEnum :: LockFileBehavior -> Int
$cfromEnum :: LockFileBehavior -> Int
toEnum :: Int -> LockFileBehavior
$ctoEnum :: Int -> LockFileBehavior
pred :: LockFileBehavior -> LockFileBehavior
$cpred :: LockFileBehavior -> LockFileBehavior
succ :: LockFileBehavior -> LockFileBehavior
$csucc :: LockFileBehavior -> LockFileBehavior
Enum, LockFileBehavior
forall a. a -> a -> Bounded a
maxBound :: LockFileBehavior
$cmaxBound :: LockFileBehavior
minBound :: LockFileBehavior
$cminBound :: LockFileBehavior
Bounded)

lockFileBehaviorL :: HasRunner env => SimpleGetter env LockFileBehavior
lockFileBehaviorL :: forall env. HasRunner env => SimpleGetter env LockFileBehavior
lockFileBehaviorL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to GlobalOpts -> LockFileBehavior
globalLockFileBehavior

-- | Parser for 'LockFileBehavior'

readLockFileBehavior :: ReadM LockFileBehavior
readLockFileBehavior :: ReadM LockFileBehavior
readLockFileBehavior = do
  [Char]
s <- ReadM [Char]
OA.readerAsk
  case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup [Char]
s Map [Char] LockFileBehavior
m of
    Just LockFileBehavior
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure LockFileBehavior
x
    Maybe LockFileBehavior
Nothing -> forall a. [Char] -> ReadM a
OA.readerError forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid lock file behavior, valid options: " forall a. [a] -> [a] -> [a]
++
                                forall a. [a] -> [[a]] -> [a]
List.intercalate [Char]
", " (forall k a. Map k a -> [k]
Map.keys Map [Char] LockFileBehavior
m)
  where
    m :: Map [Char] LockFileBehavior
m = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\LockFileBehavior
x -> (forall {a}. IsString a => LockFileBehavior -> a
render LockFileBehavior
x, LockFileBehavior
x)) [forall a. Bounded a => a
minBound..forall a. Bounded a => a
maxBound]
    render :: LockFileBehavior -> a
render LockFileBehavior
LFBReadWrite = a
"read-write"
    render LockFileBehavior
LFBReadOnly = a
"read-only"
    render LockFileBehavior
LFBIgnore = a
"ignore"
    render LockFileBehavior
LFBErrorOnWrite = a
"error-on-write"

-- | Project configuration information. Not every run of Stack has a

-- true local project; see constructors below.

data ProjectConfig a
    = PCProject a
    -- ^ Normal run: we want a project, and have one. This comes from

    -- either 'SYLDefault' or 'SYLOverride'.

    | PCGlobalProject
    -- ^ No project was found when using 'SYLDefault'. Instead, use

    -- the implicit global.

    | PCNoProject ![PackageIdentifierRevision]
    -- ^ Use a no project run. This comes from 'SYLNoProject'.


-- | Parsed global command-line options monoid.

data GlobalOptsMonoid = GlobalOptsMonoid
    { GlobalOptsMonoid -> First [Char]
globalMonoidReExecVersion :: !(First String) -- ^ Expected re-exec in container version

    , GlobalOptsMonoid -> First DockerEntrypoint
globalMonoidDockerEntrypoint :: !(First DockerEntrypoint)
      -- ^ Data used when Stack is acting as a Docker entrypoint (internal use only)

    , GlobalOptsMonoid -> First LogLevel
globalMonoidLogLevel     :: !(First LogLevel) -- ^ Log level

    , GlobalOptsMonoid -> FirstTrue
globalMonoidTimeInLog    :: !FirstTrue -- ^ Whether to include timings in logs.

    , GlobalOptsMonoid -> FirstFalse
globalMonoidRSLInLog     :: !FirstFalse -- ^ Whether to include raw snapshot layer (RSL) in logs.

    , GlobalOptsMonoid -> ConfigMonoid
globalMonoidConfigMonoid :: !ConfigMonoid -- ^ Config monoid, for passing into 'loadConfig'

    , GlobalOptsMonoid -> First (Unresolved AbstractResolver)
globalMonoidResolver     :: !(First (Unresolved AbstractResolver)) -- ^ Resolver override

    , GlobalOptsMonoid -> First [Char]
globalMonoidResolverRoot :: !(First FilePath) -- ^ root directory for resolver relative path

    , GlobalOptsMonoid -> First WantedCompiler
globalMonoidCompiler     :: !(First WantedCompiler) -- ^ Compiler override

    , GlobalOptsMonoid -> First Bool
globalMonoidTerminal     :: !(First Bool) -- ^ We're in a terminal?

    , GlobalOptsMonoid -> StylesUpdate
globalMonoidStyles       :: !StylesUpdate -- ^ Stack's output styles

    , GlobalOptsMonoid -> First Int
globalMonoidTermWidth    :: !(First Int) -- ^ Terminal width override

    , GlobalOptsMonoid -> First [Char]
globalMonoidStackYaml    :: !(First FilePath) -- ^ Override project stack.yaml

    , GlobalOptsMonoid -> First LockFileBehavior
globalMonoidLockFileBehavior :: !(First LockFileBehavior) -- ^ See 'globalLockFileBehavior'

    } deriving forall x. Rep GlobalOptsMonoid x -> GlobalOptsMonoid
forall x. GlobalOptsMonoid -> Rep GlobalOptsMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GlobalOptsMonoid x -> GlobalOptsMonoid
$cfrom :: forall x. GlobalOptsMonoid -> Rep GlobalOptsMonoid x
Generic

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

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

-- | Default logging level should be something useful but not crazy.

defaultLogLevel :: LogLevel
defaultLogLevel :: LogLevel
defaultLogLevel = LogLevel
LevelInfo

readColorWhen :: ReadM ColorWhen
readColorWhen :: ReadM ColorWhen
readColorWhen = do
    [Char]
s <- ReadM [Char]
OA.readerAsk
    case [Char]
s of
        [Char]
"never" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorNever
        [Char]
"always" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorAlways
        [Char]
"auto" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ColorWhen
ColorAuto
        [Char]
_ -> forall a. [Char] -> ReadM a
OA.readerError [Char]
"Expected values of color option are 'never', 'always', or 'auto'."

readStyles :: ReadM StylesUpdate
readStyles :: ReadM StylesUpdate
readStyles = [Char] -> StylesUpdate
parseStylesUpdateFromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM [Char]
OA.readerAsk

-- | A superset of 'Config' adding information on how to build code. The reason

-- for this breakdown is because we will need some of the information from

-- 'Config' in order to determine the values here.

--

-- These are the components which know nothing about local configuration.

data BuildConfig = BuildConfig
    { BuildConfig -> Config
bcConfig     :: !Config
    , BuildConfig -> SMWanted
bcSMWanted :: !SMWanted
    , BuildConfig -> [Path Abs Dir]
bcExtraPackageDBs :: ![Path Abs Dir]
      -- ^ Extra package databases

    , BuildConfig -> Path Abs File
bcStackYaml  :: !(Path Abs File)
      -- ^ Location of the stack.yaml file.

      --

      -- Note: if the STACK_YAML environment variable is used, this may be

      -- different from projectRootL </> "stack.yaml" if a different file

      -- name is used.

    , BuildConfig -> ProjectStorage
bcProjectStorage :: !ProjectStorage
    -- ^ Database connection pool for project Stack database

    , BuildConfig -> Maybe Curator
bcCurator :: !(Maybe Curator)
    }

stackYamlL :: HasBuildConfig env => Lens' env (Path Abs File)
stackYamlL :: forall env. HasBuildConfig env => Lens' env (Path Abs File)
stackYamlL = forall env. HasBuildConfig env => Lens' env BuildConfig
buildConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BuildConfig -> Path Abs File
bcStackYaml (\BuildConfig
x Path Abs File
y -> BuildConfig
x { bcStackYaml :: Path Abs File
bcStackYaml = Path Abs File
y })

-- | Directory containing the project's stack.yaml file

projectRootL :: HasBuildConfig env => Getting r env (Path Abs Dir)
projectRootL :: forall env r. HasBuildConfig env => Getting r env (Path Abs Dir)
projectRootL = forall env. HasBuildConfig env => Lens' env (Path Abs File)
stackYamlLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to forall b t. Path b t -> Path b Dir
parent

-- | Configuration after the environment has been setup.

data EnvConfig = EnvConfig
    {EnvConfig -> BuildConfig
envConfigBuildConfig :: !BuildConfig
    ,EnvConfig -> BuildOptsCLI
envConfigBuildOptsCLI :: !BuildOptsCLI
    ,EnvConfig -> SourceMap
envConfigSourceMap :: !SourceMap
    ,EnvConfig -> SourceMapHash
envConfigSourceMapHash :: !SourceMapHash
    ,EnvConfig -> CompilerPaths
envConfigCompilerPaths :: !CompilerPaths
    }

ppGPD :: MonadIO m => ProjectPackage -> m GenericPackageDescription
ppGPD :: forall (m :: * -> *).
MonadIO m =>
ProjectPackage -> m GenericPackageDescription
ppGPD = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommonPackage -> IO GenericPackageDescription
cpGPD forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectPackage -> CommonPackage
ppCommon

-- | Root directory for the given 'ProjectPackage'

ppRoot :: ProjectPackage -> Path Abs Dir
ppRoot :: ProjectPackage -> Path Abs Dir
ppRoot = forall b t. Path b t -> Path b Dir
parent forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectPackage -> Path Abs File
ppCabalFP

-- | All components available in the given 'ProjectPackage'

ppComponents :: MonadIO m => ProjectPackage -> m (Set NamedComponent)
ppComponents :: forall (m :: * -> *).
MonadIO m =>
ProjectPackage -> m (Set NamedComponent)
ppComponents ProjectPackage
pp = do
  GenericPackageDescription
gpd <- forall (m :: * -> *).
MonadIO m =>
ProjectPackage -> m GenericPackageDescription
ppGPD ProjectPackage
pp
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ forall b a. b -> (a -> b) -> Maybe a -> b
maybe []  (forall a b. a -> b -> a
const [NamedComponent
CLib]) (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
C.condLibrary GenericPackageDescription
gpd)
    , (Text -> NamedComponent)
-> [UnqualComponentName] -> [NamedComponent]
go Text -> NamedComponent
CExe   (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
C.condExecutables GenericPackageDescription
gpd)
    , (Text -> NamedComponent)
-> [UnqualComponentName] -> [NamedComponent]
go Text -> NamedComponent
CTest  (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
C.condTestSuites GenericPackageDescription
gpd)
    , (Text -> NamedComponent)
-> [UnqualComponentName] -> [NamedComponent]
go Text -> NamedComponent
CBench (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
C.condBenchmarks GenericPackageDescription
gpd)
    ]
  where
    go :: (T.Text -> NamedComponent)
       -> [C.UnqualComponentName]
       -> [NamedComponent]
    go :: (Text -> NamedComponent)
-> [UnqualComponentName] -> [NamedComponent]
go Text -> NamedComponent
wrapper = forall a b. (a -> b) -> [a] -> [b]
map (Text -> NamedComponent
wrapper forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnqualComponentName -> [Char]
C.unUnqualComponentName)

-- | Version for the given 'ProjectPackage

ppVersion :: MonadIO m => ProjectPackage -> m Version
ppVersion :: forall (m :: * -> *). MonadIO m => ProjectPackage -> m Version
ppVersion = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GenericPackageDescription -> Version
gpdVersion forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadIO m =>
ProjectPackage -> m GenericPackageDescription
ppGPD

-- | A project is a collection of packages. We can have multiple stack.yaml

-- files, but only one of them may contain project information.

data Project = Project
    { Project -> Maybe [Char]
projectUserMsg :: !(Maybe String)
    -- ^ A warning message to display to the user when the auto generated

    -- config may have issues.

    , Project -> [RelFilePath]
projectPackages :: ![RelFilePath]
    -- ^ Packages which are actually part of the project (as opposed

    -- to dependencies).

    , Project -> [RawPackageLocation]
projectDependencies :: ![RawPackageLocation]
    -- ^ Dependencies defined within the stack.yaml file, to be

    -- applied on top of the snapshot.

    , Project -> Map PackageName (Map FlagName Bool)
projectFlags :: !(Map PackageName (Map FlagName Bool))
    -- ^ Flags to be applied on top of the snapshot flags.

    , Project -> RawSnapshotLocation
projectResolver :: !RawSnapshotLocation
    -- ^ How we resolve which @Snapshot@ to use

    , Project -> Maybe WantedCompiler
projectCompiler :: !(Maybe WantedCompiler)
    -- ^ Override the compiler in 'projectResolver'

    , Project -> [[Char]]
projectExtraPackageDBs :: ![FilePath]
    , Project -> Maybe Curator
projectCurator :: !(Maybe Curator)
    -- ^ Extra configuration intended exclusively for usage by the

    -- curator tool. In other words, this is /not/ part of the

    -- documented and exposed Stack API. SUBJECT TO CHANGE.

    , Project -> Set PackageName
projectDropPackages :: !(Set PackageName)
    -- ^ Packages to drop from the 'projectResolver'.

    }
  deriving Int -> Project -> ShowS
[Project] -> ShowS
Project -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Project] -> ShowS
$cshowList :: [Project] -> ShowS
show :: Project -> [Char]
$cshow :: Project -> [Char]
showsPrec :: Int -> Project -> ShowS
$cshowsPrec :: Int -> Project -> ShowS
Show

instance ToJSON Project where
    -- Expanding the constructor fully to ensure we don't miss any fields.

    toJSON :: Project -> Value
toJSON (Project Maybe [Char]
userMsg [RelFilePath]
packages [RawPackageLocation]
extraDeps Map PackageName (Map FlagName Bool)
flags RawSnapshotLocation
resolver Maybe WantedCompiler
mcompiler [[Char]]
extraPackageDBs Maybe Curator
mcurator Set PackageName
drops) = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
      [ forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\WantedCompiler
cv -> [Key
"compiler" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= WantedCompiler
cv]) Maybe WantedCompiler
mcompiler
      , forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\[Char]
msg -> [Key
"user-message" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Char]
msg]) Maybe [Char]
userMsg
      , if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Char]]
extraPackageDBs then [] else [Key
"extra-package-dbs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [[Char]]
extraPackageDBs]
      , if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RawPackageLocation]
extraDeps then [] else [Key
"extra-deps" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [RawPackageLocation]
extraDeps]
      , if forall k a. Map k a -> Bool
Map.null Map PackageName (Map FlagName Bool)
flags then [] else [Key
"flags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a v. Map a v -> Map (CabalString a) v
toCabalStringMap (forall a v. Map a v -> Map (CabalString a) v
toCabalStringMap Map PackageName (Map FlagName Bool)
flags)]
      , [Key
"packages" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [RelFilePath]
packages]
      , [Key
"resolver" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RawSnapshotLocation
resolver]
      , forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Curator
c -> [Key
"curator" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Curator
c]) Maybe Curator
mcurator
      , if forall a. Set a -> Bool
Set.null Set PackageName
drops then [] else [Key
"drop-packages" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString Set PackageName
drops]
      ]

-- | Extra configuration intended exclusively for usage by the

-- curator tool. In other words, this is /not/ part of the

-- documented and exposed Stack API. SUBJECT TO CHANGE.

data Curator = Curator
  { Curator -> Set PackageName
curatorSkipTest :: !(Set PackageName)
  , Curator -> Set PackageName
curatorExpectTestFailure :: !(Set PackageName)
  , Curator -> Set PackageName
curatorSkipBenchmark :: !(Set PackageName)
  , Curator -> Set PackageName
curatorExpectBenchmarkFailure :: !(Set PackageName)
  , Curator -> Set PackageName
curatorSkipHaddock :: !(Set PackageName)
  , Curator -> Set PackageName
curatorExpectHaddockFailure :: !(Set PackageName)
  }
  deriving Int -> Curator -> ShowS
[Curator] -> ShowS
Curator -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Curator] -> ShowS
$cshowList :: [Curator] -> ShowS
show :: Curator -> [Char]
$cshow :: Curator -> [Char]
showsPrec :: Int -> Curator -> ShowS
$cshowsPrec :: Int -> Curator -> ShowS
Show
instance ToJSON Curator where
  toJSON :: Curator -> Value
toJSON Curator
c = [Pair] -> Value
object
    [ Key
"skip-test" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorSkipTest Curator
c)
    , Key
"expect-test-failure" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorExpectTestFailure Curator
c)
    , Key
"skip-bench" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorSkipBenchmark Curator
c)
    , Key
"expect-benchmark-failure" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorExpectTestFailure Curator
c)
    , Key
"skip-haddock" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorSkipHaddock Curator
c)
    , Key
"expect-test-failure" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. a -> CabalString a
CabalString (Curator -> Set PackageName
curatorExpectHaddockFailure Curator
c)
    ]
instance FromJSON (WithJSONWarnings Curator) where
  parseJSON :: Value -> Parser (WithJSONWarnings Curator)
parseJSON = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"Curator" forall a b. (a -> b) -> a -> b
$ \Object
o -> Set PackageName
-> Set PackageName
-> Set PackageName
-> Set PackageName
-> Set PackageName
-> Set PackageName
-> Curator
Curator
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"skip-test" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"expect-test-failure" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"skip-bench" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"expect-benchmark-failure" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"skip-haddock" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString) (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"expect-haddock-failure" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)

-- An uninterpreted representation of configuration options.

-- Configurations may be "cascaded" using mappend (left-biased).

data ConfigMonoid =
  ConfigMonoid
    { ConfigMonoid -> First (Path Abs Dir)
configMonoidStackRoot          :: !(First (Path Abs Dir))
    -- ^ See: 'clStackRoot'

    , ConfigMonoid -> First (Path Rel Dir)
configMonoidWorkDir            :: !(First (Path Rel Dir))
    -- ^ See: 'configWorkDir'.

    , ConfigMonoid -> BuildOptsMonoid
configMonoidBuildOpts          :: !BuildOptsMonoid
    -- ^ build options.

    , ConfigMonoid -> DockerOptsMonoid
configMonoidDockerOpts         :: !DockerOptsMonoid
    -- ^ Docker options.

    , ConfigMonoid -> NixOptsMonoid
configMonoidNixOpts            :: !NixOptsMonoid
    -- ^ Options for the execution environment (nix-shell or container)

    , ConfigMonoid -> First Int
configMonoidConnectionCount    :: !(First Int)
    -- ^ See: 'configConnectionCount'

    , ConfigMonoid -> FirstTrue
configMonoidHideTHLoading      :: !FirstTrue
    -- ^ See: 'configHideTHLoading'

    , ConfigMonoid -> First Bool
configMonoidPrefixTimestamps   :: !(First Bool)
    -- ^ See: 'configPrefixTimestamps'

    , ConfigMonoid -> First Text
configMonoidLatestSnapshot     :: !(First Text)
    -- ^ See: 'configLatestSnapshot'

    , ConfigMonoid -> First PackageIndexConfig
configMonoidPackageIndex     :: !(First PackageIndexConfig)
    -- ^ See: 'withPantryConfig'

    , ConfigMonoid -> First [PackageIndexConfig]
configMonoidPackageIndices     :: !(First [PackageIndexConfig])
    -- ^ Deprecated in favour of package-index

    , ConfigMonoid -> First Bool
configMonoidSystemGHC          :: !(First Bool)
    -- ^ See: 'configSystemGHC'

    ,ConfigMonoid -> FirstTrue
configMonoidInstallGHC          :: !FirstTrue
    -- ^ See: 'configInstallGHC'

    ,ConfigMonoid -> FirstFalse
configMonoidSkipGHCCheck        :: !FirstFalse
    -- ^ See: 'configSkipGHCCheck'

    ,ConfigMonoid -> FirstFalse
configMonoidSkipMsys            :: !FirstFalse
    -- ^ See: 'configSkipMsys'

    ,ConfigMonoid -> First VersionCheck
configMonoidCompilerCheck       :: !(First VersionCheck)
    -- ^ See: 'configCompilerCheck'

    ,ConfigMonoid -> First CompilerRepository
configMonoidCompilerRepository  :: !(First CompilerRepository)
    -- ^ See: 'configCompilerRepository'

    ,ConfigMonoid -> IntersectingVersionRange
configMonoidRequireStackVersion :: !IntersectingVersionRange
    -- ^ See: 'configRequireStackVersion'

    ,ConfigMonoid -> First [Char]
configMonoidArch                :: !(First String)
    -- ^ Used for overriding the platform

    ,ConfigMonoid -> First GHCVariant
configMonoidGHCVariant          :: !(First GHCVariant)
    -- ^ Used for overriding the platform

    ,ConfigMonoid -> First CompilerBuild
configMonoidGHCBuild            :: !(First CompilerBuild)
    -- ^ Used for overriding the GHC build

    ,ConfigMonoid -> First Int
configMonoidJobs                :: !(First Int)
    -- ^ See: 'configJobs'

    ,ConfigMonoid -> [[Char]]
configMonoidExtraIncludeDirs    :: ![FilePath]
    -- ^ See: 'configExtraIncludeDirs'

    ,ConfigMonoid -> [[Char]]
configMonoidExtraLibDirs        :: ![FilePath]
    -- ^ See: 'configExtraLibDirs'

    ,ConfigMonoid -> [Text]
configMonoidCustomPreprocessorExts :: ![Text]
    -- ^ See: 'configCustomPreprocessorExts'

    , ConfigMonoid -> First (Path Abs File)
configMonoidOverrideGccPath    :: !(First (Path Abs File))
    -- ^ Allow users to override the path to gcc

    ,ConfigMonoid -> First [Char]
configMonoidOverrideHpack       :: !(First FilePath)
    -- ^ Use Hpack executable (overrides bundled Hpack)

    ,ConfigMonoid -> First Bool
configMonoidConcurrentTests     :: !(First Bool)
    -- ^ See: 'configConcurrentTests'

    ,ConfigMonoid -> First [Char]
configMonoidLocalBinPath        :: !(First FilePath)
    -- ^ Used to override the binary installation dir

    ,ConfigMonoid -> Map Text Text
configMonoidTemplateParameters  :: !(Map Text Text)
    -- ^ Template parameters.

    ,ConfigMonoid -> First SCM
configMonoidScmInit             :: !(First SCM)
    -- ^ Initialize SCM (e.g. git init) when making new projects?

    ,ConfigMonoid -> MonoidMap PackageName (Dual [Text])
configMonoidGhcOptionsByName    :: !(MonoidMap PackageName (Monoid.Dual [Text]))
    -- ^ See 'configGhcOptionsByName'. Uses 'Monoid.Dual' so that

    -- options from the configs on the right come first, so that they

    -- can be overridden.

    ,ConfigMonoid -> MonoidMap ApplyGhcOptions (Dual [Text])
configMonoidGhcOptionsByCat     :: !(MonoidMap ApplyGhcOptions (Monoid.Dual [Text]))
    -- ^ See 'configGhcOptionsAll'. Uses 'Monoid.Dual' so that options

    -- from the configs on the right come first, so that they can be

    -- overridden.

    ,ConfigMonoid -> MonoidMap CabalConfigKey (Dual [Text])
configMonoidCabalConfigOpts     :: !(MonoidMap CabalConfigKey (Monoid.Dual [Text]))
    -- ^ See 'configCabalConfigOpts'.

    ,ConfigMonoid -> [Path Abs Dir]
configMonoidExtraPath           :: ![Path Abs Dir]
    -- ^ Additional paths to search for executables in

    ,ConfigMonoid -> [[Char]]
configMonoidSetupInfoLocations  :: ![String]
    -- ^ See 'configSetupInfoLocations'

    ,ConfigMonoid -> SetupInfo
configMonoidSetupInfoInline     :: !SetupInfo
    -- ^ See 'configSetupInfoInline'

    ,ConfigMonoid -> First (Path Abs Dir)
configMonoidLocalProgramsBase   :: !(First (Path Abs Dir))
    -- ^ Override the default local programs dir, where e.g. GHC is installed.

    ,ConfigMonoid -> First PvpBounds
configMonoidPvpBounds           :: !(First PvpBounds)
    -- ^ See 'configPvpBounds'

    ,ConfigMonoid -> FirstTrue
configMonoidModifyCodePage      :: !FirstTrue
    -- ^ See 'configModifyCodePage'

    ,ConfigMonoid -> FirstFalse
configMonoidRebuildGhcOptions   :: !FirstFalse
    -- ^ See 'configMonoidRebuildGhcOptions'

    ,ConfigMonoid -> First ApplyGhcOptions
configMonoidApplyGhcOptions     :: !(First ApplyGhcOptions)
    -- ^ See 'configApplyGhcOptions'

    ,ConfigMonoid -> First Bool
configMonoidAllowNewer          :: !(First Bool)
    -- ^ See 'configMonoidAllowNewer'

    ,ConfigMonoid -> Maybe AllowNewerDeps
configMonoidAllowNewerDeps      :: !(Maybe AllowNewerDeps)
    -- ^ See 'configMonoidAllowNewerDeps'

    ,ConfigMonoid -> First TemplateName
configMonoidDefaultTemplate     :: !(First TemplateName)
    -- ^ The default template to use when none is specified.

    -- (If Nothing, the 'default' default template is used.)

    , ConfigMonoid -> First Bool
configMonoidAllowDifferentUser :: !(First Bool)
    -- ^ Allow users other than the Stack root owner to use the Stack

    -- installation.

    , ConfigMonoid -> First DumpLogs
configMonoidDumpLogs           :: !(First DumpLogs)
    -- ^ See 'configDumpLogs'

    , ConfigMonoid -> First Bool
configMonoidSaveHackageCreds   :: !(First Bool)
    -- ^ See 'configSaveHackageCreds'

    , ConfigMonoid -> First Text
configMonoidHackageBaseUrl     :: !(First Text)
    -- ^ See 'configHackageBaseUrl'

    , ConfigMonoid -> First ColorWhen
configMonoidColorWhen          :: !(First ColorWhen)
    -- ^ When to use 'ANSI' colors

    , ConfigMonoid -> StylesUpdate
configMonoidStyles             :: !StylesUpdate
    , ConfigMonoid -> FirstTrue
configMonoidHideSourcePaths    :: !FirstTrue
    -- ^ See 'configHideSourcePaths'

    , ConfigMonoid -> FirstTrue
configMonoidRecommendUpgrade   :: !FirstTrue
    -- ^ See 'configRecommendUpgrade'

    , ConfigMonoid -> First CasaRepoPrefix
configMonoidCasaRepoPrefix     :: !(First CasaRepoPrefix)
    , ConfigMonoid -> First Text
configMonoidSnapshotLocation :: !(First Text)
    -- ^ Custom location of LTS/Nightly snapshots

    , ConfigMonoid -> FirstFalse
configMonoidNoRunCompile  :: !FirstFalse
    -- ^ See: 'configNoRunCompile'

    , ConfigMonoid -> First Bool
configMonoidStackDeveloperMode :: !(First Bool)
    -- ^ See 'configStackDeveloperMode'

    }
  deriving (Int -> ConfigMonoid -> ShowS
[ConfigMonoid] -> ShowS
ConfigMonoid -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ConfigMonoid] -> ShowS
$cshowList :: [ConfigMonoid] -> ShowS
show :: ConfigMonoid -> [Char]
$cshow :: ConfigMonoid -> [Char]
showsPrec :: Int -> ConfigMonoid -> ShowS
$cshowsPrec :: Int -> ConfigMonoid -> ShowS
Show, forall x. Rep ConfigMonoid x -> ConfigMonoid
forall x. ConfigMonoid -> Rep ConfigMonoid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConfigMonoid x -> ConfigMonoid
$cfrom :: forall x. ConfigMonoid -> Rep ConfigMonoid x
Generic)

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

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

parseConfigMonoid :: Path Abs Dir -> Value -> Yaml.Parser (WithJSONWarnings ConfigMonoid)
parseConfigMonoid :: Path Abs Dir -> Value -> Parser (WithJSONWarnings ConfigMonoid)
parseConfigMonoid = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"ConfigMonoid" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Abs Dir -> Object -> WarningParser ConfigMonoid
parseConfigMonoidObject

-- | Parse a partial configuration.  Used both to parse both a standalone config

-- file and a project file, so that a sub-parser is not required, which would interfere with

-- warnings for missing fields.

parseConfigMonoidObject :: Path Abs Dir -> Object -> WarningParser ConfigMonoid
parseConfigMonoidObject :: Path Abs Dir -> Object -> WarningParser ConfigMonoid
parseConfigMonoidObject Path Abs Dir
rootDir Object
obj = do
    -- Parsing 'stackRoot' from 'stackRoot'/config.yaml would be nonsensical

    let configMonoidStackRoot :: First a
configMonoidStackRoot = forall a. Maybe a -> First a
First forall a. Maybe a
Nothing
    First (Path Rel Dir)
configMonoidWorkDir <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidWorkDirName
    BuildOptsMonoid
configMonoidBuildOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidBuildOptsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    DockerOptsMonoid
configMonoidDockerOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidDockerOptsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    NixOptsMonoid
configMonoidNixOpts <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidNixOptsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
    First Int
configMonoidConnectionCount <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidConnectionCountName
    FirstTrue
configMonoidHideTHLoading <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidHideTHLoadingName
    First Bool
configMonoidPrefixTimestamps <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidPrefixTimestampsName

    Maybe Value
murls :: Maybe Value <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidUrlsName
    First Text
configMonoidLatestSnapshot <-
      case Maybe Value
murls of
        Maybe Value
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> First a
First forall a. Maybe a
Nothing
        Just Value
urls -> forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings
          [Char]
"urls"
          (\Object
o -> 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
"latest-snapshot" :: WarningParser (First Text))
          Value
urls

    First PackageIndexConfig
configMonoidPackageIndex <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:?  Text
configMonoidPackageIndexName)
    First [PackageIndexConfig]
configMonoidPackageIndices <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (u :: * -> *) a.
(Traversable t, Traversable u) =>
WarningParser (u (t (WithJSONWarnings a)))
-> WarningParser (u (t a))
jsonSubWarningsTT (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:?  Text
configMonoidPackageIndicesName)
    First Bool
configMonoidSystemGHC <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSystemGHCName
    FirstTrue
configMonoidInstallGHC <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidInstallGHCName
    FirstFalse
configMonoidSkipGHCCheck <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSkipGHCCheckName
    FirstFalse
configMonoidSkipMsys <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSkipMsysName
    IntersectingVersionRange
configMonoidRequireStackVersion <- VersionRange -> IntersectingVersionRange
IntersectingVersionRange forall b c a. (b -> c) -> (a -> b) -> a -> c
. VersionRangeJSON -> VersionRange
unVersionRangeJSON forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (
                                       Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidRequireStackVersionName
                                           forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= VersionRange -> VersionRangeJSON
VersionRangeJSON VersionRange
anyVersion)
    First [Char]
configMonoidArch <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidArchName
    First GHCVariant
configMonoidGHCVariant <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidGHCVariantName
    First CompilerBuild
configMonoidGHCBuild <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidGHCBuildName
    First Int
configMonoidJobs <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidJobsName
    [[Char]]
configMonoidExtraIncludeDirs <- forall a b. (a -> b) -> [a] -> [b]
map (forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
rootDir [Char] -> ShowS
FilePath.</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:?  Text
configMonoidExtraIncludeDirsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
    [[Char]]
configMonoidExtraLibDirs <- forall a b. (a -> b) -> [a] -> [b]
map (forall b t. Path b t -> [Char]
toFilePath Path Abs Dir
rootDir [Char] -> ShowS
FilePath.</>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:?  Text
configMonoidExtraLibDirsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
    [Text]
configMonoidCustomPreprocessorExts <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:?  Text
configMonoidCustomPreprocessorExtsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
    First (Path Abs File)
configMonoidOverrideGccPath <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidOverrideGccPathName
    First [Char]
configMonoidOverrideHpack <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidOverrideHpackName
    First Bool
configMonoidConcurrentTests <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidConcurrentTestsName
    First [Char]
configMonoidLocalBinPath <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidLocalBinPathName
    Maybe Object
templates <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"templates"
    (First SCM
configMonoidScmInit,Map Text Text
configMonoidTemplateParameters) <-
      case Maybe Object
templates of
        Maybe Object
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Maybe a -> First a
First forall a. Maybe a
Nothing,forall k a. Map k a
M.empty)
        Just Object
tobj -> do
          Maybe SCM
scmInit <- Object
tobj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidScmInitName
          Maybe (Map Text Text)
params <- Object
tobj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidTemplateParametersName
          forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Maybe a -> First a
First Maybe SCM
scmInit,forall a. a -> Maybe a -> a
fromMaybe forall k a. Map k a
M.empty Maybe (Map Text Text)
params)
    First VersionCheck
configMonoidCompilerCheck <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidCompilerCheckName
    First CompilerRepository
configMonoidCompilerRepository <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidCompilerRepositoryName)

    Map GhcOptionKey [Text]
options <- forall a b k. (a -> b) -> Map k a -> Map k b
Map.map GhcOptions -> [Text]
unGhcOptions forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidGhcOptionsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty

    [Text]
optionsEverything <-
      case (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup GhcOptionKey
GOKOldEverything Map GhcOptionKey [Text]
options, forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup GhcOptionKey
GOKEverything Map GhcOptionKey [Text]
options) of
        (Just [Text]
_, Just [Text]
_) -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"Cannot specify both `*` and `$everything` GHC options"
        (Maybe [Text]
Nothing, Just [Text]
x) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [Text]
x
        (Just [Text]
x, Maybe [Text]
Nothing) -> do
          forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell WarningParserMonoid
"The `*` ghc-options key is not recommended. Consider using $locals, or if really needed, $everything"
          forall (f :: * -> *) a. Applicative f => a -> f a
pure [Text]
x
        (Maybe [Text]
Nothing, Maybe [Text]
Nothing) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure []

    let configMonoidGhcOptionsByCat :: MonoidMap ApplyGhcOptions (Dual [Text])
configMonoidGhcOptionsByCat = coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
          [ (ApplyGhcOptions
AGOEverything, [Text]
optionsEverything)
          , (ApplyGhcOptions
AGOLocals, forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault [] GhcOptionKey
GOKLocals Map GhcOptionKey [Text]
options)
          , (ApplyGhcOptions
AGOTargets, forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault [] GhcOptionKey
GOKTargets Map GhcOptionKey [Text]
options)
          ]

        configMonoidGhcOptionsByName :: MonoidMap PackageName (Dual [Text])
configMonoidGhcOptionsByName = coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
            [(PackageName
name, [Text]
opts) | (GOKPackage PackageName
name, [Text]
opts) <- forall k a. Map k a -> [(k, a)]
Map.toList Map GhcOptionKey [Text]
options]

    Map CabalConfigKey [Text]
configMonoidCabalConfigOpts' <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"configure-options" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
    let configMonoidCabalConfigOpts :: MonoidMap CabalConfigKey (Dual [Text])
configMonoidCabalConfigOpts = coerce :: forall a b. Coercible a b => a -> b
coerce (Map CabalConfigKey [Text]
configMonoidCabalConfigOpts' :: Map CabalConfigKey [Text])

    [Path Abs Dir]
configMonoidExtraPath <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidExtraPathName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
    [[Char]]
configMonoidSetupInfoLocations <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSetupInfoLocationsName forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
    SetupInfo
configMonoidSetupInfoInline <- forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSetupInfoInlineName) forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
    First (Path Abs Dir)
configMonoidLocalProgramsBase <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidLocalProgramsBaseName
    First PvpBounds
configMonoidPvpBounds <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidPvpBoundsName
    FirstTrue
configMonoidModifyCodePage <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidModifyCodePageName
    FirstFalse
configMonoidRebuildGhcOptions <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidRebuildGhcOptionsName
    First ApplyGhcOptions
configMonoidApplyGhcOptions <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidApplyGhcOptionsName
    First Bool
configMonoidAllowNewer <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidAllowNewerName
    Maybe AllowNewerDeps
configMonoidAllowNewerDeps <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidAllowNewerDepsName
    First TemplateName
configMonoidDefaultTemplate <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidDefaultTemplateName
    First Bool
configMonoidAllowDifferentUser <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidAllowDifferentUserName
    First DumpLogs
configMonoidDumpLogs <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidDumpLogsName
    First Bool
configMonoidSaveHackageCreds <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSaveHackageCredsName
    First Text
configMonoidHackageBaseUrl <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidHackageBaseUrlName

    Maybe ColorWhen
configMonoidColorWhenUS <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidColorWhenUSName
    Maybe ColorWhen
configMonoidColorWhenGB <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidColorWhenGBName
    let configMonoidColorWhen :: First ColorWhen
configMonoidColorWhen =  forall a. Maybe a -> First a
First forall a b. (a -> b) -> a -> b
$   Maybe ColorWhen
configMonoidColorWhenUS
                                       forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe ColorWhen
configMonoidColorWhenGB

    Maybe StylesUpdate
configMonoidStylesUS <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidStylesUSName
    Maybe StylesUpdate
configMonoidStylesGB <- Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidStylesGBName
    let configMonoidStyles :: StylesUpdate
configMonoidStyles = forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall a b. (a -> b) -> a -> b
$   Maybe StylesUpdate
configMonoidStylesUS
                                              forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe StylesUpdate
configMonoidStylesGB

    FirstTrue
configMonoidHideSourcePaths <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidHideSourcePathsName
    FirstTrue
configMonoidRecommendUpgrade <- Maybe Bool -> FirstTrue
FirstTrue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidRecommendUpgradeName

    First CasaRepoPrefix
configMonoidCasaRepoPrefix <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidCasaRepoPrefixName
    First Text
configMonoidSnapshotLocation <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidSnapshotLocationName
    FirstFalse
configMonoidNoRunCompile <- Maybe Bool -> FirstFalse
FirstFalse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidNoRunCompileName

    First Bool
configMonoidStackDeveloperMode <- forall a. Maybe a -> First a
First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
configMonoidStackDeveloperModeName

    forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfigMonoid {[[Char]]
[Text]
[Path Abs Dir]
Maybe AllowNewerDeps
Map Text Text
First Bool
First Int
First [Char]
First [PackageIndexConfig]
First Text
First CasaRepoPrefix
First PackageIndexConfig
First (Path Abs File)
First (Path Abs Dir)
First (Path Rel Dir)
First CompilerBuild
First TemplateName
First VersionCheck
First CompilerRepository
First PvpBounds
First GHCVariant
First SCM
First DumpLogs
First ApplyGhcOptions
First ColorWhen
StylesUpdate
FirstFalse
FirstTrue
MonoidMap PackageName (Dual [Text])
MonoidMap ApplyGhcOptions (Dual [Text])
MonoidMap CabalConfigKey (Dual [Text])
BuildOptsMonoid
NixOptsMonoid
IntersectingVersionRange
DockerOptsMonoid
SetupInfo
forall {a}. First a
configMonoidStackDeveloperMode :: First Bool
configMonoidNoRunCompile :: FirstFalse
configMonoidSnapshotLocation :: First Text
configMonoidCasaRepoPrefix :: First CasaRepoPrefix
configMonoidRecommendUpgrade :: FirstTrue
configMonoidHideSourcePaths :: FirstTrue
configMonoidStyles :: StylesUpdate
configMonoidColorWhen :: First ColorWhen
configMonoidHackageBaseUrl :: First Text
configMonoidSaveHackageCreds :: First Bool
configMonoidDumpLogs :: First DumpLogs
configMonoidAllowDifferentUser :: First Bool
configMonoidDefaultTemplate :: First TemplateName
configMonoidAllowNewerDeps :: Maybe AllowNewerDeps
configMonoidAllowNewer :: First Bool
configMonoidApplyGhcOptions :: First ApplyGhcOptions
configMonoidRebuildGhcOptions :: FirstFalse
configMonoidModifyCodePage :: FirstTrue
configMonoidPvpBounds :: First PvpBounds
configMonoidLocalProgramsBase :: First (Path Abs Dir)
configMonoidSetupInfoInline :: SetupInfo
configMonoidSetupInfoLocations :: [[Char]]
configMonoidExtraPath :: [Path Abs Dir]
configMonoidCabalConfigOpts :: MonoidMap CabalConfigKey (Dual [Text])
configMonoidGhcOptionsByName :: MonoidMap PackageName (Dual [Text])
configMonoidGhcOptionsByCat :: MonoidMap ApplyGhcOptions (Dual [Text])
configMonoidCompilerRepository :: First CompilerRepository
configMonoidCompilerCheck :: First VersionCheck
configMonoidTemplateParameters :: Map Text Text
configMonoidScmInit :: First SCM
configMonoidLocalBinPath :: First [Char]
configMonoidConcurrentTests :: First Bool
configMonoidOverrideHpack :: First [Char]
configMonoidOverrideGccPath :: First (Path Abs File)
configMonoidCustomPreprocessorExts :: [Text]
configMonoidExtraLibDirs :: [[Char]]
configMonoidExtraIncludeDirs :: [[Char]]
configMonoidJobs :: First Int
configMonoidGHCBuild :: First CompilerBuild
configMonoidGHCVariant :: First GHCVariant
configMonoidArch :: First [Char]
configMonoidRequireStackVersion :: IntersectingVersionRange
configMonoidSkipMsys :: FirstFalse
configMonoidSkipGHCCheck :: FirstFalse
configMonoidInstallGHC :: FirstTrue
configMonoidSystemGHC :: First Bool
configMonoidPackageIndices :: First [PackageIndexConfig]
configMonoidPackageIndex :: First PackageIndexConfig
configMonoidLatestSnapshot :: First Text
configMonoidPrefixTimestamps :: First Bool
configMonoidHideTHLoading :: FirstTrue
configMonoidConnectionCount :: First Int
configMonoidNixOpts :: NixOptsMonoid
configMonoidDockerOpts :: DockerOptsMonoid
configMonoidBuildOpts :: BuildOptsMonoid
configMonoidWorkDir :: First (Path Rel Dir)
configMonoidStackRoot :: forall {a}. First a
configMonoidStackDeveloperMode :: First Bool
configMonoidNoRunCompile :: FirstFalse
configMonoidSnapshotLocation :: First Text
configMonoidCasaRepoPrefix :: First CasaRepoPrefix
configMonoidRecommendUpgrade :: FirstTrue
configMonoidHideSourcePaths :: FirstTrue
configMonoidStyles :: StylesUpdate
configMonoidColorWhen :: First ColorWhen
configMonoidHackageBaseUrl :: First Text
configMonoidSaveHackageCreds :: First Bool
configMonoidDumpLogs :: First DumpLogs
configMonoidAllowDifferentUser :: First Bool
configMonoidDefaultTemplate :: First TemplateName
configMonoidAllowNewerDeps :: Maybe AllowNewerDeps
configMonoidAllowNewer :: First Bool
configMonoidApplyGhcOptions :: First ApplyGhcOptions
configMonoidRebuildGhcOptions :: FirstFalse
configMonoidModifyCodePage :: FirstTrue
configMonoidPvpBounds :: First PvpBounds
configMonoidLocalProgramsBase :: First (Path Abs Dir)
configMonoidSetupInfoInline :: SetupInfo
configMonoidSetupInfoLocations :: [[Char]]
configMonoidExtraPath :: [Path Abs Dir]
configMonoidCabalConfigOpts :: MonoidMap CabalConfigKey (Dual [Text])
configMonoidGhcOptionsByCat :: MonoidMap ApplyGhcOptions (Dual [Text])
configMonoidGhcOptionsByName :: MonoidMap PackageName (Dual [Text])
configMonoidScmInit :: First SCM
configMonoidTemplateParameters :: Map Text Text
configMonoidLocalBinPath :: First [Char]
configMonoidConcurrentTests :: First Bool
configMonoidOverrideHpack :: First [Char]
configMonoidOverrideGccPath :: First (Path Abs File)
configMonoidCustomPreprocessorExts :: [Text]
configMonoidExtraLibDirs :: [[Char]]
configMonoidExtraIncludeDirs :: [[Char]]
configMonoidJobs :: First Int
configMonoidGHCBuild :: First CompilerBuild
configMonoidGHCVariant :: First GHCVariant
configMonoidArch :: First [Char]
configMonoidRequireStackVersion :: IntersectingVersionRange
configMonoidCompilerRepository :: First CompilerRepository
configMonoidCompilerCheck :: First VersionCheck
configMonoidSkipMsys :: FirstFalse
configMonoidSkipGHCCheck :: FirstFalse
configMonoidInstallGHC :: FirstTrue
configMonoidSystemGHC :: First Bool
configMonoidPackageIndices :: First [PackageIndexConfig]
configMonoidPackageIndex :: First PackageIndexConfig
configMonoidLatestSnapshot :: First Text
configMonoidPrefixTimestamps :: First Bool
configMonoidHideTHLoading :: FirstTrue
configMonoidConnectionCount :: First Int
configMonoidNixOpts :: NixOptsMonoid
configMonoidDockerOpts :: DockerOptsMonoid
configMonoidBuildOpts :: BuildOptsMonoid
configMonoidWorkDir :: First (Path Rel Dir)
configMonoidStackRoot :: First (Path Abs Dir)
..}

configMonoidWorkDirName :: Text
configMonoidWorkDirName :: Text
configMonoidWorkDirName = Text
"work-dir"

configMonoidBuildOptsName :: Text
configMonoidBuildOptsName :: Text
configMonoidBuildOptsName = Text
"build"

configMonoidDockerOptsName :: Text
configMonoidDockerOptsName :: Text
configMonoidDockerOptsName = Text
"docker"

configMonoidNixOptsName :: Text
configMonoidNixOptsName :: Text
configMonoidNixOptsName = Text
"nix"

configMonoidConnectionCountName :: Text
configMonoidConnectionCountName :: Text
configMonoidConnectionCountName = Text
"connection-count"

configMonoidHideTHLoadingName :: Text
configMonoidHideTHLoadingName :: Text
configMonoidHideTHLoadingName = Text
"hide-th-loading"

configMonoidPrefixTimestampsName :: Text
configMonoidPrefixTimestampsName :: Text
configMonoidPrefixTimestampsName = Text
"build-output-timestamps"

configMonoidUrlsName :: Text
configMonoidUrlsName :: Text
configMonoidUrlsName = Text
"urls"

configMonoidPackageIndexName :: Text
configMonoidPackageIndexName :: Text
configMonoidPackageIndexName = Text
"package-index"

-- Deprecated in favour of package-index

configMonoidPackageIndicesName :: Text
configMonoidPackageIndicesName :: Text
configMonoidPackageIndicesName = Text
"package-indices"

configMonoidSystemGHCName :: Text
configMonoidSystemGHCName :: Text
configMonoidSystemGHCName = Text
"system-ghc"

configMonoidInstallGHCName :: Text
configMonoidInstallGHCName :: Text
configMonoidInstallGHCName = Text
"install-ghc"

configMonoidSkipGHCCheckName :: Text
configMonoidSkipGHCCheckName :: Text
configMonoidSkipGHCCheckName = Text
"skip-ghc-check"

configMonoidSkipMsysName :: Text
configMonoidSkipMsysName :: Text
configMonoidSkipMsysName = Text
"skip-msys"

configMonoidRequireStackVersionName :: Text
configMonoidRequireStackVersionName :: Text
configMonoidRequireStackVersionName = Text
"require-stack-version"

configMonoidArchName :: Text
configMonoidArchName :: Text
configMonoidArchName = Text
"arch"

configMonoidGHCVariantName :: Text
configMonoidGHCVariantName :: Text
configMonoidGHCVariantName = Text
"ghc-variant"

configMonoidGHCBuildName :: Text
configMonoidGHCBuildName :: Text
configMonoidGHCBuildName = Text
"ghc-build"

configMonoidJobsName :: Text
configMonoidJobsName :: Text
configMonoidJobsName = Text
"jobs"

configMonoidExtraIncludeDirsName :: Text
configMonoidExtraIncludeDirsName :: Text
configMonoidExtraIncludeDirsName = Text
"extra-include-dirs"

configMonoidExtraLibDirsName :: Text
configMonoidExtraLibDirsName :: Text
configMonoidExtraLibDirsName = Text
"extra-lib-dirs"

configMonoidCustomPreprocessorExtsName  :: Text
configMonoidCustomPreprocessorExtsName :: Text
configMonoidCustomPreprocessorExtsName  = Text
"custom-preprocessor-extensions"

configMonoidOverrideGccPathName :: Text
configMonoidOverrideGccPathName :: Text
configMonoidOverrideGccPathName = Text
"with-gcc"

configMonoidOverrideHpackName :: Text
configMonoidOverrideHpackName :: Text
configMonoidOverrideHpackName = Text
"with-hpack"

configMonoidConcurrentTestsName :: Text
configMonoidConcurrentTestsName :: Text
configMonoidConcurrentTestsName = Text
"concurrent-tests"

configMonoidLocalBinPathName :: Text
configMonoidLocalBinPathName :: Text
configMonoidLocalBinPathName = Text
"local-bin-path"

configMonoidScmInitName :: Text
configMonoidScmInitName :: Text
configMonoidScmInitName = Text
"scm-init"

configMonoidTemplateParametersName :: Text
configMonoidTemplateParametersName :: Text
configMonoidTemplateParametersName = Text
"params"

configMonoidCompilerCheckName :: Text
configMonoidCompilerCheckName :: Text
configMonoidCompilerCheckName = Text
"compiler-check"

configMonoidCompilerRepositoryName :: Text
configMonoidCompilerRepositoryName :: Text
configMonoidCompilerRepositoryName = Text
"compiler-repository"

configMonoidGhcOptionsName :: Text
configMonoidGhcOptionsName :: Text
configMonoidGhcOptionsName = Text
"ghc-options"

configMonoidExtraPathName :: Text
configMonoidExtraPathName :: Text
configMonoidExtraPathName = Text
"extra-path"

configMonoidSetupInfoLocationsName :: Text
configMonoidSetupInfoLocationsName :: Text
configMonoidSetupInfoLocationsName = Text
"setup-info-locations"

configMonoidSetupInfoInlineName :: Text
configMonoidSetupInfoInlineName :: Text
configMonoidSetupInfoInlineName = Text
"setup-info"

configMonoidLocalProgramsBaseName :: Text
configMonoidLocalProgramsBaseName :: Text
configMonoidLocalProgramsBaseName = Text
"local-programs-path"

configMonoidPvpBoundsName :: Text
configMonoidPvpBoundsName :: Text
configMonoidPvpBoundsName = Text
"pvp-bounds"

configMonoidModifyCodePageName :: Text
configMonoidModifyCodePageName :: Text
configMonoidModifyCodePageName = Text
"modify-code-page"

configMonoidRebuildGhcOptionsName :: Text
configMonoidRebuildGhcOptionsName :: Text
configMonoidRebuildGhcOptionsName = Text
"rebuild-ghc-options"

configMonoidApplyGhcOptionsName :: Text
configMonoidApplyGhcOptionsName :: Text
configMonoidApplyGhcOptionsName = Text
"apply-ghc-options"

configMonoidAllowNewerName :: Text
configMonoidAllowNewerName :: Text
configMonoidAllowNewerName = Text
"allow-newer"

configMonoidAllowNewerDepsName :: Text
configMonoidAllowNewerDepsName :: Text
configMonoidAllowNewerDepsName = Text
"allow-newer-deps"

configMonoidDefaultTemplateName :: Text
configMonoidDefaultTemplateName :: Text
configMonoidDefaultTemplateName = Text
"default-template"

configMonoidAllowDifferentUserName :: Text
configMonoidAllowDifferentUserName :: Text
configMonoidAllowDifferentUserName = Text
"allow-different-user"

configMonoidDumpLogsName :: Text
configMonoidDumpLogsName :: Text
configMonoidDumpLogsName = Text
"dump-logs"

configMonoidSaveHackageCredsName :: Text
configMonoidSaveHackageCredsName :: Text
configMonoidSaveHackageCredsName = Text
"save-hackage-creds"

configMonoidHackageBaseUrlName :: Text
configMonoidHackageBaseUrlName :: Text
configMonoidHackageBaseUrlName = Text
"hackage-base-url"

configMonoidColorWhenUSName :: Text
configMonoidColorWhenUSName :: Text
configMonoidColorWhenUSName = Text
"color"

configMonoidColorWhenGBName :: Text
configMonoidColorWhenGBName :: Text
configMonoidColorWhenGBName = Text
"colour"

configMonoidStylesUSName :: Text
configMonoidStylesUSName :: Text
configMonoidStylesUSName = Text
"stack-colors"

configMonoidStylesGBName :: Text
configMonoidStylesGBName :: Text
configMonoidStylesGBName = Text
"stack-colours"

configMonoidHideSourcePathsName :: Text
configMonoidHideSourcePathsName :: Text
configMonoidHideSourcePathsName = Text
"hide-source-paths"

configMonoidRecommendUpgradeName :: Text
configMonoidRecommendUpgradeName :: Text
configMonoidRecommendUpgradeName = Text
"recommend-stack-upgrade"

configMonoidCasaRepoPrefixName :: Text
configMonoidCasaRepoPrefixName :: Text
configMonoidCasaRepoPrefixName = Text
"casa-repo-prefix"

configMonoidSnapshotLocationName :: Text
configMonoidSnapshotLocationName :: Text
configMonoidSnapshotLocationName = Text
"snapshot-location-base"

configMonoidNoRunCompileName :: Text
configMonoidNoRunCompileName :: Text
configMonoidNoRunCompileName = Text
"script-no-run-compile"

configMonoidStackDeveloperModeName :: Text
configMonoidStackDeveloperModeName :: Text
configMonoidStackDeveloperModeName = Text
"stack-developer-mode"

packageIndicesWarning :: String
packageIndicesWarning :: [Char]
packageIndicesWarning =
    [Char]
"The 'package-indices' key is deprecated in favour of 'package-index'."

resolveOptions :: StyleDoc
resolveOptions :: StyleDoc
resolveOptions =
     [Char] -> StyleDoc
flow [Char]
"This may be resolved by:"
  forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
  forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
bulletedList
       [ [StyleDoc] -> StyleDoc
fillSep
           [ StyleDoc
"Using"
           , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"--omit-packages"
           , StyleDoc
"to exclude mismatching package(s)."
           ]
       , [StyleDoc] -> StyleDoc
fillSep
           [ StyleDoc
"Using"
           , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"--resolver"
           , StyleDoc
"to specify a matching snapshot/resolver."
           ]
       ]

-- | Get the URL to request the information on the latest snapshots

askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text
askLatestSnapshotUrl :: forall env (m :: * -> *).
(MonadReader env m, HasConfig env) =>
m Text
askLatestSnapshotUrl = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Config -> Text
configLatestSnapshot

-- | @".stack-work"@

workDirL :: HasConfig env => Lens' env (Path Rel Dir)
workDirL :: forall env. HasConfig env => Lens' env (Path Rel Dir)
workDirL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> Path Rel Dir
configWorkDir (\Config
x Path Rel Dir
y -> Config
x { configWorkDir :: Path Rel Dir
configWorkDir = Path Rel Dir
y })

-- | @STACK_ROOT\/hooks\/@

hooksDir :: HasConfig env => RIO env (Path Abs Dir)
hooksDir :: forall env. HasConfig env => RIO env (Path Abs Dir)
hooksDir = do
  Path Abs Dir
sr <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Config -> Path Abs Dir
configStackRoot
  forall (f :: * -> *) a. Applicative f => a -> f a
pure (Path Abs Dir
sr forall b t. Path b Dir -> Path Rel t -> Path b t
</> [reldir|hooks|])

-- | @STACK_ROOT\/hooks\/ghc-install.sh@

ghcInstallHook :: HasConfig env => RIO env (Path Abs File)
ghcInstallHook :: forall env. HasConfig env => RIO env (Path Abs File)
ghcInstallHook = do
  Path Abs Dir
hd <- forall env. HasConfig env => RIO env (Path Abs Dir)
hooksDir
  forall (f :: * -> *) a. Applicative f => a -> f a
pure (Path Abs Dir
hd forall b t. Path b Dir -> Path Rel t -> Path b t
</> [relfile|ghc-install.sh|])

-- | Per-project work dir

getProjectWorkDir :: (HasBuildConfig env, MonadReader env m) => m (Path Abs Dir)
getProjectWorkDir :: forall env (m :: * -> *).
(HasBuildConfig env, MonadReader env m) =>
m (Path Abs Dir)
getProjectWorkDir = do
    Path Abs Dir
root    <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env r. HasBuildConfig env => Getting r env (Path Abs Dir)
projectRootL
    Path Rel Dir
workDir <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasConfig env => Lens' env (Path Rel Dir)
workDirL
    forall (f :: * -> *) a. Applicative f => a -> f a
pure (Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
workDir)

-- | Relative directory for the platform identifier

platformOnlyRelDir
    :: (MonadReader env m, HasPlatform env, MonadThrow m)
    => m (Path Rel Dir)
platformOnlyRelDir :: forall env (m :: * -> *).
(MonadReader env m, HasPlatform env, MonadThrow m) =>
m (Path Rel Dir)
platformOnlyRelDir = do
    Platform
platform <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasPlatform env => Lens' env Platform
platformL
    PlatformVariant
platformVariant <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasPlatform env => Lens' env PlatformVariant
platformVariantL
    forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir (forall a. Pretty a => a -> [Char]
Distribution.Text.display Platform
platform forall a. [a] -> [a] -> [a]
++ PlatformVariant -> [Char]
platformVariantSuffix PlatformVariant
platformVariant)

-- | Directory containing snapshots

snapshotsDir :: (MonadReader env m, HasEnvConfig env, MonadThrow m) => m (Path Abs Dir)
snapshotsDir :: forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env, MonadThrow m) =>
m (Path Abs Dir)
snapshotsDir = do
    Path Abs Dir
root <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall s. HasConfig s => Lens' s (Path Abs Dir)
stackRootL
    Path Rel Dir
platform <- forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env, MonadThrow m) =>
m (Path Rel Dir)
platformGhcRelDir
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirSnapshots forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
platform

-- | Installation root for dependencies

installationRootDeps :: (HasEnvConfig env) => RIO env (Path Abs Dir)
installationRootDeps :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootDeps = do
    Path Abs Dir
root <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall s. HasConfig s => Lens' s (Path Abs Dir)
stackRootL
    -- TODO: also useShaPathOnWindows here, once #1173 is resolved.

    Path Rel Dir
psc <- forall env. HasEnvConfig env => RIO env (Path Rel Dir)
platformSnapAndCompilerRel
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirSnapshots forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
psc

-- | Installation root for locals

installationRootLocal :: (HasEnvConfig env) => RIO env (Path Abs Dir)
installationRootLocal :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootLocal = do
    Path Abs Dir
workDir <- forall env (m :: * -> *).
(HasBuildConfig env, MonadReader env m) =>
m (Path Abs Dir)
getProjectWorkDir
    Path Rel Dir
psc <- forall (m :: * -> *).
MonadThrow m =>
Path Rel Dir -> m (Path Rel Dir)
useShaPathOnWindows forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall env. HasEnvConfig env => RIO env (Path Rel Dir)
platformSnapAndCompilerRel
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
workDir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirInstall forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
psc

-- | Installation root for compiler tools

bindirCompilerTools :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
bindirCompilerTools :: forall (m :: * -> *) env.
(MonadThrow m, MonadReader env m, HasEnvConfig env) =>
m (Path Abs Dir)
bindirCompilerTools = do
    Config
config <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasConfig env => Lens' env Config
configL
    Path Rel Dir
platform <- forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env, MonadThrow m) =>
m (Path Rel Dir)
platformGhcRelDir
    ActualCompiler
compilerVersion <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasSourceMap env => SimpleGetter env ActualCompiler
actualCompilerVersionL
    Path Rel Dir
compiler <- forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir forall a b. (a -> b) -> a -> b
$ ActualCompiler -> [Char]
compilerVersionString ActualCompiler
compilerVersion
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
        forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall s. HasConfig s => Lens' s (Path Abs Dir)
stackRootL Config
config forall b t. Path b Dir -> Path Rel t -> Path b t
</>
        Path Rel Dir
relDirCompilerTools forall b t. Path b Dir -> Path Rel t -> Path b t
</>
        Path Rel Dir
platform forall b t. Path b Dir -> Path Rel t -> Path b t
</>
        Path Rel Dir
compiler forall b t. Path b Dir -> Path Rel t -> Path b t
</>
        Path Rel Dir
bindirSuffix

-- | Hoogle directory.

hoogleRoot :: (HasEnvConfig env) => RIO env (Path Abs Dir)
hoogleRoot :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
hoogleRoot = do
    Path Abs Dir
workDir <- forall env (m :: * -> *).
(HasBuildConfig env, MonadReader env m) =>
m (Path Abs Dir)
getProjectWorkDir
    Path Rel Dir
psc <- forall (m :: * -> *).
MonadThrow m =>
Path Rel Dir -> m (Path Rel Dir)
useShaPathOnWindows forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall env. HasEnvConfig env => RIO env (Path Rel Dir)
platformSnapAndCompilerRel
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
workDir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirHoogle forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
psc

-- | Get the hoogle database path.

hoogleDatabasePath :: (HasEnvConfig env) => RIO env (Path Abs File)
hoogleDatabasePath :: forall env. HasEnvConfig env => RIO env (Path Abs File)
hoogleDatabasePath = do
    Path Abs Dir
dir <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
hoogleRoot
    forall (f :: * -> *) a. Applicative f => a -> f a
pure (Path Abs Dir
dir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
relFileDatabaseHoo)

-- | Path for platform followed by snapshot name followed by compiler

-- name.

platformSnapAndCompilerRel
    :: (HasEnvConfig env)
    => RIO env (Path Rel Dir)
platformSnapAndCompilerRel :: forall env. HasEnvConfig env => RIO env (Path Rel Dir)
platformSnapAndCompilerRel = do
    Path Rel Dir
platform <- forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env, MonadThrow m) =>
m (Path Rel Dir)
platformGhcRelDir
    SourceMapHash
smh <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasEnvConfig env => Lens' env EnvConfig
envConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to EnvConfig -> SourceMapHash
envConfigSourceMapHash
    Path Rel Dir
name <- forall (m :: * -> *).
MonadThrow m =>
SourceMapHash -> m (Path Rel Dir)
smRelDir SourceMapHash
smh
    Path Rel Dir
ghc <- forall (m :: * -> *) env.
(MonadThrow m, MonadReader env m, HasEnvConfig env) =>
m (Path Rel Dir)
compilerVersionDir
    forall (m :: * -> *).
MonadThrow m =>
Path Rel Dir -> m (Path Rel Dir)
useShaPathOnWindows (Path Rel Dir
platform forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
name forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
ghc)

-- | Relative directory for the platform and GHC identifier

platformGhcRelDir
    :: (MonadReader env m, HasEnvConfig env, MonadThrow m)
    => m (Path Rel Dir)
platformGhcRelDir :: forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env, MonadThrow m) =>
m (Path Rel Dir)
platformGhcRelDir = do
    CompilerPaths
cp <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasCompiler env => SimpleGetter env CompilerPaths
compilerPathsL
    let cbSuffix :: [Char]
cbSuffix = CompilerBuild -> [Char]
compilerBuildSuffix forall a b. (a -> b) -> a -> b
$ CompilerPaths -> CompilerBuild
cpBuild CompilerPaths
cp
    [Char]
verOnly <- forall env (m :: * -> *).
(MonadReader env m, HasPlatform env, HasGHCVariant env) =>
m [Char]
platformGhcVerOnlyRelDirStr
    forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir (forall a. Monoid a => [a] -> a
mconcat [ [Char]
verOnly, [Char]
cbSuffix ])

-- | Relative directory for the platform and GHC identifier without GHC bindist build

platformGhcVerOnlyRelDir
    :: (MonadReader env m, HasPlatform env, HasGHCVariant env, MonadThrow m)
    => m (Path Rel Dir)
platformGhcVerOnlyRelDir :: forall env (m :: * -> *).
(MonadReader env m, HasPlatform env, HasGHCVariant env,
 MonadThrow m) =>
m (Path Rel Dir)
platformGhcVerOnlyRelDir =
    forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall env (m :: * -> *).
(MonadReader env m, HasPlatform env, HasGHCVariant env) =>
m [Char]
platformGhcVerOnlyRelDirStr

-- | Relative directory for the platform and GHC identifier without GHC bindist build

-- (before parsing into a Path)

platformGhcVerOnlyRelDirStr
    :: (MonadReader env m, HasPlatform env, HasGHCVariant env)
    => m FilePath
platformGhcVerOnlyRelDirStr :: forall env (m :: * -> *).
(MonadReader env m, HasPlatform env, HasGHCVariant env) =>
m [Char]
platformGhcVerOnlyRelDirStr = do
    Platform
platform <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasPlatform env => Lens' env Platform
platformL
    PlatformVariant
platformVariant <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasPlatform env => Lens' env PlatformVariant
platformVariantL
    GHCVariant
ghcVariant <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasGHCVariant env => SimpleGetter env GHCVariant
ghcVariantL
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall a. Pretty a => a -> [Char]
Distribution.Text.display Platform
platform
                     , PlatformVariant -> [Char]
platformVariantSuffix PlatformVariant
platformVariant
                     , GHCVariant -> [Char]
ghcVariantSuffix GHCVariant
ghcVariant ]

-- | This is an attempt to shorten Stack paths on Windows to decrease our

-- chances of hitting 260 symbol path limit. The idea is to calculate

-- SHA1 hash of the path used on other architectures, encode with base

-- 16 and take first 8 symbols of it.

useShaPathOnWindows :: MonadThrow m => Path Rel Dir -> m (Path Rel Dir)
useShaPathOnWindows :: forall (m :: * -> *).
MonadThrow m =>
Path Rel Dir -> m (Path Rel Dir)
useShaPathOnWindows
  | Bool
osIsWindows = forall t (m :: * -> *).
(IsPath Rel t, MonadThrow m) =>
Path Rel t -> m (Path Rel t)
shaPath
  | Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure

shaPath :: (IsPath Rel t, MonadThrow m) => Path Rel t -> m (Path Rel t)
shaPath :: forall t (m :: * -> *).
(IsPath Rel t, MonadThrow m) =>
Path Rel t -> m (Path Rel t)
shaPath = forall t (m :: * -> *).
(IsPath Rel t, MonadThrow m) =>
ByteString -> m (Path Rel t)
shaPathForBytes forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> [Char]
toFilePath

shaPathForBytes :: (IsPath Rel t, MonadThrow m) => ByteString -> m (Path Rel t)
shaPathForBytes :: forall t (m :: * -> *).
(IsPath Rel t, MonadThrow m) =>
ByteString -> m (Path Rel t)
shaPathForBytes
    = forall b t (m :: * -> *).
(IsPath b t, MonadThrow m) =>
[Char] -> m (Path b t)
parsePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
S8.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString -> ByteString
S8.take Int
8
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
Mem.convertToBase Base
Mem.Base16 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith SHA1
SHA1

-- TODO: Move something like this into the path package. Consider

-- subsuming path-io's 'AnyPath'?

class IsPath b t where
  parsePath :: MonadThrow m => FilePath -> m (Path b t)

instance IsPath Abs Dir where parsePath :: forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs Dir)
parsePath = forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs Dir)
parseAbsDir
instance IsPath Rel Dir where parsePath :: forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parsePath = forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir
instance IsPath Abs File where parsePath :: forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs File)
parsePath = forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Abs File)
parseAbsFile
instance IsPath Rel File where parsePath :: forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel File)
parsePath = forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel File)
parseRelFile

compilerVersionDir :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Rel Dir)
compilerVersionDir :: forall (m :: * -> *) env.
(MonadThrow m, MonadReader env m, HasEnvConfig env) =>
m (Path Rel Dir)
compilerVersionDir = do
    ActualCompiler
compilerVersion <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasSourceMap env => SimpleGetter env ActualCompiler
actualCompilerVersionL
    forall (m :: * -> *). MonadThrow m => [Char] -> m (Path Rel Dir)
parseRelDir forall a b. (a -> b) -> a -> b
$ case ActualCompiler
compilerVersion of
        ACGhc Version
version -> Version -> [Char]
versionString Version
version
        ACGhcGit {} -> ActualCompiler -> [Char]
compilerVersionString ActualCompiler
compilerVersion

-- | Package database for installing dependencies into

packageDatabaseDeps :: (HasEnvConfig env) => RIO env (Path Abs Dir)
packageDatabaseDeps :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
packageDatabaseDeps = do
    Path Abs Dir
root <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootDeps
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirPkgdb

-- | Package database for installing local packages into

packageDatabaseLocal :: (HasEnvConfig env) => RIO env (Path Abs Dir)
packageDatabaseLocal :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
packageDatabaseLocal = do
    Path Abs Dir
root <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootLocal
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirPkgdb

-- | Extra package databases

packageDatabaseExtra :: (MonadReader env m, HasEnvConfig env) => m [Path Abs Dir]
packageDatabaseExtra :: forall env (m :: * -> *).
(MonadReader env m, HasEnvConfig env) =>
m [Path Abs Dir]
packageDatabaseExtra = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasBuildConfig env => Lens' env BuildConfig
buildConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to BuildConfig -> [Path Abs Dir]
bcExtraPackageDBs

-- | Where do we get information on global packages for loading up a

-- 'LoadedSnapshot'?

data GlobalInfoSource
  = GISSnapshotHints
  -- ^ Accept the hints in the snapshot definition

  | GISCompiler ActualCompiler
  -- ^ Look up the actual information in the installed compiler


-- | Where HPC reports and tix files get stored.

hpcReportDir :: (HasEnvConfig env)
             => RIO env (Path Abs Dir)
hpcReportDir :: forall env. HasEnvConfig env => RIO env (Path Abs Dir)
hpcReportDir = do
   Path Abs Dir
root <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootLocal
   forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Path Abs Dir
root forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDirHpc

-- | Get the extra bin directories (for the PATH). Puts more local first

--

-- Bool indicates whether or not to include the locals

extraBinDirs :: (HasEnvConfig env)
             => RIO env (Bool -> [Path Abs Dir])
extraBinDirs :: forall env. HasEnvConfig env => RIO env (Bool -> [Path Abs Dir])
extraBinDirs = do
    Path Abs Dir
deps <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootDeps
    Path Abs Dir
local' <- forall env. HasEnvConfig env => RIO env (Path Abs Dir)
installationRootLocal
    Path Abs Dir
tools <- forall (m :: * -> *) env.
(MonadThrow m, MonadReader env m, HasEnvConfig env) =>
m (Path Abs Dir)
bindirCompilerTools
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ \Bool
locals -> if Bool
locals
        then [Path Abs Dir
local' forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
bindirSuffix, Path Abs Dir
deps forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
bindirSuffix, Path Abs Dir
tools]
        else [Path Abs Dir
deps forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
bindirSuffix, Path Abs Dir
tools]

minimalEnvSettings :: EnvSettings
minimalEnvSettings :: EnvSettings
minimalEnvSettings =
    EnvSettings
    { esIncludeLocals :: Bool
esIncludeLocals = Bool
False
    , esIncludeGhcPackagePath :: Bool
esIncludeGhcPackagePath = Bool
False
    , esStackExe :: Bool
esStackExe = Bool
False
    , esLocaleUtf8 :: Bool
esLocaleUtf8 = Bool
False
    , esKeepGhcRts :: Bool
esKeepGhcRts = Bool
False
    }

-- | Default @EnvSettings@ which includes locals and GHC_PACKAGE_PATH.

--

-- Note that this also passes through the GHCRTS environment variable.

-- See https://github.com/commercialhaskell/stack/issues/3444

defaultEnvSettings :: EnvSettings
defaultEnvSettings :: EnvSettings
defaultEnvSettings = EnvSettings
    { esIncludeLocals :: Bool
esIncludeLocals = Bool
True
    , esIncludeGhcPackagePath :: Bool
esIncludeGhcPackagePath = Bool
True
    , esStackExe :: Bool
esStackExe = Bool
True
    , esLocaleUtf8 :: Bool
esLocaleUtf8 = Bool
False
    , esKeepGhcRts :: Bool
esKeepGhcRts = Bool
True
    }

-- | Environment settings which do not embellish the environment

--

-- Note that this also passes through the GHCRTS environment variable.

-- See https://github.com/commercialhaskell/stack/issues/3444

plainEnvSettings :: EnvSettings
plainEnvSettings :: EnvSettings
plainEnvSettings = EnvSettings
    { esIncludeLocals :: Bool
esIncludeLocals = Bool
False
    , esIncludeGhcPackagePath :: Bool
esIncludeGhcPackagePath = Bool
False
    , esStackExe :: Bool
esStackExe = Bool
False
    , esLocaleUtf8 :: Bool
esLocaleUtf8 = Bool
False
    , esKeepGhcRts :: Bool
esKeepGhcRts = Bool
True
    }

-- | Get the path for the given compiler ignoring any local binaries.

--

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

getCompilerPath :: HasCompiler env => RIO env (Path Abs File)
getCompilerPath :: forall env. HasCompiler env => RIO env (Path Abs File)
getCompilerPath = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasCompiler env => SimpleGetter env CompilerPaths
compilerPathsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to CompilerPaths -> Path Abs File
cpCompiler

data ProjectAndConfigMonoid
  = ProjectAndConfigMonoid !Project !ConfigMonoid

parseProjectAndConfigMonoid :: Path Abs Dir -> Value -> Yaml.Parser (WithJSONWarnings (IO ProjectAndConfigMonoid))
parseProjectAndConfigMonoid :: Path Abs Dir
-> Value -> Parser (WithJSONWarnings (IO ProjectAndConfigMonoid))
parseProjectAndConfigMonoid Path Abs Dir
rootDir =
    forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"ProjectAndConfigMonoid" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        [RelFilePath]
packages <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"packages" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= [Text -> RelFilePath
RelFilePath Text
"."]
        [Unresolved (NonEmpty RawPackageLocation)]
deps <- forall (t :: * -> *) (u :: * -> *) a.
(Traversable t, Traversable u) =>
WarningParser (u (t (WithJSONWarnings a)))
-> WarningParser (u (t a))
jsonSubWarningsTT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"extra-deps") forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
        Map (CabalString PackageName) (Map (CabalString FlagName) Bool)
flags' <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"flags" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
        let flags :: Map PackageName (Map FlagName Bool)
flags = forall a v. Map (CabalString a) v -> Map a v
unCabalStringMap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a v. Map (CabalString a) v -> Map a v
unCabalStringMap
                    (Map (CabalString PackageName) (Map (CabalString FlagName) Bool)
flags' :: Map (CabalString PackageName) (Map (CabalString FlagName) Bool))

        Unresolved RawSnapshotLocation
resolver <- forall a. WarningParser (WithJSONWarnings a) -> WarningParser a
jsonSubWarnings forall a b. (a -> b) -> a -> b
$ Object
o forall a. FromJSON a => Object -> [Text] -> WarningParser a
...: [Text
"snapshot", Text
"resolver"]
        Maybe WantedCompiler
mcompiler <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"compiler"
        Maybe [Char]
msg <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"user-message"
        ConfigMonoid
config <- Path Abs Dir -> Object -> WarningParser ConfigMonoid
parseConfigMonoidObject Path Abs Dir
rootDir Object
o
        [[Char]]
extraPackageDBs <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"extra-package-dbs" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= []
        Maybe Curator
mcurator <- forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"curator")
        Set (CabalString PackageName)
drops <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"drop-packages" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
        forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ do
          [NonEmpty RawPackageLocation]
deps' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) a.
MonadIO m =>
Maybe (Path Abs Dir) -> Unresolved a -> m a
resolvePaths (forall a. a -> Maybe a
Just Path Abs Dir
rootDir)) [Unresolved (NonEmpty RawPackageLocation)]
deps
          RawSnapshotLocation
resolver' <- forall (m :: * -> *) a.
MonadIO m =>
Maybe (Path Abs Dir) -> Unresolved a -> m a
resolvePaths (forall a. a -> Maybe a
Just Path Abs Dir
rootDir) Unresolved RawSnapshotLocation
resolver
          let project :: Project
project = Project
                  { projectUserMsg :: Maybe [Char]
projectUserMsg = Maybe [Char]
msg
                  , projectResolver :: RawSnapshotLocation
projectResolver = RawSnapshotLocation
resolver'
                  , projectCompiler :: Maybe WantedCompiler
projectCompiler = Maybe WantedCompiler
mcompiler -- FIXME make sure resolver' isn't SLCompiler

                  , projectExtraPackageDBs :: [[Char]]
projectExtraPackageDBs = [[Char]]
extraPackageDBs
                  , projectPackages :: [RelFilePath]
projectPackages = [RelFilePath]
packages
                  , projectDependencies :: [RawPackageLocation]
projectDependencies = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall (t :: * -> *) a. Foldable t => t a -> [a]
toList ([NonEmpty RawPackageLocation]
deps' :: [NonEmpty RawPackageLocation])
                  , projectFlags :: Map PackageName (Map FlagName Bool)
projectFlags = Map PackageName (Map FlagName Bool)
flags
                  , projectCurator :: Maybe Curator
projectCurator = Maybe Curator
mcurator
                  , projectDropPackages :: Set PackageName
projectDropPackages = forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map forall a. CabalString a -> a
unCabalString Set (CabalString PackageName)
drops
                  }
          forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Project -> ConfigMonoid -> ProjectAndConfigMonoid
ProjectAndConfigMonoid Project
project ConfigMonoid
config

-- | A software control system.

data SCM = Git
  deriving (Int -> SCM -> ShowS
[SCM] -> ShowS
SCM -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SCM] -> ShowS
$cshowList :: [SCM] -> ShowS
show :: SCM -> [Char]
$cshow :: SCM -> [Char]
showsPrec :: Int -> SCM -> ShowS
$cshowsPrec :: Int -> SCM -> ShowS
Show)

instance FromJSON SCM where
    parseJSON :: Value -> Parser SCM
parseJSON Value
v = do
        [Char]
s <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
        case [Char]
s of
            [Char]
"git" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure SCM
Git
            [Char]
_ -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"Unknown or unsupported SCM: " forall a. Semigroup a => a -> a -> a
<> [Char]
s)

instance ToJSON SCM where
    toJSON :: SCM -> Value
toJSON SCM
Git = forall a. ToJSON a => a -> Value
toJSON (Text
"git" :: Text)

-- | A variant of the platform, used to differentiate Docker builds from host

data PlatformVariant = PlatformVariantNone
                     | PlatformVariant String

-- | Render a platform variant to a String suffix.

platformVariantSuffix :: PlatformVariant -> String
platformVariantSuffix :: PlatformVariant -> [Char]
platformVariantSuffix PlatformVariant
PlatformVariantNone = [Char]
""
platformVariantSuffix (PlatformVariant [Char]
v) = [Char]
"-" forall a. [a] -> [a] -> [a]
++ [Char]
v

-- | Specialized variant of GHC (e.g. libgmp4 or integer-simple)

data GHCVariant
    = GHCStandard
    -- ^ Standard bindist

    | GHCIntegerSimple
    -- ^ Bindist that uses integer-simple

    | GHCNativeBignum
    -- ^ Bindist that uses the Haskell-native big-integer backend

    | GHCCustom String
    -- ^ Other bindists

    deriving (Int -> GHCVariant -> ShowS
[GHCVariant] -> ShowS
GHCVariant -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GHCVariant] -> ShowS
$cshowList :: [GHCVariant] -> ShowS
show :: GHCVariant -> [Char]
$cshow :: GHCVariant -> [Char]
showsPrec :: Int -> GHCVariant -> ShowS
$cshowsPrec :: Int -> GHCVariant -> ShowS
Show)

instance FromJSON GHCVariant where
    -- Strange structuring is to give consistent error messages

    parseJSON :: Value -> Parser GHCVariant
parseJSON =
        forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText
            [Char]
"GHCVariant"
            (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> [Char]
show) forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => [Char] -> m GHCVariant
parseGHCVariant forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack)

-- | Render a GHC variant to a String.

ghcVariantName :: GHCVariant -> String
ghcVariantName :: GHCVariant -> [Char]
ghcVariantName GHCVariant
GHCStandard = [Char]
"standard"
ghcVariantName GHCVariant
GHCIntegerSimple = [Char]
"integersimple"
ghcVariantName GHCVariant
GHCNativeBignum = [Char]
"int-native"
ghcVariantName (GHCCustom [Char]
name) = [Char]
"custom-" forall a. [a] -> [a] -> [a]
++ [Char]
name

-- | Render a GHC variant to a String suffix.

ghcVariantSuffix :: GHCVariant -> String
ghcVariantSuffix :: GHCVariant -> [Char]
ghcVariantSuffix GHCVariant
GHCStandard = [Char]
""
ghcVariantSuffix GHCVariant
v = [Char]
"-" forall a. [a] -> [a] -> [a]
++ GHCVariant -> [Char]
ghcVariantName GHCVariant
v

-- | Parse GHC variant from a String.

parseGHCVariant :: (MonadThrow m) => String -> m GHCVariant
parseGHCVariant :: forall (m :: * -> *). MonadThrow m => [Char] -> m GHCVariant
parseGHCVariant [Char]
s =
    case forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix [Char]
"custom-" [Char]
s of
        Just [Char]
name -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> GHCVariant
GHCCustom [Char]
name)
        Maybe [Char]
Nothing
          | [Char]
s forall a. Eq a => a -> a -> Bool
== [Char]
"" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GHCVariant
GHCStandard
          | [Char]
s forall a. Eq a => a -> a -> Bool
== [Char]
"standard" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GHCVariant
GHCStandard
          | [Char]
s forall a. Eq a => a -> a -> Bool
== [Char]
"integersimple" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GHCVariant
GHCIntegerSimple
          | [Char]
s forall a. Eq a => a -> a -> Bool
== [Char]
"int-native" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GHCVariant
GHCNativeBignum
          | Bool
otherwise -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> GHCVariant
GHCCustom [Char]
s)

-- | Build of the compiler distribution (e.g. standard, gmp4, tinfo6)

-- | Information for a file to download.

data DownloadInfo = DownloadInfo
    { DownloadInfo -> Text
downloadInfoUrl :: Text
      -- ^ URL or absolute file path

    , DownloadInfo -> Maybe Int
downloadInfoContentLength :: Maybe Int
    , DownloadInfo -> Maybe ByteString
downloadInfoSha1 :: Maybe ByteString
    , DownloadInfo -> Maybe ByteString
downloadInfoSha256 :: Maybe ByteString
    } deriving (Int -> DownloadInfo -> ShowS
[DownloadInfo] -> ShowS
DownloadInfo -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DownloadInfo] -> ShowS
$cshowList :: [DownloadInfo] -> ShowS
show :: DownloadInfo -> [Char]
$cshow :: DownloadInfo -> [Char]
showsPrec :: Int -> DownloadInfo -> ShowS
$cshowsPrec :: Int -> DownloadInfo -> ShowS
Show)

instance FromJSON (WithJSONWarnings DownloadInfo) where
    parseJSON :: Value -> Parser (WithJSONWarnings DownloadInfo)
parseJSON = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"DownloadInfo" Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject

-- | Parse JSON in existing object for 'DownloadInfo'

parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject Object
o = do
    Text
url <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser a
..: Text
"url"
    Maybe Int
contentLength <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"content-length"
    Maybe Text
sha1TextMay <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sha1"
    Maybe Text
sha256TextMay <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sha256"
    forall (f :: * -> *) a. Applicative f => a -> f a
pure
        DownloadInfo
        { downloadInfoUrl :: Text
downloadInfoUrl = Text
url
        , downloadInfoContentLength :: Maybe Int
downloadInfoContentLength = Maybe Int
contentLength
        , downloadInfoSha1 :: Maybe ByteString
downloadInfoSha1 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 Maybe Text
sha1TextMay
        , downloadInfoSha256 :: Maybe ByteString
downloadInfoSha256 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 Maybe Text
sha256TextMay
        }

data VersionedDownloadInfo = VersionedDownloadInfo
    { VersionedDownloadInfo -> Version
vdiVersion :: Version
    , VersionedDownloadInfo -> DownloadInfo
vdiDownloadInfo :: DownloadInfo
    }
    deriving Int -> VersionedDownloadInfo -> ShowS
[VersionedDownloadInfo] -> ShowS
VersionedDownloadInfo -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [VersionedDownloadInfo] -> ShowS
$cshowList :: [VersionedDownloadInfo] -> ShowS
show :: VersionedDownloadInfo -> [Char]
$cshow :: VersionedDownloadInfo -> [Char]
showsPrec :: Int -> VersionedDownloadInfo -> ShowS
$cshowsPrec :: Int -> VersionedDownloadInfo -> ShowS
Show

instance FromJSON (WithJSONWarnings VersionedDownloadInfo) where
    parseJSON :: Value -> Parser (WithJSONWarnings VersionedDownloadInfo)
parseJSON = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"VersionedDownloadInfo" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        CabalString Version
version <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser a
..: Text
"version"
        DownloadInfo
downloadInfo <- Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject Object
o
        forall (f :: * -> *) a. Applicative f => a -> f a
pure VersionedDownloadInfo
            { vdiVersion :: Version
vdiVersion = Version
version
            , vdiDownloadInfo :: DownloadInfo
vdiDownloadInfo = DownloadInfo
downloadInfo
            }

data GHCDownloadInfo = GHCDownloadInfo
    { GHCDownloadInfo -> [Text]
gdiConfigureOpts :: [Text]
    , GHCDownloadInfo -> Map Text Text
gdiConfigureEnv :: Map Text Text
    , GHCDownloadInfo -> DownloadInfo
gdiDownloadInfo :: DownloadInfo
    }
    deriving Int -> GHCDownloadInfo -> ShowS
[GHCDownloadInfo] -> ShowS
GHCDownloadInfo -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GHCDownloadInfo] -> ShowS
$cshowList :: [GHCDownloadInfo] -> ShowS
show :: GHCDownloadInfo -> [Char]
$cshow :: GHCDownloadInfo -> [Char]
showsPrec :: Int -> GHCDownloadInfo -> ShowS
$cshowsPrec :: Int -> GHCDownloadInfo -> ShowS
Show

instance FromJSON (WithJSONWarnings GHCDownloadInfo) where
    parseJSON :: Value -> Parser (WithJSONWarnings GHCDownloadInfo)
parseJSON = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"GHCDownloadInfo" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        [Text]
configureOpts <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"configure-opts" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
        Map Text Text
configureEnv <- Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"configure-env" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty
        DownloadInfo
downloadInfo <- Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject Object
o
        forall (f :: * -> *) a. Applicative f => a -> f a
pure GHCDownloadInfo
            { gdiConfigureOpts :: [Text]
gdiConfigureOpts = [Text]
configureOpts
            , gdiConfigureEnv :: Map Text Text
gdiConfigureEnv = Map Text Text
configureEnv
            , gdiDownloadInfo :: DownloadInfo
gdiDownloadInfo = DownloadInfo
downloadInfo
            }

data SetupInfo = SetupInfo
    { SetupInfo -> Maybe DownloadInfo
siSevenzExe :: Maybe DownloadInfo
    , SetupInfo -> Maybe DownloadInfo
siSevenzDll :: Maybe DownloadInfo
    , SetupInfo -> Map Text VersionedDownloadInfo
siMsys2 :: Map Text VersionedDownloadInfo
    , SetupInfo -> Map Text (Map Version GHCDownloadInfo)
siGHCs :: Map Text (Map Version GHCDownloadInfo)
    , SetupInfo -> Map Text (Map Version DownloadInfo)
siStack :: Map Text (Map Version DownloadInfo)
    }
    deriving Int -> SetupInfo -> ShowS
[SetupInfo] -> ShowS
SetupInfo -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SetupInfo] -> ShowS
$cshowList :: [SetupInfo] -> ShowS
show :: SetupInfo -> [Char]
$cshow :: SetupInfo -> [Char]
showsPrec :: Int -> SetupInfo -> ShowS
$cshowsPrec :: Int -> SetupInfo -> ShowS
Show

instance FromJSON (WithJSONWarnings SetupInfo) where
    parseJSON :: Value -> Parser (WithJSONWarnings SetupInfo)
parseJSON = forall a.
[Char]
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings [Char]
"SetupInfo" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Maybe DownloadInfo
siSevenzExe <- forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sevenzexe-info")
        Maybe DownloadInfo
siSevenzDll <- forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sevenzdll-info")
        Map Text VersionedDownloadInfo
siMsys2 <- forall (t :: * -> *) a.
Traversable t =>
WarningParser (t (WithJSONWarnings a)) -> WarningParser (t a)
jsonSubWarningsT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"msys2" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
        (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a v. Map (CabalString a) v -> Map a v
unCabalStringMap -> Map Text (Map Version GHCDownloadInfo)
siGHCs) <- forall (t :: * -> *) (u :: * -> *) a.
(Traversable t, Traversable u) =>
WarningParser (u (t (WithJSONWarnings a)))
-> WarningParser (u (t a))
jsonSubWarningsTT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"ghc" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
        (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a v. Map (CabalString a) v -> Map a v
unCabalStringMap -> Map Text (Map Version DownloadInfo)
siStack) <- forall (t :: * -> *) (u :: * -> *) a.
(Traversable t, Traversable u) =>
WarningParser (u (t (WithJSONWarnings a)))
-> WarningParser (u (t a))
jsonSubWarningsTT (Object
o forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"stack" forall a. WarningParser (Maybe a) -> a -> WarningParser a
..!= forall a. Monoid a => a
mempty)
        forall (f :: * -> *) a. Applicative f => a -> f a
pure SetupInfo {Maybe DownloadInfo
Map Text (Map Version GHCDownloadInfo)
Map Text (Map Version DownloadInfo)
Map Text VersionedDownloadInfo
siStack :: Map Text (Map Version DownloadInfo)
siGHCs :: Map Text (Map Version GHCDownloadInfo)
siMsys2 :: Map Text VersionedDownloadInfo
siSevenzDll :: Maybe DownloadInfo
siSevenzExe :: Maybe DownloadInfo
siStack :: Map Text (Map Version DownloadInfo)
siGHCs :: Map Text (Map Version GHCDownloadInfo)
siMsys2 :: Map Text VersionedDownloadInfo
siSevenzDll :: Maybe DownloadInfo
siSevenzExe :: Maybe DownloadInfo
..}

-- | For the @siGHCs@ field maps are deeply merged.

-- For all fields the values from the first @SetupInfo@ win.

instance Semigroup SetupInfo where
    SetupInfo
l <> :: SetupInfo -> SetupInfo -> SetupInfo
<> SetupInfo
r =
        SetupInfo
        { siSevenzExe :: Maybe DownloadInfo
siSevenzExe = SetupInfo -> Maybe DownloadInfo
siSevenzExe SetupInfo
l forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SetupInfo -> Maybe DownloadInfo
siSevenzExe SetupInfo
r
        , siSevenzDll :: Maybe DownloadInfo
siSevenzDll = SetupInfo -> Maybe DownloadInfo
siSevenzDll SetupInfo
l forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SetupInfo -> Maybe DownloadInfo
siSevenzDll SetupInfo
r
        , siMsys2 :: Map Text VersionedDownloadInfo
siMsys2 = SetupInfo -> Map Text VersionedDownloadInfo
siMsys2 SetupInfo
l forall a. Semigroup a => a -> a -> a
<> SetupInfo -> Map Text VersionedDownloadInfo
siMsys2 SetupInfo
r
        , siGHCs :: Map Text (Map Version GHCDownloadInfo)
siGHCs = forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Semigroup a => a -> a -> a
(<>) (SetupInfo -> Map Text (Map Version GHCDownloadInfo)
siGHCs SetupInfo
l) (SetupInfo -> Map Text (Map Version GHCDownloadInfo)
siGHCs SetupInfo
r)
        , siStack :: Map Text (Map Version DownloadInfo)
siStack = forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Semigroup a => a -> a -> a
(<>) (SetupInfo -> Map Text (Map Version DownloadInfo)
siStack SetupInfo
l) (SetupInfo -> Map Text (Map Version DownloadInfo)
siStack SetupInfo
r) }

instance Monoid SetupInfo where
    mempty :: SetupInfo
mempty =
        SetupInfo
        { siSevenzExe :: Maybe DownloadInfo
siSevenzExe = forall a. Maybe a
Nothing
        , siSevenzDll :: Maybe DownloadInfo
siSevenzDll = forall a. Maybe a
Nothing
        , siMsys2 :: Map Text VersionedDownloadInfo
siMsys2 = forall k a. Map k a
Map.empty
        , siGHCs :: Map Text (Map Version GHCDownloadInfo)
siGHCs = forall k a. Map k a
Map.empty
        , siStack :: Map Text (Map Version DownloadInfo)
siStack = forall k a. Map k a
Map.empty
        }
    mappend :: SetupInfo -> SetupInfo -> SetupInfo
mappend = forall a. Semigroup a => a -> a -> a
(<>)

-- | How PVP bounds should be added to .cabal files

data PvpBoundsType
  = PvpBoundsNone
  | PvpBoundsUpper
  | PvpBoundsLower
  | PvpBoundsBoth
  deriving (Int -> PvpBoundsType -> ShowS
[PvpBoundsType] -> ShowS
PvpBoundsType -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PvpBoundsType] -> ShowS
$cshowList :: [PvpBoundsType] -> ShowS
show :: PvpBoundsType -> [Char]
$cshow :: PvpBoundsType -> [Char]
showsPrec :: Int -> PvpBoundsType -> ShowS
$cshowsPrec :: Int -> PvpBoundsType -> ShowS
Show, ReadPrec [PvpBoundsType]
ReadPrec PvpBoundsType
Int -> ReadS PvpBoundsType
ReadS [PvpBoundsType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PvpBoundsType]
$creadListPrec :: ReadPrec [PvpBoundsType]
readPrec :: ReadPrec PvpBoundsType
$creadPrec :: ReadPrec PvpBoundsType
readList :: ReadS [PvpBoundsType]
$creadList :: ReadS [PvpBoundsType]
readsPrec :: Int -> ReadS PvpBoundsType
$creadsPrec :: Int -> ReadS PvpBoundsType
Read, PvpBoundsType -> PvpBoundsType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PvpBoundsType -> PvpBoundsType -> Bool
$c/= :: PvpBoundsType -> PvpBoundsType -> Bool
== :: PvpBoundsType -> PvpBoundsType -> Bool
$c== :: PvpBoundsType -> PvpBoundsType -> Bool
Eq, Typeable, Eq PvpBoundsType
PvpBoundsType -> PvpBoundsType -> Bool
PvpBoundsType -> PvpBoundsType -> Ordering
PvpBoundsType -> PvpBoundsType -> PvpBoundsType
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 :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType
$cmin :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType
max :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType
$cmax :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType
>= :: PvpBoundsType -> PvpBoundsType -> Bool
$c>= :: PvpBoundsType -> PvpBoundsType -> Bool
> :: PvpBoundsType -> PvpBoundsType -> Bool
$c> :: PvpBoundsType -> PvpBoundsType -> Bool
<= :: PvpBoundsType -> PvpBoundsType -> Bool
$c<= :: PvpBoundsType -> PvpBoundsType -> Bool
< :: PvpBoundsType -> PvpBoundsType -> Bool
$c< :: PvpBoundsType -> PvpBoundsType -> Bool
compare :: PvpBoundsType -> PvpBoundsType -> Ordering
$ccompare :: PvpBoundsType -> PvpBoundsType -> Ordering
Ord, Int -> PvpBoundsType
PvpBoundsType -> Int
PvpBoundsType -> [PvpBoundsType]
PvpBoundsType -> PvpBoundsType
PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
PvpBoundsType -> PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
$cenumFromThenTo :: PvpBoundsType -> PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
enumFromTo :: PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
$cenumFromTo :: PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
enumFromThen :: PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
$cenumFromThen :: PvpBoundsType -> PvpBoundsType -> [PvpBoundsType]
enumFrom :: PvpBoundsType -> [PvpBoundsType]
$cenumFrom :: PvpBoundsType -> [PvpBoundsType]
fromEnum :: PvpBoundsType -> Int
$cfromEnum :: PvpBoundsType -> Int
toEnum :: Int -> PvpBoundsType
$ctoEnum :: Int -> PvpBoundsType
pred :: PvpBoundsType -> PvpBoundsType
$cpred :: PvpBoundsType -> PvpBoundsType
succ :: PvpBoundsType -> PvpBoundsType
$csucc :: PvpBoundsType -> PvpBoundsType
Enum, PvpBoundsType
forall a. a -> a -> Bounded a
maxBound :: PvpBoundsType
$cmaxBound :: PvpBoundsType
minBound :: PvpBoundsType
$cminBound :: PvpBoundsType
Bounded)

data PvpBounds = PvpBounds
  { PvpBounds -> PvpBoundsType
pbType :: !PvpBoundsType
  , PvpBounds -> Bool
pbAsRevision :: !Bool
  }
  deriving (Int -> PvpBounds -> ShowS
[PvpBounds] -> ShowS
PvpBounds -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PvpBounds] -> ShowS
$cshowList :: [PvpBounds] -> ShowS
show :: PvpBounds -> [Char]
$cshow :: PvpBounds -> [Char]
showsPrec :: Int -> PvpBounds -> ShowS
$cshowsPrec :: Int -> PvpBounds -> ShowS
Show, ReadPrec [PvpBounds]
ReadPrec PvpBounds
Int -> ReadS PvpBounds
ReadS [PvpBounds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PvpBounds]
$creadListPrec :: ReadPrec [PvpBounds]
readPrec :: ReadPrec PvpBounds
$creadPrec :: ReadPrec PvpBounds
readList :: ReadS [PvpBounds]
$creadList :: ReadS [PvpBounds]
readsPrec :: Int -> ReadS PvpBounds
$creadsPrec :: Int -> ReadS PvpBounds
Read, PvpBounds -> PvpBounds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PvpBounds -> PvpBounds -> Bool
$c/= :: PvpBounds -> PvpBounds -> Bool
== :: PvpBounds -> PvpBounds -> Bool
$c== :: PvpBounds -> PvpBounds -> Bool
Eq, Typeable, Eq PvpBounds
PvpBounds -> PvpBounds -> Bool
PvpBounds -> PvpBounds -> Ordering
PvpBounds -> PvpBounds -> PvpBounds
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 :: PvpBounds -> PvpBounds -> PvpBounds
$cmin :: PvpBounds -> PvpBounds -> PvpBounds
max :: PvpBounds -> PvpBounds -> PvpBounds
$cmax :: PvpBounds -> PvpBounds -> PvpBounds
>= :: PvpBounds -> PvpBounds -> Bool
$c>= :: PvpBounds -> PvpBounds -> Bool
> :: PvpBounds -> PvpBounds -> Bool
$c> :: PvpBounds -> PvpBounds -> Bool
<= :: PvpBounds -> PvpBounds -> Bool
$c<= :: PvpBounds -> PvpBounds -> Bool
< :: PvpBounds -> PvpBounds -> Bool
$c< :: PvpBounds -> PvpBounds -> Bool
compare :: PvpBounds -> PvpBounds -> Ordering
$ccompare :: PvpBounds -> PvpBounds -> Ordering
Ord)

pvpBoundsText :: PvpBoundsType -> Text
pvpBoundsText :: PvpBoundsType -> Text
pvpBoundsText PvpBoundsType
PvpBoundsNone = Text
"none"
pvpBoundsText PvpBoundsType
PvpBoundsUpper = Text
"upper"
pvpBoundsText PvpBoundsType
PvpBoundsLower = Text
"lower"
pvpBoundsText PvpBoundsType
PvpBoundsBoth = Text
"both"

parsePvpBounds :: Text -> Either String PvpBounds
parsePvpBounds :: Text -> Either [Char] PvpBounds
parsePvpBounds Text
t = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Either [Char] PvpBounds
err forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ do
    (Text
t', Bool
asRevision) <-
      case (Char -> Bool) -> Text -> (Text, Text)
T.break (forall a. Eq a => a -> a -> Bool
== Char
'-') Text
t of
        (Text
x, Text
"") -> forall a. a -> Maybe a
Just (Text
x, Bool
False)
        (Text
x, Text
"-revision") -> forall a. a -> Maybe a
Just (Text
x, Bool
True)
        (Text, Text)
_ -> forall a. Maybe a
Nothing
    PvpBoundsType
x <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
t' Map Text PvpBoundsType
m
    forall a. a -> Maybe a
Just PvpBounds
      { pbType :: PvpBoundsType
pbType = PvpBoundsType
x
      , pbAsRevision :: Bool
pbAsRevision = Bool
asRevision
      }
  where
    m :: Map Text PvpBoundsType
m = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (PvpBoundsType -> Text
pvpBoundsText forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall a. a -> a
id) [forall a. Bounded a => a
minBound..forall a. Bounded a => a
maxBound]
    err :: Either [Char] PvpBounds
err = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid PVP bounds: " forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack Text
t

instance ToJSON PvpBounds where
  toJSON :: PvpBounds -> Value
toJSON (PvpBounds PvpBoundsType
typ Bool
asRevision) =
    forall a. ToJSON a => a -> Value
toJSON (PvpBoundsType -> Text
pvpBoundsText PvpBoundsType
typ forall a. Semigroup a => a -> a -> a
<> (if Bool
asRevision then Text
"-revision" else Text
""))
instance FromJSON PvpBounds where
  parseJSON :: Value -> Parser PvpBounds
parseJSON = forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText [Char]
"PvpBounds" (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either [Char] PvpBounds
parsePvpBounds)

-- | Data passed into Docker container for the Docker entrypoint's use

newtype DockerEntrypoint = DockerEntrypoint
    { DockerEntrypoint -> Maybe DockerUser
deUser :: Maybe DockerUser
      -- ^ UID/GID/etc of host user, if we wish to perform UID/GID switch in container

    } deriving (ReadPrec [DockerEntrypoint]
ReadPrec DockerEntrypoint
Int -> ReadS DockerEntrypoint
ReadS [DockerEntrypoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DockerEntrypoint]
$creadListPrec :: ReadPrec [DockerEntrypoint]
readPrec :: ReadPrec DockerEntrypoint
$creadPrec :: ReadPrec DockerEntrypoint
readList :: ReadS [DockerEntrypoint]
$creadList :: ReadS [DockerEntrypoint]
readsPrec :: Int -> ReadS DockerEntrypoint
$creadsPrec :: Int -> ReadS DockerEntrypoint
Read,Int -> DockerEntrypoint -> ShowS
[DockerEntrypoint] -> ShowS
DockerEntrypoint -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DockerEntrypoint] -> ShowS
$cshowList :: [DockerEntrypoint] -> ShowS
show :: DockerEntrypoint -> [Char]
$cshow :: DockerEntrypoint -> [Char]
showsPrec :: Int -> DockerEntrypoint -> ShowS
$cshowsPrec :: Int -> DockerEntrypoint -> ShowS
Show)

-- | Docker host user info

data DockerUser = DockerUser
    { DockerUser -> UserID
duUid :: UserID -- ^ uid

    , DockerUser -> GroupID
duGid :: GroupID -- ^ gid

    , DockerUser -> [GroupID]
duGroups :: [GroupID] -- ^ Supplemental groups

    , DockerUser -> FileMode
duUmask :: FileMode -- ^ File creation mask }

    } deriving (ReadPrec [DockerUser]
ReadPrec DockerUser
Int -> ReadS DockerUser
ReadS [DockerUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DockerUser]
$creadListPrec :: ReadPrec [DockerUser]
readPrec :: ReadPrec DockerUser
$creadPrec :: ReadPrec DockerUser
readList :: ReadS [DockerUser]
$creadList :: ReadS [DockerUser]
readsPrec :: Int -> ReadS DockerUser
$creadsPrec :: Int -> ReadS DockerUser
Read,Int -> DockerUser -> ShowS
[DockerUser] -> ShowS
DockerUser -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DockerUser] -> ShowS
$cshowList :: [DockerUser] -> ShowS
show :: DockerUser -> [Char]
$cshow :: DockerUser -> [Char]
showsPrec :: Int -> DockerUser -> ShowS
$cshowsPrec :: Int -> DockerUser -> ShowS
Show)

data GhcOptionKey
  = GOKOldEverything
  | GOKEverything
  | GOKLocals
  | GOKTargets
  | GOKPackage !PackageName
  deriving (GhcOptionKey -> GhcOptionKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcOptionKey -> GhcOptionKey -> Bool
$c/= :: GhcOptionKey -> GhcOptionKey -> Bool
== :: GhcOptionKey -> GhcOptionKey -> Bool
$c== :: GhcOptionKey -> GhcOptionKey -> Bool
Eq, Eq GhcOptionKey
GhcOptionKey -> GhcOptionKey -> Bool
GhcOptionKey -> GhcOptionKey -> Ordering
GhcOptionKey -> GhcOptionKey -> GhcOptionKey
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 :: GhcOptionKey -> GhcOptionKey -> GhcOptionKey
$cmin :: GhcOptionKey -> GhcOptionKey -> GhcOptionKey
max :: GhcOptionKey -> GhcOptionKey -> GhcOptionKey
$cmax :: GhcOptionKey -> GhcOptionKey -> GhcOptionKey
>= :: GhcOptionKey -> GhcOptionKey -> Bool
$c>= :: GhcOptionKey -> GhcOptionKey -> Bool
> :: GhcOptionKey -> GhcOptionKey -> Bool
$c> :: GhcOptionKey -> GhcOptionKey -> Bool
<= :: GhcOptionKey -> GhcOptionKey -> Bool
$c<= :: GhcOptionKey -> GhcOptionKey -> Bool
< :: GhcOptionKey -> GhcOptionKey -> Bool
$c< :: GhcOptionKey -> GhcOptionKey -> Bool
compare :: GhcOptionKey -> GhcOptionKey -> Ordering
$ccompare :: GhcOptionKey -> GhcOptionKey -> Ordering
Ord)

instance FromJSONKey GhcOptionKey where
  fromJSONKey :: FromJSONKeyFunction GhcOptionKey
fromJSONKey = forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser forall a b. (a -> b) -> a -> b
$ \Text
t ->
    case Text
t of
      Text
"*" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GhcOptionKey
GOKOldEverything
      Text
"$everything" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GhcOptionKey
GOKEverything
      Text
"$locals" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GhcOptionKey
GOKLocals
      Text
"$targets" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GhcOptionKey
GOKTargets
      Text
_ ->
        case [Char] -> Maybe PackageName
parsePackageName forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
t of
          Maybe PackageName
Nothing -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid package name: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
t
          Just PackageName
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PackageName -> GhcOptionKey
GOKPackage PackageName
x
  fromJSONKeyList :: FromJSONKeyFunction [GhcOptionKey]
fromJSONKeyList = forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser forall a b. (a -> b) -> a -> b
$ \Text
_ -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"GhcOptionKey.fromJSONKeyList"

newtype GhcOptions = GhcOptions { GhcOptions -> [Text]
unGhcOptions :: [Text] }

instance FromJSON GhcOptions where
  parseJSON :: Value -> Parser GhcOptions
parseJSON = forall a. [Char] -> (Text -> Parser a) -> Value -> Parser a
withText [Char]
"GhcOptions" forall a b. (a -> b) -> a -> b
$ \Text
t ->
    case EscapingMode -> Text -> Either [Char] [[Char]]
parseArgs EscapingMode
Escaping Text
t of
      Left [Char]
e -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
e
      Right [[Char]]
opts -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [Text] -> GhcOptions
GhcOptions forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Text
T.pack [[Char]]
opts

-----------------------------------

-- Lens classes

-----------------------------------


-- | Class for environment values which have a Platform

class HasPlatform env where
    platformL :: Lens' env Platform
    default platformL :: HasConfig env => Lens' env Platform
    platformL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasPlatform env => Lens' env Platform
platformL
    {-# INLINE platformL #-}
    platformVariantL :: Lens' env PlatformVariant
    default platformVariantL :: HasConfig env => Lens' env PlatformVariant
    platformVariantL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasPlatform env => Lens' env PlatformVariant
platformVariantL
    {-# INLINE platformVariantL #-}

-- | Class for environment values which have a GHCVariant

class HasGHCVariant env where
    ghcVariantL :: SimpleGetter env GHCVariant
    default ghcVariantL :: HasConfig env => SimpleGetter env GHCVariant
    ghcVariantL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasGHCVariant env => SimpleGetter env GHCVariant
ghcVariantL
    {-# INLINE ghcVariantL #-}

-- | Class for environment values which have a 'Runner'.

class (HasProcessContext env, HasLogFunc env) => HasRunner env where
  runnerL :: Lens' env Runner
instance HasLogFunc Runner where
  logFuncL :: Lens' Runner LogFunc
logFuncL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Runner -> LogFunc
runnerLogFunc (\Runner
x LogFunc
y -> Runner
x { runnerLogFunc :: LogFunc
runnerLogFunc = LogFunc
y })
instance HasProcessContext Runner where
  processContextL :: Lens' Runner ProcessContext
processContextL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Runner -> ProcessContext
runnerProcessContext (\Runner
x ProcessContext
y -> Runner
x { runnerProcessContext :: ProcessContext
runnerProcessContext = ProcessContext
y })
instance HasRunner Runner where
  runnerL :: Lens' Runner Runner
runnerL = forall a. a -> a
id
instance HasStylesUpdate Runner where
  stylesUpdateL :: Lens' Runner StylesUpdate
stylesUpdateL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GlobalOpts -> StylesUpdate
globalStylesUpdate (\GlobalOpts
x StylesUpdate
y -> GlobalOpts
x { globalStylesUpdate :: StylesUpdate
globalStylesUpdate = StylesUpdate
y })
instance HasTerm Runner where
  useColorL :: Lens' Runner Bool
useColorL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Runner -> Bool
runnerUseColor (\Runner
x Bool
y -> Runner
x { runnerUseColor :: Bool
runnerUseColor = Bool
y })
  termWidthL :: Lens' Runner Int
termWidthL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Runner -> Int
runnerTermWidth (\Runner
x Int
y -> Runner
x { runnerTermWidth :: Int
runnerTermWidth = Int
y })

globalOptsL :: HasRunner env => Lens' env GlobalOpts
globalOptsL :: forall env. HasRunner env => Lens' env GlobalOpts
globalOptsL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Runner -> GlobalOpts
runnerGlobalOpts (\Runner
x GlobalOpts
y -> Runner
x { runnerGlobalOpts :: GlobalOpts
runnerGlobalOpts = GlobalOpts
y })

-- | Class for environment values that can provide a 'Config'.

class ( HasPlatform env, HasGHCVariant env, HasProcessContext env, HasPantryConfig env, HasTerm env, HasRunner env) => HasConfig env where
    configL :: Lens' env Config
    default configL :: HasBuildConfig env => Lens' env Config
    configL = forall env. HasBuildConfig env => Lens' env BuildConfig
buildConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BuildConfig -> Config
bcConfig (\BuildConfig
x Config
y -> BuildConfig
x { bcConfig :: Config
bcConfig = Config
y })
    {-# INLINE configL #-}

class HasConfig env => HasBuildConfig env where
    buildConfigL :: Lens' env BuildConfig
    default buildConfigL :: HasEnvConfig env => Lens' env BuildConfig
    buildConfigL = forall env. HasEnvConfig env => Lens' env EnvConfig
envConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
        EnvConfig -> BuildConfig
envConfigBuildConfig
        (\EnvConfig
x BuildConfig
y -> EnvConfig
x { envConfigBuildConfig :: BuildConfig
envConfigBuildConfig = BuildConfig
y })

class (HasBuildConfig env, HasSourceMap env, HasCompiler env) => HasEnvConfig env where
    envConfigL :: Lens' env EnvConfig

-----------------------------------

-- Lens instances

-----------------------------------


instance HasPlatform (Platform,PlatformVariant) where
    platformL :: Lens' (Platform, PlatformVariant) Platform
platformL = forall s t a b. Field1 s t a b => Lens s t a b
_1
    platformVariantL :: Lens' (Platform, PlatformVariant) PlatformVariant
platformVariantL = forall s t a b. Field2 s t a b => Lens s t a b
_2
instance HasPlatform Config where
    platformL :: Lens' Config Platform
platformL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> Platform
configPlatform (\Config
x Platform
y -> Config
x { configPlatform :: Platform
configPlatform = Platform
y })
    platformVariantL :: Lens' Config PlatformVariant
platformVariantL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> PlatformVariant
configPlatformVariant (\Config
x PlatformVariant
y -> Config
x { configPlatformVariant :: PlatformVariant
configPlatformVariant = PlatformVariant
y })
instance HasPlatform BuildConfig
instance HasPlatform EnvConfig

instance HasGHCVariant GHCVariant where
    ghcVariantL :: SimpleGetter GHCVariant GHCVariant
ghcVariantL = forall a. a -> a
id
    {-# INLINE ghcVariantL #-}
instance HasGHCVariant Config where
    ghcVariantL :: SimpleGetter Config GHCVariant
ghcVariantL = forall s a. (s -> a) -> SimpleGetter s a
to forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe GHCVariant
GHCStandard forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Maybe GHCVariant
configGHCVariant
instance HasGHCVariant BuildConfig
instance HasGHCVariant EnvConfig

instance HasProcessContext Config where
    processContextL :: Lens' Config ProcessContext
processContextL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasProcessContext env => Lens' env ProcessContext
processContextL
instance HasProcessContext BuildConfig where
    processContextL :: Lens' BuildConfig ProcessContext
processContextL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasProcessContext env => Lens' env ProcessContext
processContextL
instance HasProcessContext EnvConfig where
    processContextL :: Lens' EnvConfig ProcessContext
processContextL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasProcessContext env => Lens' env ProcessContext
processContextL

instance HasPantryConfig Config where
    pantryConfigL :: Lens' Config PantryConfig
pantryConfigL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> PantryConfig
configPantryConfig (\Config
x PantryConfig
y -> Config
x { configPantryConfig :: PantryConfig
configPantryConfig = PantryConfig
y })
instance HasPantryConfig BuildConfig where
    pantryConfigL :: Lens' BuildConfig PantryConfig
pantryConfigL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasPantryConfig env => Lens' env PantryConfig
pantryConfigL
instance HasPantryConfig EnvConfig where
    pantryConfigL :: Lens' EnvConfig PantryConfig
pantryConfigL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasPantryConfig env => Lens' env PantryConfig
pantryConfigL

instance HasConfig Config where
    configL :: Lens' Config Config
configL = forall a. a -> a
id
    {-# INLINE configL #-}
instance HasConfig BuildConfig where
    configL :: Lens' BuildConfig Config
configL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BuildConfig -> Config
bcConfig (\BuildConfig
x Config
y -> BuildConfig
x { bcConfig :: Config
bcConfig = Config
y })
instance HasConfig EnvConfig

instance HasBuildConfig BuildConfig where
    buildConfigL :: Lens' BuildConfig BuildConfig
buildConfigL = forall a. a -> a
id
    {-# INLINE buildConfigL #-}
instance HasBuildConfig EnvConfig

instance HasCompiler EnvConfig where
    compilerPathsL :: SimpleGetter EnvConfig CompilerPaths
compilerPathsL = forall s a. (s -> a) -> SimpleGetter s a
to EnvConfig -> CompilerPaths
envConfigCompilerPaths
instance HasEnvConfig EnvConfig where
    envConfigL :: Lens' EnvConfig EnvConfig
envConfigL = forall a. a -> a
id
    {-# INLINE envConfigL #-}

instance HasRunner Config where
  runnerL :: Lens' Config Runner
runnerL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> Runner
configRunner (\Config
x Runner
y -> Config
x { configRunner :: Runner
configRunner = Runner
y })
instance HasRunner BuildConfig where
  runnerL :: Lens' BuildConfig Runner
runnerL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasRunner env => Lens' env Runner
runnerL
instance HasRunner EnvConfig where
  runnerL :: Lens' EnvConfig Runner
runnerL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasRunner env => Lens' env Runner
runnerL

instance HasLogFunc Config where
  logFuncL :: Lens' Config LogFunc
logFuncL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasLogFunc env => Lens' env LogFunc
logFuncL
instance HasLogFunc BuildConfig where
  logFuncL :: Lens' BuildConfig LogFunc
logFuncL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasLogFunc env => Lens' env LogFunc
logFuncL
instance HasLogFunc EnvConfig where
  logFuncL :: Lens' EnvConfig LogFunc
logFuncL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasLogFunc env => Lens' env LogFunc
logFuncL

instance HasStylesUpdate Config where
  stylesUpdateL :: Lens' Config StylesUpdate
stylesUpdateL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasStylesUpdate env => Lens' env StylesUpdate
stylesUpdateL
instance HasStylesUpdate BuildConfig where
  stylesUpdateL :: Lens' BuildConfig StylesUpdate
stylesUpdateL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasStylesUpdate env => Lens' env StylesUpdate
stylesUpdateL
instance HasStylesUpdate EnvConfig where
  stylesUpdateL :: Lens' EnvConfig StylesUpdate
stylesUpdateL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasStylesUpdate env => Lens' env StylesUpdate
stylesUpdateL

instance HasTerm Config where
  useColorL :: Lens' Config Bool
useColorL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Bool
useColorL
  termWidthL :: Lens' Config Int
termWidthL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Int
termWidthL
instance HasTerm BuildConfig where
  useColorL :: Lens' BuildConfig Bool
useColorL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Bool
useColorL
  termWidthL :: Lens' BuildConfig Int
termWidthL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Int
termWidthL
instance HasTerm EnvConfig where
  useColorL :: Lens' EnvConfig Bool
useColorL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Bool
useColorL
  termWidthL :: Lens' EnvConfig Int
termWidthL = forall env. HasRunner env => Lens' env Runner
runnerLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall env. HasTerm env => Lens' env Int
termWidthL

-----------------------------------

-- Helper lenses

-----------------------------------


stackRootL :: HasConfig s => Lens' s (Path Abs Dir)
stackRootL :: forall s. HasConfig s => Lens' s (Path Abs Dir)
stackRootL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> Path Abs Dir
configStackRoot (\Config
x Path Abs Dir
y -> Config
x { configStackRoot :: Path Abs Dir
configStackRoot = Path Abs Dir
y })

stackGlobalConfigL :: HasConfig s => Lens' s (Path Abs File)
stackGlobalConfigL :: forall s. HasConfig s => Lens' s (Path Abs File)
stackGlobalConfigL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Config -> Path Abs File
configUserConfigPath (\Config
x Path Abs File
y -> Config
x { configUserConfigPath :: Path Abs File
configUserConfigPath = Path Abs File
y })

-- | The compiler specified by the @SnapshotDef@. This may be

-- different from the actual compiler used!

wantedCompilerVersionL :: HasBuildConfig s => Getting r s WantedCompiler
wantedCompilerVersionL :: forall s r. HasBuildConfig s => Getting r s WantedCompiler
wantedCompilerVersionL = forall env. HasBuildConfig env => Lens' env BuildConfig
buildConfigLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to (SMWanted -> WantedCompiler
smwCompiler forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildConfig -> SMWanted
bcSMWanted)

-- | Location of the ghc-pkg executable

newtype GhcPkgExe = GhcPkgExe (Path Abs File)
  deriving Int -> GhcPkgExe -> ShowS
[GhcPkgExe] -> ShowS
GhcPkgExe -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GhcPkgExe] -> ShowS
$cshowList :: [GhcPkgExe] -> ShowS
show :: GhcPkgExe -> [Char]
$cshow :: GhcPkgExe -> [Char]
showsPrec :: Int -> GhcPkgExe -> ShowS
$cshowsPrec :: Int -> GhcPkgExe -> ShowS
Show

-- | Get the 'GhcPkgExe' from a 'HasCompiler' environment

getGhcPkgExe :: HasCompiler env => RIO env GhcPkgExe
getGhcPkgExe :: forall env. HasCompiler env => RIO env GhcPkgExe
getGhcPkgExe = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasCompiler env => SimpleGetter env CompilerPaths
compilerPathsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to CompilerPaths -> GhcPkgExe
cpPkg

-- | Dump information for a single package

data DumpPackage = DumpPackage
    { DumpPackage -> GhcPkgId
dpGhcPkgId :: !GhcPkgId
    , DumpPackage -> PackageIdentifier
dpPackageIdent :: !PackageIdentifier
    , DumpPackage -> Maybe PackageIdentifier
dpParentLibIdent :: !(Maybe PackageIdentifier)
    , DumpPackage -> Maybe License
dpLicense :: !(Maybe C.License)
    , DumpPackage -> [[Char]]
dpLibDirs :: ![FilePath]
    , DumpPackage -> [Text]
dpLibraries :: ![Text]
    , DumpPackage -> Bool
dpHasExposedModules :: !Bool
    , DumpPackage -> Set ModuleName
dpExposedModules :: !(Set ModuleName)
    , DumpPackage -> [GhcPkgId]
dpDepends :: ![GhcPkgId]
    , DumpPackage -> [[Char]]
dpHaddockInterfaces :: ![FilePath]
    , DumpPackage -> Maybe [Char]
dpHaddockHtml :: !(Maybe FilePath)
    , DumpPackage -> Bool
dpIsExposed :: !Bool
    }
    deriving (Int -> DumpPackage -> ShowS
[DumpPackage] -> ShowS
DumpPackage -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DumpPackage] -> ShowS
$cshowList :: [DumpPackage] -> ShowS
show :: DumpPackage -> [Char]
$cshow :: DumpPackage -> [Char]
showsPrec :: Int -> DumpPackage -> ShowS
$cshowsPrec :: Int -> DumpPackage -> ShowS
Show, ReadPrec [DumpPackage]
ReadPrec DumpPackage
Int -> ReadS DumpPackage
ReadS [DumpPackage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DumpPackage]
$creadListPrec :: ReadPrec [DumpPackage]
readPrec :: ReadPrec DumpPackage
$creadPrec :: ReadPrec DumpPackage
readList :: ReadS [DumpPackage]
$creadList :: ReadS [DumpPackage]
readsPrec :: Int -> ReadS DumpPackage
$creadsPrec :: Int -> ReadS DumpPackage
Read, DumpPackage -> DumpPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DumpPackage -> DumpPackage -> Bool
$c/= :: DumpPackage -> DumpPackage -> Bool
== :: DumpPackage -> DumpPackage -> Bool
$c== :: DumpPackage -> DumpPackage -> Bool
Eq)

-- | Paths on the filesystem for the compiler we're using

data CompilerPaths = CompilerPaths
  { CompilerPaths -> ActualCompiler
cpCompilerVersion :: !ActualCompiler
  , CompilerPaths -> Arch
cpArch :: !Arch
  , CompilerPaths -> CompilerBuild
cpBuild :: !CompilerBuild
  , CompilerPaths -> Path Abs File
cpCompiler :: !(Path Abs File)
  -- | ghc-pkg or equivalent

  , CompilerPaths -> GhcPkgExe
cpPkg :: !GhcPkgExe
  -- | runghc

  , CompilerPaths -> Path Abs File
cpInterpreter :: !(Path Abs File)
  -- | haddock, in 'IO' to allow deferring the lookup

  , CompilerPaths -> Path Abs File
cpHaddock :: !(Path Abs File)
  -- | Is this a Stack-sandboxed installation?

  , CompilerPaths -> Bool
cpSandboxed :: !Bool
  , CompilerPaths -> Version
cpCabalVersion :: !Version
  -- ^ This is the version of Cabal that Stack will use to compile Setup.hs files

  -- in the build process.

  --

  -- Note that this is not necessarily the same version as the one that Stack

  -- depends on as a library and which is displayed when running

  -- @stack ls dependencies | grep Cabal@ in the Stack project.

  , CompilerPaths -> Path Abs Dir
cpGlobalDB :: !(Path Abs Dir)
  -- ^ Global package database

  , CompilerPaths -> ByteString
cpGhcInfo :: !ByteString
  -- ^ Output of @ghc --info@

  , CompilerPaths -> Map PackageName DumpPackage
cpGlobalDump :: !(Map PackageName DumpPackage)
  }
  deriving Int -> CompilerPaths -> ShowS
[CompilerPaths] -> ShowS
CompilerPaths -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CompilerPaths] -> ShowS
$cshowList :: [CompilerPaths] -> ShowS
show :: CompilerPaths -> [Char]
$cshow :: CompilerPaths -> [Char]
showsPrec :: Int -> CompilerPaths -> ShowS
$cshowsPrec :: Int -> CompilerPaths -> ShowS
Show

cpWhich :: (MonadReader env m, HasCompiler env) => m WhichCompiler
cpWhich :: forall env (m :: * -> *).
(MonadReader env m, HasCompiler env) =>
m WhichCompiler
cpWhich = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasCompiler env => SimpleGetter env CompilerPaths
compilerPathsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to (ActualCompiler -> WhichCompiler
whichCompilerforall b c a. (b -> c) -> (a -> b) -> a -> c
.CompilerPaths -> ActualCompiler
cpCompilerVersion)

data ExtraDirs = ExtraDirs
    { ExtraDirs -> [Path Abs Dir]
edBins :: ![Path Abs Dir]
    , ExtraDirs -> [Path Abs Dir]
edInclude :: ![Path Abs Dir]
    , ExtraDirs -> [Path Abs Dir]
edLib :: ![Path Abs Dir]
    } deriving (Int -> ExtraDirs -> ShowS
[ExtraDirs] -> ShowS
ExtraDirs -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ExtraDirs] -> ShowS
$cshowList :: [ExtraDirs] -> ShowS
show :: ExtraDirs -> [Char]
$cshow :: ExtraDirs -> [Char]
showsPrec :: Int -> ExtraDirs -> ShowS
$cshowsPrec :: Int -> ExtraDirs -> ShowS
Show, forall x. Rep ExtraDirs x -> ExtraDirs
forall x. ExtraDirs -> Rep ExtraDirs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExtraDirs x -> ExtraDirs
$cfrom :: forall x. ExtraDirs -> Rep ExtraDirs x
Generic)
instance Semigroup ExtraDirs where
    <> :: ExtraDirs -> ExtraDirs -> ExtraDirs
(<>) = forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault
instance Monoid ExtraDirs where
    mempty :: ExtraDirs
mempty = forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
    mappend :: ExtraDirs -> ExtraDirs -> ExtraDirs
mappend = forall a. Semigroup a => a -> a -> a
(<>)

-- | An environment which ensures that the given compiler is available

-- on the PATH

class HasCompiler env where
  compilerPathsL :: SimpleGetter env CompilerPaths
instance HasCompiler CompilerPaths where
  compilerPathsL :: SimpleGetter CompilerPaths CompilerPaths
compilerPathsL = forall a. a -> a
id

class HasSourceMap env where
  sourceMapL :: Lens' env SourceMap
instance HasSourceMap EnvConfig where
  sourceMapL :: Lens' EnvConfig SourceMap
sourceMapL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens EnvConfig -> SourceMap
envConfigSourceMap (\EnvConfig
x SourceMap
y -> EnvConfig
x { envConfigSourceMap :: SourceMap
envConfigSourceMap = SourceMap
y })

-- | The version of the compiler which will actually be used. May be

-- different than that specified in the 'SnapshotDef' and returned

-- by 'wantedCompilerVersionL'.

actualCompilerVersionL :: HasSourceMap env => SimpleGetter env ActualCompiler
actualCompilerVersionL :: forall env. HasSourceMap env => SimpleGetter env ActualCompiler
actualCompilerVersionL = forall env. HasSourceMap env => Lens' env SourceMap
sourceMapLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to SourceMap -> ActualCompiler
smCompiler

buildOptsL :: HasConfig s => Lens' s BuildOpts
buildOptsL :: forall s. HasConfig s => Lens' s BuildOpts
buildOptsL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
    Config -> BuildOpts
configBuild
    (\Config
x BuildOpts
y -> Config
x { configBuild :: BuildOpts
configBuild = BuildOpts
y })

buildOptsMonoidHaddockL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidHaddockL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidHaddockL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (FirstFalse -> Maybe Bool
getFirstFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildOptsMonoid -> FirstFalse
buildMonoidHaddock)
                            (\BuildOptsMonoid
buildMonoid Maybe Bool
t -> BuildOptsMonoid
buildMonoid {buildMonoidHaddock :: FirstFalse
buildMonoidHaddock = Maybe Bool -> FirstFalse
FirstFalse Maybe Bool
t})

buildOptsMonoidTestsL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidTestsL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidTestsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (FirstFalse -> Maybe Bool
getFirstFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildOptsMonoid -> FirstFalse
buildMonoidTests)
                            (\BuildOptsMonoid
buildMonoid Maybe Bool
t -> BuildOptsMonoid
buildMonoid {buildMonoidTests :: FirstFalse
buildMonoidTests = Maybe Bool -> FirstFalse
FirstFalse Maybe Bool
t})

buildOptsMonoidBenchmarksL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidBenchmarksL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidBenchmarksL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (FirstFalse -> Maybe Bool
getFirstFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildOptsMonoid -> FirstFalse
buildMonoidBenchmarks)
                            (\BuildOptsMonoid
buildMonoid Maybe Bool
t -> BuildOptsMonoid
buildMonoid {buildMonoidBenchmarks :: FirstFalse
buildMonoidBenchmarks = Maybe Bool -> FirstFalse
FirstFalse Maybe Bool
t})

buildOptsMonoidInstallExesL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidInstallExesL :: Lens' BuildOptsMonoid (Maybe Bool)
buildOptsMonoidInstallExesL =
  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (FirstFalse -> Maybe Bool
getFirstFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildOptsMonoid -> FirstFalse
buildMonoidInstallExes)
       (\BuildOptsMonoid
buildMonoid Maybe Bool
t -> BuildOptsMonoid
buildMonoid {buildMonoidInstallExes :: FirstFalse
buildMonoidInstallExes = Maybe Bool -> FirstFalse
FirstFalse Maybe Bool
t})

buildOptsInstallExesL :: Lens' BuildOpts Bool
buildOptsInstallExesL :: Lens' BuildOpts Bool
buildOptsInstallExesL =
  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BuildOpts -> Bool
boptsInstallExes
       (\BuildOpts
bopts Bool
t -> BuildOpts
bopts {boptsInstallExes :: Bool
boptsInstallExes = Bool
t})

buildOptsHaddockL :: Lens' BuildOpts Bool
buildOptsHaddockL :: Lens' BuildOpts Bool
buildOptsHaddockL =
  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens BuildOpts -> Bool
boptsHaddock
       (\BuildOpts
bopts Bool
t -> BuildOpts
bopts {boptsHaddock :: Bool
boptsHaddock = Bool
t})

globalOptsBuildOptsMonoidL :: Lens' GlobalOpts BuildOptsMonoid
globalOptsBuildOptsMonoidL :: Lens' GlobalOpts BuildOptsMonoid
globalOptsBuildOptsMonoidL =
  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
    GlobalOpts -> ConfigMonoid
globalConfigMonoid
    (\GlobalOpts
x ConfigMonoid
y -> GlobalOpts
x { globalConfigMonoid :: ConfigMonoid
globalConfigMonoid = ConfigMonoid
y })
  forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
    ConfigMonoid -> BuildOptsMonoid
configMonoidBuildOpts
    (\ConfigMonoid
x BuildOptsMonoid
y -> ConfigMonoid
x { configMonoidBuildOpts :: BuildOptsMonoid
configMonoidBuildOpts = BuildOptsMonoid
y })

cabalVersionL :: HasCompiler env => SimpleGetter env Version
cabalVersionL :: forall env. HasCompiler env => SimpleGetter env Version
cabalVersionL = forall env. HasCompiler env => SimpleGetter env CompilerPaths
compilerPathsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to CompilerPaths -> Version
cpCabalVersion

whichCompilerL :: Getting r ActualCompiler WhichCompiler
whichCompilerL :: forall r. Getting r ActualCompiler WhichCompiler
whichCompilerL = forall s a. (s -> a) -> SimpleGetter s a
to ActualCompiler -> WhichCompiler
whichCompiler

envOverrideSettingsL :: HasConfig env => Lens' env (EnvSettings -> IO ProcessContext)
envOverrideSettingsL :: forall env.
HasConfig env =>
Lens' env (EnvSettings -> IO ProcessContext)
envOverrideSettingsL = forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
    Config -> EnvSettings -> IO ProcessContext
configProcessContextSettings
    (\Config
x EnvSettings -> IO ProcessContext
y -> Config
x { configProcessContextSettings :: EnvSettings -> IO ProcessContext
configProcessContextSettings = EnvSettings -> IO ProcessContext
y })

shouldForceGhcColorFlag :: (HasRunner env, HasEnvConfig env)
                        => RIO env Bool
shouldForceGhcColorFlag :: forall env. (HasRunner env, HasEnvConfig env) => RIO env Bool
shouldForceGhcColorFlag = do
    Bool
canDoColor <- (forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
8, Int
2, Int
1]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActualCompiler -> Version
getGhcVersion
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasSourceMap env => SimpleGetter env ActualCompiler
actualCompilerVersionL
    Bool
shouldDoColor <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasTerm env => Lens' env Bool
useColorL
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
canDoColor Bool -> Bool -> Bool
&& Bool
shouldDoColor

appropriateGhcColorFlag :: (HasRunner env, HasEnvConfig env)
                        => RIO env (Maybe String)
appropriateGhcColorFlag :: forall env.
(HasRunner env, HasEnvConfig env) =>
RIO env (Maybe [Char])
appropriateGhcColorFlag = Bool -> Maybe [Char]
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall env. (HasRunner env, HasEnvConfig env) => RIO env Bool
shouldForceGhcColorFlag
  where f :: Bool -> Maybe [Char]
f Bool
True = forall a. a -> Maybe a
Just [Char]
ghcColorForceFlag
        f Bool
False = forall a. Maybe a
Nothing

-- | See 'globalTerminal'

terminalL :: HasRunner env => Lens' env Bool
terminalL :: forall env. HasRunner env => Lens' env Bool
terminalL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GlobalOpts -> Bool
globalTerminal (\GlobalOpts
x Bool
y -> GlobalOpts
x { globalTerminal :: Bool
globalTerminal = Bool
y })

-- | See 'globalReExecVersion'

reExecL :: HasRunner env => SimpleGetter env Bool
reExecL :: forall env. HasRunner env => SimpleGetter env Bool
reExecL = forall env. HasRunner env => Lens' env GlobalOpts
globalOptsLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to (forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalOpts -> Maybe [Char]
globalReExecVersion)

-- | In dev mode, print as a warning, otherwise as debug

prettyStackDevL :: HasConfig env => [StyleDoc] -> RIO env ()
prettyStackDevL :: forall env. HasConfig env => [StyleDoc] -> RIO env ()
prettyStackDevL [StyleDoc]
docs = do
  Config
config <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall env. HasConfig env => Lens' env Config
configL
  if Config -> Bool
configStackDeveloperMode Config
config
    then forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
[StyleDoc] -> m ()
prettyWarnL [StyleDoc]
docs
    else forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
[StyleDoc] -> m ()
prettyDebugL [StyleDoc]
docs