{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      :  Main
-- Copyright   :  (c) David Himmelstrup 2005
-- License     :  BSD-like
--
-- Maintainer  :  lemmih@gmail.com
-- Stability   :  provisional
-- Portability :  portable
--
-- Entry point to the default cabal-install front-end.
--
-- @since 3.10.0.0
module Distribution.Client.Main (main) where

import Distribution.Client.Setup
  ( ActAsSetupFlags (..)
  , BuildFlags (..)
  , CheckFlags (..)
  , CommonSetupFlags (..)
  , ConfigExFlags (..)
  , ConfigFlags (..)
  , FetchFlags (..)
  , FreezeFlags (..)
  , GetFlags (..)
  , GlobalFlags (..)
  , InfoFlags (..)
  , InitFlags (initHcPath, initVerbosity)
  , InstallFlags (..)
  , ListFlags (..)
  , ReportFlags (..)
  , UploadFlags (..)
  , UserConfigFlags (..)
  , actAsSetupCommand
  , benchmarkCommand
  , buildCommand
  , checkCommand
  , cleanCommand
  , configCompilerAux'
  , configPackageDB'
  , configureExCommand
  , copyCommand
  , defaultConfigExFlags
  , defaultInstallFlags
  , fetchCommand
  , filterCommonFlags
  , formatCommand
  , freezeCommand
  , genBoundsCommand
  , getCommand
  , globalCommand
  , haddockCommand
  , infoCommand
  , initCommand
  , installCommand
  , listCommand
  , listNeedsCompiler
  , manpageCommand
  , reconfigureCommand
  , registerCommand
  , replCommand
  , reportCommand
  , runCommand
  , testCommand
  , unpackCommand
  , uploadCommand
  , userConfigCommand
  , withRepoContext
  )
import Distribution.Simple.Setup
  ( BenchmarkFlags (..)
  , CleanFlags (..)
  , CopyFlags (..)
  , Flag (..)
  , HaddockFlags (..)
  , HaddockTarget (..)
  , HscolourFlags (..)
  , RegisterFlags (..)
  , ReplFlags (..)
  , TestFlags (..)
  , defaultHaddockFlags
  , flagToMaybe
  , fromFlag
  , fromFlagOrDefault
  , hscolourCommand
  , toFlag
  )

import Distribution.Client.Compat.Prelude hiding (get)
import Prelude ()

import Distribution.Client.Config
  ( SavedConfig (..)
  , createDefaultConfigFile
  , defaultConfigFile
  , getConfigFilePath
  , loadConfig
  , userConfigDiff
  , userConfigUpdate
  )
import qualified Distribution.Client.List as List
  ( info
  , list
  )
import Distribution.Client.SetupWrapper
  ( SetupScriptOptions (..)
  , defaultSetupScriptOptions
  , setupWrapper
  )
import Distribution.Client.Targets
  ( readUserTargets
  )

import qualified Distribution.Client.CmdBench as CmdBench
import qualified Distribution.Client.CmdBuild as CmdBuild
import qualified Distribution.Client.CmdClean as CmdClean
import qualified Distribution.Client.CmdConfigure as CmdConfigure
import qualified Distribution.Client.CmdExec as CmdExec
import qualified Distribution.Client.CmdFreeze as CmdFreeze
import qualified Distribution.Client.CmdHaddock as CmdHaddock
import qualified Distribution.Client.CmdHaddockProject as CmdHaddockProject
import qualified Distribution.Client.CmdInstall as CmdInstall
import Distribution.Client.CmdLegacy
import qualified Distribution.Client.CmdListBin as CmdListBin
import qualified Distribution.Client.CmdOutdated as CmdOutdated
import qualified Distribution.Client.CmdPath as CmdPath
import qualified Distribution.Client.CmdRepl as CmdRepl
import qualified Distribution.Client.CmdRun as CmdRun
import qualified Distribution.Client.CmdSdist as CmdSdist
import qualified Distribution.Client.CmdTest as CmdTest
import qualified Distribution.Client.CmdUpdate as CmdUpdate

import Distribution.Client.Check as Check (check)
import Distribution.Client.Configure (configure, writeConfigFlags)
import Distribution.Client.Fetch (fetch)
import Distribution.Client.Freeze (freeze)
import Distribution.Client.GenBounds (genBounds)
import Distribution.Client.Install (install)

-- import Distribution.Client.Clean            (clean)

import Distribution.Client.Get (get)
import Distribution.Client.Init (initCmd)
import Distribution.Client.Manpage (manpageCmd)
import Distribution.Client.ManpageFlags (ManpageFlags (..))
import Distribution.Client.Nix
  ( nixInstantiate
  , nixShell
  )
import Distribution.Client.Reconfigure (Check (..), reconfigure)
import Distribution.Client.Run (run, splitRunArgs)
import Distribution.Client.Sandbox
  ( findSavedDistPref
  , loadConfigOrSandboxConfig
  , updateInstallDirs
  )
import Distribution.Client.Signal
  ( installTerminationHandler
  )
import Distribution.Client.Tar (createTarGzFile)
import Distribution.Client.Types.Credentials (Password (..))
import qualified Distribution.Client.Upload as Upload
import Distribution.Client.Utils
  ( determineNumJobs
  , relaxEncodingErrors
  )
import Distribution.Client.Version
  ( cabalInstallVersion
  )

import Distribution.Package (packageId)
import Distribution.PackageDescription
  ( BuildType (..)
  , Executable (..)
  , buildable
  )

import Distribution.Client.Errors
import Distribution.Compat.ResponseFile
import qualified Distribution.Make as Make
import Distribution.PackageDescription.PrettyPrint
  ( writeGenericPackageDescription
  )
import qualified Distribution.Simple as Simple
import Distribution.Simple.Build
  ( startInterpreter
  )
import Distribution.Simple.Command
  ( Command
  , CommandParse (..)
  , CommandSpec (..)
  , CommandType (..)
  , CommandUI (..)
  , commandAddAction
  , commandFromSpec
  , commandShowOptions
  , commandsRunWithFallback
  , defaultCommandFallback
  , hiddenCommand
  )
import Distribution.Simple.Compiler (PackageDBStack, interpretPackageDBStack)
import Distribution.Simple.Configure
  ( ConfigStateFileError (..)
  , configCompilerAuxEx
  , getPersistBuildConfig
  , interpretPackageDbFlags
  , tryGetPersistBuildConfig
  )
import qualified Distribution.Simple.LocalBuildInfo as LBI
import Distribution.Simple.PackageDescription (readGenericPackageDescription)
import Distribution.Simple.Program
  ( configureAllKnownPrograms
  , defaultProgramDb
  , defaultProgramSearchPath
  , findProgramOnSearchPath
  , getProgramInvocationOutput
  , simpleProgramInvocation
  )
import Distribution.Simple.Program.Db (reconfigurePrograms)
import qualified Distribution.Simple.Setup as Cabal
import Distribution.Simple.Utils
  ( cabalVersion
  , createDirectoryIfMissingVerbose
  , dieNoVerbosity
  , dieWithException
  , findPackageDesc
  , info
  , notice
  , topHandler
  , tryFindPackageDesc
  )
import Distribution.Text
  ( display
  )
import qualified Distribution.Types.UnqualComponentName as Make
import Distribution.Utils.Path hiding
  ( (<.>)
  , (</>)
  )
import Distribution.Verbosity as Verbosity
  ( normal
  )
import Distribution.Version
  ( Version
  , mkVersion
  , orLaterVersion
  )

import Control.Exception (AssertionFailed, assert, try)
import Data.Monoid (Any (..))
import System.Directory
  ( doesFileExist
  , withCurrentDirectory
  )
import System.Environment (getEnvironment, getExecutablePath, getProgName)
import System.FilePath
  ( dropExtension
  , splitExtension
  , takeExtension
  , (<.>)
  , (</>)
  )
import System.IO
  ( BufferMode (LineBuffering)
  , hPutStrLn
  , hSetBuffering
  , stderr
  , stdout
  )
import System.Process (createProcess, env, proc, waitForProcess)

-- | Entry point
--
-- This does three things.
--
-- One, it initializes the program, providing support for termination
-- signals, preparing console linebuffering, and relaxing encoding errors.
--
-- Two, it processes (via an IO action) response
-- files, calling 'expandResponse' in Cabal/Distribution.Compat.ResponseFile
--
-- Note that here, it splits the arguments on a strict match to
-- "--", and won't parse response files after the split.
--
-- Three, it calls the 'mainWorker', which calls the argument parser,
-- producing 'CommandParse' data, which mainWorker pattern-matches
-- into IO actions for execution.
main :: [String] -> IO ()
main :: [FilePath] -> IO ()
main [FilePath]
args = do
  IO ()
installTerminationHandler
  -- Enable line buffering so that we can get fast feedback even when piped.
  -- This is especially important for CI and build systems.
  Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout BufferMode
LineBuffering

  -- If the locale encoding for CLI doesn't support all Unicode characters,
  -- printing to it may fail unless we relax the handling of encoding errors
  -- when writing to stderr and stdout.
  Handle -> IO ()
relaxEncodingErrors Handle
stdout
  Handle -> IO ()
relaxEncodingErrors Handle
stderr

  -- Response files support.
  -- See 'expandResponse' documentation in Cabal/Distribution.Compat.ResponseFile
  -- for more information.
  let ([FilePath]
args0, [FilePath]
args1) = (FilePath -> Bool) -> [FilePath] -> ([FilePath], [FilePath])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"--") [FilePath]
args

  [FilePath] -> IO ()
mainWorker ([FilePath] -> IO ()) -> IO [FilePath] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ([FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
args1) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FilePath] -> IO [FilePath]
expandResponse [FilePath]
args0

-- | Check whether assertions are enabled and print a warning in that case.
warnIfAssertionsAreEnabled :: IO ()
warnIfAssertionsAreEnabled :: IO ()
warnIfAssertionsAreEnabled =
  Bool -> IO () -> IO ()
forall a. HasCallStack => Bool -> a -> a
assert Bool
False (() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
    IO () -> (AssertionFailed -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(AssertionFailed
_e :: AssertionFailed) -> Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr FilePath
assertionsEnabledMsg)
  where
    -- Andreas, 2022-12-30, issue #8654:
    -- The verbosity machinery is not in place at this point (option -v not parsed),
    -- so instead of using function @warn@, we print straight to stderr.

    assertionsEnabledMsg :: FilePath
assertionsEnabledMsg =
      FilePath
"Warning: this is a debug build of cabal-install with assertions enabled."

-- | Core worker, similar to 'defaultMainHelper' in Cabal/Distribution.Simple
--
-- With an exception-handler @topHandler@, mainWorker calls commandsRun
-- to parse arguments, then pattern-matches the CommandParse data
-- into IO actions for execution.
mainWorker :: [String] -> IO ()
mainWorker :: [FilePath] -> IO ()
mainWorker [FilePath]
args = do
  IO () -> IO ()
forall a. IO a -> IO a
topHandler (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    CommandParse (GlobalFlags, CommandParse Action)
command <- CommandUI GlobalFlags
-> [Command Action]
-> ([Command Action]
    -> FilePath -> [FilePath] -> IO (CommandParse Action))
-> [FilePath]
-> IO (CommandParse (GlobalFlags, CommandParse Action))
forall a action.
CommandUI a
-> [Command action]
-> ([Command action]
    -> FilePath -> [FilePath] -> IO (CommandParse action))
-> [FilePath]
-> IO (CommandParse (a, CommandParse action))
commandsRunWithFallback ([Command Action] -> CommandUI GlobalFlags
forall action. [Command action] -> CommandUI GlobalFlags
globalCommand [Command Action]
commands) [Command Action]
commands [Command Action]
-> FilePath -> [FilePath] -> IO (CommandParse Action)
delegateToExternal [FilePath]
args
    case CommandParse (GlobalFlags, CommandParse Action)
command of
      CommandHelp FilePath -> FilePath
help -> (FilePath -> FilePath) -> IO ()
printGlobalHelp FilePath -> FilePath
help
      CommandList [FilePath]
opts -> [FilePath] -> IO ()
printOptionsList [FilePath]
opts
      CommandErrors [FilePath]
errs -> [FilePath] -> IO ()
forall {a}. [FilePath] -> IO a
printErrors [FilePath]
errs
      CommandReadyToGo (GlobalFlags
globalFlags, CommandParse Action
commandParse) ->
        case CommandParse Action
commandParse of
          CommandParse Action
_
            | Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (GlobalFlags -> Flag Bool
globalVersion GlobalFlags
globalFlags) ->
                IO ()
printVersion
            | Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (GlobalFlags -> Flag Bool
globalNumericVersion GlobalFlags
globalFlags) ->
                IO ()
printNumericVersion
          CommandHelp FilePath -> FilePath
help -> (FilePath -> FilePath) -> IO ()
printCommandHelp FilePath -> FilePath
help
          CommandList [FilePath]
opts -> [FilePath] -> IO ()
printOptionsList [FilePath]
opts
          CommandErrors [FilePath]
errs -> do
            -- Check whether cabal is called from a script, like #!/path/to/cabal.
            case [FilePath]
args of
              [] -> [FilePath] -> IO ()
forall {a}. [FilePath] -> IO a
printErrors [FilePath]
errs
              FilePath
script : [FilePath]
scriptArgs ->
                FilePath -> IO Bool
CmdRun.validScript FilePath
script IO Bool -> (Bool -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                  Bool
False -> [FilePath] -> IO ()
forall {a}. [FilePath] -> IO a
printErrors [FilePath]
errs
                  Bool
True -> do
                    -- In main operation (not help, version etc.) print warning if assertions are on.
                    IO ()
warnIfAssertionsAreEnabled
                    FilePath -> [FilePath] -> IO ()
CmdRun.handleShebang FilePath
script [FilePath]
scriptArgs
          CommandReadyToGo Action
action -> do
            -- In main operation (not help, version etc.) print warning if assertions are on.
            IO ()
warnIfAssertionsAreEnabled
            Action
action GlobalFlags
globalFlags
  where
    delegateToExternal
      :: [Command Action]
      -> String
      -> [String]
      -> IO (CommandParse Action)
    delegateToExternal :: [Command Action]
-> FilePath -> [FilePath] -> IO (CommandParse Action)
delegateToExternal [Command Action]
commands' FilePath
name [FilePath]
cmdArgs = do
      Maybe (FilePath, [FilePath])
mCommand <- Verbosity
-> ProgramSearchPath
-> FilePath
-> IO (Maybe (FilePath, [FilePath]))
findProgramOnSearchPath Verbosity
normal ProgramSearchPath
defaultProgramSearchPath (FilePath
"cabal-" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
name)
      case Maybe (FilePath, [FilePath])
mCommand of
        Just (FilePath
exec, [FilePath]
_) -> CommandParse Action -> IO (CommandParse Action)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Action -> CommandParse Action
forall flags. flags -> CommandParse flags
CommandReadyToGo (Action -> CommandParse Action) -> Action -> CommandParse Action
forall a b. (a -> b) -> a -> b
$ \GlobalFlags
_ -> FilePath -> FilePath -> [FilePath] -> IO ()
callExternal FilePath
exec FilePath
name [FilePath]
cmdArgs)
        Maybe (FilePath, [FilePath])
Nothing -> [Command Action]
-> FilePath -> [FilePath] -> IO (CommandParse Action)
forall action.
[Command action]
-> FilePath -> [FilePath] -> IO (CommandParse action)
defaultCommandFallback [Command Action]
commands' FilePath
name [FilePath]
cmdArgs

    callExternal :: String -> String -> [String] -> IO ()
    callExternal :: FilePath -> FilePath -> [FilePath] -> IO ()
callExternal FilePath
exec FilePath
name [FilePath]
cmdArgs = do
      [(FilePath, FilePath)]
cur_env <- IO [(FilePath, FilePath)]
getEnvironment
      FilePath
cabal_exe <- IO FilePath
getExecutablePath
      let new_env :: [(FilePath, FilePath)]
new_env = (FilePath
"CABAL", FilePath
cabal_exe) (FilePath, FilePath)
-> [(FilePath, FilePath)] -> [(FilePath, FilePath)]
forall a. a -> [a] -> [a]
: [(FilePath, FilePath)]
cur_env
      Either
  SomeException
  (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
result <- IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> IO
     (Either
        SomeException
        (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle))
forall e a. Exception e => IO a -> IO (Either e a)
try (IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
 -> IO
      (Either
         SomeException
         (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)))
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> IO
     (Either
        SomeException
        (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle))
forall a b. (a -> b) -> a -> b
$ CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess ((FilePath -> [FilePath] -> CreateProcess
proc FilePath
exec (FilePath
name FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
cmdArgs)){env = Just new_env})
      case Either
  SomeException
  (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
result of
        Left SomeException
ex -> [FilePath] -> IO ()
forall {a}. [FilePath] -> IO a
printErrors [FilePath
"Error executing external command: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ SomeException -> FilePath
forall a. Show a => a -> FilePath
show (SomeException
ex :: SomeException)]
        Right (Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
ph) -> ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
ph IO ExitCode -> (ExitCode -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith

    printCommandHelp :: (FilePath -> FilePath) -> IO ()
printCommandHelp FilePath -> FilePath
help = do
      FilePath
pname <- IO FilePath
getProgName
      FilePath -> IO ()
putStr (FilePath -> FilePath
help FilePath
pname)
    printGlobalHelp :: (FilePath -> FilePath) -> IO ()
printGlobalHelp FilePath -> FilePath
help = do
      FilePath
pname <- IO FilePath
getProgName
      FilePath
configFile <- IO FilePath
defaultConfigFile
      FilePath -> IO ()
putStr (FilePath -> FilePath
help FilePath
pname)
      -- Andreas Abel, 2024-01-28: https://github.com/haskell/cabal/pull/9614
      -- See cabal-testsuite/PackageTests/Help/HelpPrintsConfigFile/
      -- Third-party tools may rely on the specific wording
      -- to find the config file in the help text, so do not change!
      FilePath -> IO ()
putStr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath
"\nYou can edit the cabal configuration file to set defaults:\n"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
configFile
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      Bool
exists <- FilePath -> IO Bool
doesFileExist FilePath
configFile
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
          FilePath
"This file will be generated with sensible "
            FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"defaults if you run 'cabal update'."
    printOptionsList :: [FilePath] -> IO ()
printOptionsList = FilePath -> IO ()
putStr (FilePath -> IO ())
-> ([FilePath] -> FilePath) -> [FilePath] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines
    printErrors :: [FilePath] -> IO a
printErrors [FilePath]
errs = FilePath -> IO a
forall a. FilePath -> IO a
dieNoVerbosity (FilePath -> IO a) -> FilePath -> IO a
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"\n" [FilePath]
errs
    printNumericVersion :: IO ()
printNumericVersion = FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ Version -> FilePath
forall a. Pretty a => a -> FilePath
display Version
cabalInstallVersion
    printVersion :: IO ()
printVersion =
      FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath
"cabal-install version "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
display Version
cabalInstallVersion
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\ncompiled using version "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
display Version
cabalVersion
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" of the Cabal library "

    commands :: [Command Action]
commands = (CommandSpec Action -> Command Action)
-> [CommandSpec Action] -> [Command Action]
forall a b. (a -> b) -> [a] -> [b]
map CommandSpec Action -> Command Action
forall a. CommandSpec a -> Command a
commandFromSpec [CommandSpec Action]
commandSpecs
    commandSpecs :: [CommandSpec Action]
commandSpecs =
      [ CommandUI ListFlags
-> (ListFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI ListFlags
listCommand ListFlags -> [FilePath] -> Action
listAction
      , CommandUI InfoFlags
-> (InfoFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI InfoFlags
infoCommand InfoFlags -> [FilePath] -> Action
infoAction
      , CommandUI FetchFlags
-> (FetchFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI FetchFlags
fetchCommand FetchFlags -> [FilePath] -> Action
fetchAction
      , CommandUI GetFlags
-> (GetFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI GetFlags
getCommand GetFlags -> [FilePath] -> Action
getAction
      , CommandUI GetFlags
-> (GetFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI GetFlags
unpackCommand GetFlags -> [FilePath] -> Action
unpackAction
      , CommandUI CheckFlags
-> (CheckFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI CheckFlags
checkCommand CheckFlags -> [FilePath] -> Action
checkAction
      , CommandUI UploadFlags
-> (UploadFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI UploadFlags
uploadCommand UploadFlags -> [FilePath] -> Action
uploadAction
      , CommandUI ReportFlags
-> (ReportFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI ReportFlags
reportCommand ReportFlags -> [FilePath] -> Action
reportAction
      , CommandUI InitFlags
-> (InitFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI InitFlags
initCommand InitFlags -> [FilePath] -> Action
initAction
      , CommandUI UserConfigFlags
-> (UserConfigFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI UserConfigFlags
userConfigCommand UserConfigFlags -> [FilePath] -> Action
userConfigAction
      , CommandUI (NixStyleFlags PathFlags)
-> (NixStyleFlags PathFlags -> [FilePath] -> Action)
-> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI (NixStyleFlags PathFlags)
CmdPath.pathCommand NixStyleFlags PathFlags -> [FilePath] -> Action
CmdPath.pathAction
      , CommandUI FreezeFlags
-> (FreezeFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI FreezeFlags
genBoundsCommand FreezeFlags -> [FilePath] -> Action
genBoundsAction
      , CommandUI (ProjectFlags, OutdatedFlags)
-> ((ProjectFlags, OutdatedFlags) -> [FilePath] -> Action)
-> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI (ProjectFlags, OutdatedFlags)
CmdOutdated.outdatedCommand (ProjectFlags, OutdatedFlags) -> [FilePath] -> Action
CmdOutdated.outdatedAction
      , CommandUI HscolourFlags
-> (HscolourFlags -> CommonSetupFlags) -> CommandSpec Action
forall flags.
Monoid flags =>
CommandUI flags
-> (flags -> CommonSetupFlags) -> CommandSpec Action
wrapperCmd CommandUI HscolourFlags
hscolourCommand HscolourFlags -> CommonSetupFlags
hscolourCommonFlags
      , CommandUI (Flag Verbosity)
-> (Flag Verbosity -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
hiddenCmd CommandUI (Flag Verbosity)
formatCommand Flag Verbosity -> [FilePath] -> Action
formatAction
      , CommandUI ActAsSetupFlags
-> (ActAsSetupFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
hiddenCmd CommandUI ActAsSetupFlags
actAsSetupCommand ActAsSetupFlags -> [FilePath] -> Action
actAsSetupAction
      , CommandUI ManpageFlags
-> (ManpageFlags -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
hiddenCmd CommandUI ManpageFlags
manpageCommand ([CommandSpec Action] -> ManpageFlags -> [FilePath] -> Action
forall action.
[CommandSpec action] -> ManpageFlags -> [FilePath] -> Action
manpageAction [CommandSpec Action]
commandSpecs)
      , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action) -> CommandSpec Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI (NixStyleFlags ())
CmdListBin.listbinCommand NixStyleFlags () -> [FilePath] -> Action
CmdListBin.listbinAction
      ]
        [CommandSpec Action]
-> [CommandSpec Action] -> [CommandSpec Action]
forall a. [a] -> [a] -> [a]
++ [[CommandSpec Action]] -> [CommandSpec Action]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
          [ CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdConfigure.configureCommand NixStyleFlags () -> [FilePath] -> Action
CmdConfigure.configureAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdUpdate.updateCommand NixStyleFlags () -> [FilePath] -> Action
CmdUpdate.updateAction
          , CommandUI (NixStyleFlags BuildFlags)
-> (NixStyleFlags BuildFlags -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags BuildFlags)
CmdBuild.buildCommand NixStyleFlags BuildFlags -> [FilePath] -> Action
CmdBuild.buildAction
          , CommandUI (NixStyleFlags ReplFlags)
-> (NixStyleFlags ReplFlags -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ReplFlags)
CmdRepl.replCommand NixStyleFlags ReplFlags -> [FilePath] -> Action
CmdRepl.replAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdFreeze.freezeCommand NixStyleFlags () -> [FilePath] -> Action
CmdFreeze.freezeAction
          , CommandUI (NixStyleFlags ClientHaddockFlags)
-> (NixStyleFlags ClientHaddockFlags -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ClientHaddockFlags)
CmdHaddock.haddockCommand NixStyleFlags ClientHaddockFlags -> [FilePath] -> Action
CmdHaddock.haddockAction
          , CommandUI HaddockProjectFlags
-> (HaddockProjectFlags -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd
              CommandUI HaddockProjectFlags
CmdHaddockProject.haddockProjectCommand
              HaddockProjectFlags -> [FilePath] -> Action
CmdHaddockProject.haddockProjectAction
          , CommandUI (NixStyleFlags ClientInstallFlags)
-> (NixStyleFlags ClientInstallFlags -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ClientInstallFlags)
CmdInstall.installCommand NixStyleFlags ClientInstallFlags -> [FilePath] -> Action
CmdInstall.installAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdRun.runCommand NixStyleFlags () -> [FilePath] -> Action
CmdRun.runAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdTest.testCommand NixStyleFlags () -> [FilePath] -> Action
CmdTest.testAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdBench.benchCommand NixStyleFlags () -> [FilePath] -> Action
CmdBench.benchAction
          , CommandUI (NixStyleFlags ())
-> (NixStyleFlags () -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (NixStyleFlags ())
CmdExec.execCommand NixStyleFlags () -> [FilePath] -> Action
CmdExec.execAction
          , CommandUI (ProjectFlags, CleanFlags)
-> ((ProjectFlags, CleanFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (ProjectFlags, CleanFlags)
CmdClean.cleanCommand (ProjectFlags, CleanFlags) -> [FilePath] -> Action
CmdClean.cleanAction
          , CommandUI (ProjectFlags, SdistFlags)
-> ((ProjectFlags, SdistFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
newCmd CommandUI (ProjectFlags, SdistFlags)
CmdSdist.sdistCommand (ProjectFlags, SdistFlags) -> [FilePath] -> Action
CmdSdist.sdistAction
          , CommandUI (ConfigFlags, ConfigExFlags)
-> ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI (ConfigFlags, ConfigExFlags)
configureExCommand (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
          , CommandUI BuildFlags
-> (BuildFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI BuildFlags
buildCommand BuildFlags -> [FilePath] -> Action
buildAction
          , CommandUI ReplFlags
-> (ReplFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI ReplFlags
replCommand ReplFlags -> [FilePath] -> Action
replAction
          , CommandUI FreezeFlags
-> (FreezeFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI FreezeFlags
freezeCommand FreezeFlags -> [FilePath] -> Action
freezeAction
          , CommandUI HaddockFlags
-> (HaddockFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI HaddockFlags
haddockCommand HaddockFlags -> [FilePath] -> Action
haddockAction
          , CommandUI
  (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
   BenchmarkFlags)
-> ((ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags,
     TestFlags, BenchmarkFlags)
    -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI
  (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
   BenchmarkFlags)
installCommand (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
 BenchmarkFlags)
-> [FilePath] -> Action
installAction
          , CommandUI BuildFlags
-> (BuildFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI BuildFlags
runCommand BuildFlags -> [FilePath] -> Action
runAction
          , CommandUI (BuildFlags, TestFlags)
-> ((BuildFlags, TestFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI (BuildFlags, TestFlags)
testCommand (BuildFlags, TestFlags) -> [FilePath] -> Action
testAction
          , CommandUI (BuildFlags, BenchmarkFlags)
-> ((BuildFlags, BenchmarkFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI (BuildFlags, BenchmarkFlags)
benchmarkCommand (BuildFlags, BenchmarkFlags) -> [FilePath] -> Action
benchmarkAction
          , CommandUI CleanFlags
-> (CleanFlags -> [FilePath] -> Action) -> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI CleanFlags
cleanCommand CleanFlags -> [FilePath] -> Action
cleanAction
          , CommandUI CopyFlags
-> (CopyFlags -> CommonSetupFlags) -> [CommandSpec Action]
forall flags.
Monoid flags =>
CommandUI flags
-> (flags -> CommonSetupFlags) -> [CommandSpec Action]
legacyWrapperCmd CommandUI CopyFlags
copyCommand CopyFlags -> CommonSetupFlags
copyCommonFlags
          , CommandUI RegisterFlags
-> (RegisterFlags -> CommonSetupFlags) -> [CommandSpec Action]
forall flags.
Monoid flags =>
CommandUI flags
-> (flags -> CommonSetupFlags) -> [CommandSpec Action]
legacyWrapperCmd CommandUI RegisterFlags
registerCommand RegisterFlags -> CommonSetupFlags
registerCommonFlags
          , CommandUI (ConfigFlags, ConfigExFlags)
-> ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> [CommandSpec Action]
forall flags globals action.
HasVerbosity flags =>
CommandUI flags
-> (flags -> [FilePath] -> globals -> IO action)
-> [CommandSpec (globals -> IO action)]
legacyCmd CommandUI (ConfigFlags, ConfigExFlags)
reconfigureCommand (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
reconfigureAction
          ]

type Action = GlobalFlags -> IO ()

-- Duplicated in Distribution.Client.CmdLegacy. Any changes must be
-- reflected there, as well.
regularCmd
  :: CommandUI flags
  -> (flags -> [String] -> action)
  -> CommandSpec action
regularCmd :: forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
regularCmd CommandUI flags
ui flags -> [FilePath] -> action
action =
  CommandUI flags
-> (CommandUI flags -> Command action)
-> CommandType
-> CommandSpec action
forall action flags.
CommandUI flags
-> (CommandUI flags -> Command action)
-> CommandType
-> CommandSpec action
CommandSpec CommandUI flags
ui (((CommandUI flags
 -> (flags -> [FilePath] -> action) -> Command action)
-> (flags -> [FilePath] -> action)
-> CommandUI flags
-> Command action
forall a b c. (a -> b -> c) -> b -> a -> c
flip CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
commandAddAction) flags -> [FilePath] -> action
action) CommandType
NormalCommand

hiddenCmd
  :: CommandUI flags
  -> (flags -> [String] -> action)
  -> CommandSpec action
hiddenCmd :: forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> CommandSpec action
hiddenCmd CommandUI flags
ui flags -> [FilePath] -> action
action =
  CommandUI flags
-> (CommandUI flags -> Command action)
-> CommandType
-> CommandSpec action
forall action flags.
CommandUI flags
-> (CommandUI flags -> Command action)
-> CommandType
-> CommandSpec action
CommandSpec
    CommandUI flags
ui
    (\CommandUI flags
ui' -> Command action -> Command action
forall action. Command action -> Command action
hiddenCommand (CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
commandAddAction CommandUI flags
ui' flags -> [FilePath] -> action
action))
    CommandType
HiddenCommand

wrapperCmd
  :: Monoid flags
  => CommandUI flags
  -> (flags -> CommonSetupFlags)
  -> CommandSpec Action
wrapperCmd :: forall flags.
Monoid flags =>
CommandUI flags
-> (flags -> CommonSetupFlags) -> CommandSpec Action
wrapperCmd CommandUI flags
ui flags -> CommonSetupFlags
getCommonFlags =
  CommandUI flags
-> (CommandUI flags -> Command Action)
-> CommandType
-> CommandSpec Action
forall action flags.
CommandUI flags
-> (CommandUI flags -> Command action)
-> CommandType
-> CommandSpec action
CommandSpec CommandUI flags
ui (\CommandUI flags
ui' -> CommandUI flags -> (flags -> CommonSetupFlags) -> Command Action
forall flags.
Monoid flags =>
CommandUI flags -> (flags -> CommonSetupFlags) -> Command Action
wrapperAction CommandUI flags
ui' flags -> CommonSetupFlags
getCommonFlags) CommandType
NormalCommand

wrapperAction
  :: Monoid flags
  => CommandUI flags
  -> (flags -> CommonSetupFlags)
  -> Command Action
wrapperAction :: forall flags.
Monoid flags =>
CommandUI flags -> (flags -> CommonSetupFlags) -> Command Action
wrapperAction CommandUI flags
command flags -> CommonSetupFlags
getCommonFlags =
  CommandUI flags
-> (flags -> [FilePath] -> Action) -> Command Action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
commandAddAction
    CommandUI flags
command
      { commandDefaultFlags = mempty
      }
    ((flags -> [FilePath] -> Action) -> Command Action)
-> (flags -> [FilePath] -> Action) -> Command Action
forall a b. (a -> b) -> a -> b
$ \flags
flags [FilePath]
extraArgs GlobalFlags
globalFlags -> do
      let common :: CommonSetupFlags
common = flags -> CommonSetupFlags
getCommonFlags flags
flags
          verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
          mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
setupWorkingDir CommonSetupFlags
common
      Either SomeException SavedConfig
load <- IO SavedConfig -> IO (Either SomeException SavedConfig)
forall e a. Exception e => IO a -> IO (Either e a)
try (Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags)
      let config :: SavedConfig
config = (SomeException -> SavedConfig)
-> (SavedConfig -> SavedConfig)
-> Either SomeException SavedConfig
-> SavedConfig
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\(SomeException e
_) -> SavedConfig
forall a. Monoid a => a
mempty) SavedConfig -> SavedConfig
forall a. a -> a
id Either SomeException SavedConfig
load
      SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
      let setupScriptOptions :: SetupScriptOptions
setupScriptOptions =
            SetupScriptOptions
defaultSetupScriptOptions
              { useDistPref = distPref
              , useWorkingDir = mbWorkDir
              }
      Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
        Verbosity
verbosity
        SetupScriptOptions
setupScriptOptions
        Maybe PackageDescription
forall a. Maybe a
Nothing
        CommandUI flags
command
        flags -> CommonSetupFlags
getCommonFlags
        (IO flags -> Version -> IO flags
forall a b. a -> b -> a
const (flags -> IO flags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return flags
flags))
        ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs)

configureAction
  :: (ConfigFlags, ConfigExFlags)
  -> [String]
  -> Action
configureAction :: (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction (ConfigFlags
configFlags, ConfigExFlags
configExFlags) [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = ConfigFlags -> CommonSetupFlags
configCommonFlags ConfigFlags
configFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  SavedConfig
config <-
    Flag Bool -> SavedConfig -> SavedConfig
updateInstallDirs (ConfigFlags -> Flag Bool
configUserInstall ConfigFlags
configFlags)
      (SavedConfig -> SavedConfig) -> IO SavedConfig -> IO SavedConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  FilePath
distPref <- SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (SymbolicPath Pkg ('Dir Dist) -> FilePath)
-> IO (SymbolicPath Pkg ('Dir Dist)) -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
  Verbosity
-> FilePath -> Bool -> GlobalFlags -> SavedConfig -> IO ()
nixInstantiate Verbosity
verbosity FilePath
distPref Bool
True GlobalFlags
globalFlags SavedConfig
config
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity FilePath
distPref GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    let configFlags' :: ConfigFlags
configFlags' = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config ConfigFlags -> ConfigFlags -> ConfigFlags
forall a. Monoid a => a -> a -> a
`mappend` ConfigFlags
configFlags
        configExFlags' :: ConfigExFlags
configExFlags' = SavedConfig -> ConfigExFlags
savedConfigureExFlags SavedConfig
config ConfigExFlags -> ConfigExFlags -> ConfigExFlags
forall a. Monoid a => a -> a -> a
`mappend` ConfigExFlags
configExFlags
        globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
    (Compiler
comp, Platform
platform, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAuxEx ConfigFlags
configFlags'

    Verbosity -> FilePath -> (ConfigFlags, ConfigExFlags) -> IO ()
writeConfigFlags Verbosity
verbosity FilePath
distPref (ConfigFlags
configFlags', ConfigExFlags
configExFlags')

    -- What package database(s) to use
    let packageDBs :: PackageDBStack
        packageDBs :: PackageDBStack
packageDBs =
          Bool
-> [Maybe (PackageDBX (SymbolicPath Pkg ('Dir PkgDB)))]
-> PackageDBStack
forall fp. Bool -> [Maybe (PackageDBX fp)] -> PackageDBStackX fp
interpretPackageDbFlags
            (Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Bool
configUserInstall ConfigFlags
configFlags'))
            (ConfigFlags -> [Maybe (PackageDBX (SymbolicPath Pkg ('Dir PkgDB)))]
configPackageDBs ConfigFlags
configFlags')

    Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
      Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> ConfigFlags
-> ConfigExFlags
-> [FilePath]
-> IO ()
configure
        Verbosity
verbosity
        (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing PackageDBStack
packageDBs)
        RepoContext
repoContext
        Compiler
comp
        Platform
platform
        ProgramDb
progdb
        ConfigFlags
configFlags'
        ConfigExFlags
configExFlags'
        [FilePath]
extraArgs

reconfigureAction
  :: (ConfigFlags, ConfigExFlags)
  -> [String]
  -> Action
reconfigureAction :: (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
reconfigureAction flags :: (ConfigFlags, ConfigExFlags)
flags@(ConfigFlags
configFlags, ConfigExFlags
_) [FilePath]
_ GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = ConfigFlags -> CommonSetupFlags
configCommonFlags ConfigFlags
configFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common)
  SavedConfig
config <-
    Flag Bool -> SavedConfig -> SavedConfig
updateInstallDirs (ConfigFlags -> Flag Bool
configUserInstall ConfigFlags
configFlags)
      (SavedConfig -> SavedConfig) -> IO SavedConfig -> IO SavedConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
  let checkFlags :: Check (ConfigFlags, ConfigExFlags)
checkFlags = (Any
 -> (ConfigFlags, ConfigExFlags)
 -> IO (Any, (ConfigFlags, ConfigExFlags)))
-> Check (ConfigFlags, ConfigExFlags)
forall a. (Any -> a -> IO (Any, a)) -> Check a
Check ((Any
  -> (ConfigFlags, ConfigExFlags)
  -> IO (Any, (ConfigFlags, ConfigExFlags)))
 -> Check (ConfigFlags, ConfigExFlags))
-> (Any
    -> (ConfigFlags, ConfigExFlags)
    -> IO (Any, (ConfigFlags, ConfigExFlags)))
-> Check (ConfigFlags, ConfigExFlags)
forall a b. (a -> b) -> a -> b
$ \Any
_ (ConfigFlags, ConfigExFlags)
saved -> do
        let flags' :: (ConfigFlags, ConfigExFlags)
flags' = (ConfigFlags, ConfigExFlags)
saved (ConfigFlags, ConfigExFlags)
-> (ConfigFlags, ConfigExFlags) -> (ConfigFlags, ConfigExFlags)
forall a. Semigroup a => a -> a -> a
<> (ConfigFlags, ConfigExFlags)
flags
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((ConfigFlags, ConfigExFlags)
saved (ConfigFlags, ConfigExFlags)
-> (ConfigFlags, ConfigExFlags) -> Bool
forall a. Eq a => a -> a -> Bool
== (ConfigFlags, ConfigExFlags)
flags') (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Verbosity -> FilePath -> IO ()
info Verbosity
verbosity FilePath
message
        (Any, (ConfigFlags, ConfigExFlags))
-> IO (Any, (ConfigFlags, ConfigExFlags))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
True, (ConfigFlags, ConfigExFlags)
flags')
        where
          -- This message is correct, but not very specific: it will list all
          -- of the new flags, even if some have not actually changed. The
          -- \*minimal* set of changes is more difficult to determine.
          message :: FilePath
message =
            FilePath
"flags changed: "
              FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords (CommandUI (ConfigFlags, ConfigExFlags)
-> (ConfigFlags, ConfigExFlags) -> [FilePath]
forall flags. CommandUI flags -> flags -> [FilePath]
commandShowOptions CommandUI (ConfigFlags, ConfigExFlags)
configureExCommand (ConfigFlags, ConfigExFlags)
flags)
  Verbosity
-> FilePath -> Bool -> GlobalFlags -> SavedConfig -> IO ()
nixInstantiate Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) Bool
True GlobalFlags
globalFlags SavedConfig
config
  SavedConfig
_ <-
    ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
      (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
      Verbosity
verbosity
      SymbolicPath Pkg ('Dir Dist)
distPref
      Flag (Maybe Int)
forall a. Flag a
NoFlag
      Check (ConfigFlags, ConfigExFlags)
checkFlags
      []
      GlobalFlags
globalFlags
      SavedConfig
config
  () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

buildAction :: BuildFlags -> [String] -> Action
buildAction :: BuildFlags -> [FilePath] -> Action
buildAction BuildFlags
buildFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = BuildFlags -> CommonSetupFlags
buildCommonFlags BuildFlags
buildFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
  -- Calls 'configureAction' to do the real work, so nothing special has to be
  -- done to support sandboxes.
  SavedConfig
config' <-
    ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
      (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
      Verbosity
verbosity
      SymbolicPath Pkg ('Dir Dist)
distPref
      (BuildFlags -> Flag (Maybe Int)
buildNumJobs BuildFlags
buildFlags)
      Check (ConfigFlags, ConfigExFlags)
forall a. Monoid a => a
mempty
      []
      GlobalFlags
globalFlags
      SavedConfig
config
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Verbosity
-> SavedConfig
-> SymbolicPath Pkg ('Dir Dist)
-> BuildFlags
-> [FilePath]
-> IO ()
build Verbosity
verbosity SavedConfig
config' SymbolicPath Pkg ('Dir Dist)
distPref BuildFlags
buildFlags [FilePath]
extraArgs

-- | Actually do the work of building the package. This is separate from
-- 'buildAction' so that 'testAction' and 'benchmarkAction' do not invoke
-- 'reconfigure' twice.
build :: Verbosity -> SavedConfig -> SymbolicPath Pkg (Dir Dist) -> BuildFlags -> [String] -> IO ()
build :: Verbosity
-> SavedConfig
-> SymbolicPath Pkg ('Dir Dist)
-> BuildFlags
-> [FilePath]
-> IO ()
build Verbosity
verbosity SavedConfig
config SymbolicPath Pkg ('Dir Dist)
distPref BuildFlags
buildFlags [FilePath]
extraArgs =
  Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI BuildFlags
-> (BuildFlags -> CommonSetupFlags)
-> (Version -> IO BuildFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
    Verbosity
verbosity
    SetupScriptOptions
setupOptions
    Maybe PackageDescription
forall a. Maybe a
Nothing
    (ProgramDb -> CommandUI BuildFlags
Cabal.buildCommand ProgramDb
progDb)
    BuildFlags -> CommonSetupFlags
buildCommonFlags
    (BuildFlags -> IO BuildFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BuildFlags -> IO BuildFlags)
-> (Version -> BuildFlags) -> Version -> IO BuildFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> BuildFlags
mkBuildFlags)
    ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs)
  where
    progDb :: ProgramDb
progDb = ProgramDb
defaultProgramDb
    setupOptions :: SetupScriptOptions
setupOptions = SetupScriptOptions
defaultSetupScriptOptions{useDistPref = distPref}

    mkBuildFlags :: Version -> BuildFlags
mkBuildFlags Version
version = Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags Version
version SavedConfig
config BuildFlags
buildFlags'
    commonFlags :: CommonSetupFlags
commonFlags = BuildFlags -> CommonSetupFlags
buildCommonFlags BuildFlags
buildFlags
    buildFlags' :: BuildFlags
buildFlags' =
      BuildFlags
buildFlags
        { buildCommonFlags =
            commonFlags
              { setupVerbosity = toFlag verbosity
              , setupDistPref = toFlag distPref
              }
        }

-- | Make sure that we don't pass new flags to setup scripts compiled against
-- old versions of Cabal.
filterBuildFlags :: Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags :: Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags Version
version SavedConfig
config BuildFlags
buildFlags =
  let flags' :: BuildFlags
flags' = Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags' Version
version SavedConfig
config BuildFlags
buildFlags
   in BuildFlags
flags'
        { buildCommonFlags =
            filterCommonFlags (buildCommonFlags flags') version
        }

filterBuildFlags' :: Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags' :: Version -> SavedConfig -> BuildFlags -> BuildFlags
filterBuildFlags' Version
version SavedConfig
config BuildFlags
buildFlags
  | Version
version Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
1, Int
19, Int
1] = BuildFlags
buildFlags_latest
  -- Cabal < 1.19.1 doesn't support 'build -j'.
  | Bool
otherwise = BuildFlags
buildFlags_pre_1_19_1
  where
    buildFlags_pre_1_19_1 :: BuildFlags
buildFlags_pre_1_19_1 =
      BuildFlags
buildFlags
        { buildNumJobs = NoFlag
        }
    buildFlags_latest :: BuildFlags
buildFlags_latest =
      BuildFlags
buildFlags
        { -- Take the 'jobs' setting config file into account.
          buildNumJobs =
            Flag . Just . determineNumJobs $
              (numJobsConfigFlag `mappend` numJobsCmdLineFlag)
        }
    numJobsConfigFlag :: Flag (Maybe Int)
numJobsConfigFlag = InstallFlags -> Flag (Maybe Int)
installNumJobs (InstallFlags -> Flag (Maybe Int))
-> (SavedConfig -> InstallFlags) -> SavedConfig -> Flag (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SavedConfig -> InstallFlags
savedInstallFlags (SavedConfig -> Flag (Maybe Int))
-> SavedConfig -> Flag (Maybe Int)
forall a b. (a -> b) -> a -> b
$ SavedConfig
config
    numJobsCmdLineFlag :: Flag (Maybe Int)
numJobsCmdLineFlag = BuildFlags -> Flag (Maybe Int)
buildNumJobs BuildFlags
buildFlags

replAction :: ReplFlags -> [String] -> Action
replAction :: ReplFlags -> [FilePath] -> Action
replAction ReplFlags
replFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = ReplFlags -> CommonSetupFlags
replCommonFlags ReplFlags
replFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
  Either CabalException (RelativePath Pkg 'File)
pkgDesc <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (Either CabalException (RelativePath Pkg 'File))
findPackageDesc Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
  let
    -- There is a .cabal file in the current directory: start a REPL and load
    -- the project's modules.
    onPkgDesc :: IO ()
onPkgDesc = do
      -- Calls 'configureAction' to do the real work, so nothing special has to
      -- be done to support sandboxes.
      SavedConfig
_ <-
        ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
          (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
          Verbosity
verbosity
          SymbolicPath Pkg ('Dir Dist)
distPref
          Flag (Maybe Int)
forall a. Flag a
NoFlag
          Check (ConfigFlags, ConfigExFlags)
forall a. Monoid a => a
mempty
          []
          GlobalFlags
globalFlags
          SavedConfig
config
      let progDb :: ProgramDb
progDb = ProgramDb
defaultProgramDb
          setupOptions :: SetupScriptOptions
setupOptions =
            SetupScriptOptions
defaultSetupScriptOptions
              { useCabalVersion = orLaterVersion $ mkVersion [1, 18, 0]
              , useDistPref = distPref
              }
          commonFlags :: CommonSetupFlags
commonFlags = ReplFlags -> CommonSetupFlags
replCommonFlags ReplFlags
replFlags
          replFlags' :: ReplFlags
replFlags' =
            ReplFlags
replFlags
              { replCommonFlags =
                  commonFlags
                    { setupVerbosity = toFlag verbosity
                    , setupDistPref = toFlag distPref
                    }
              }

      Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI ReplFlags
-> (ReplFlags -> CommonSetupFlags)
-> (Version -> IO ReplFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
          Verbosity
verbosity
          SetupScriptOptions
setupOptions
          Maybe PackageDescription
forall a. Maybe a
Nothing
          (ProgramDb -> CommandUI ReplFlags
Cabal.replCommand ProgramDb
progDb)
          ReplFlags -> CommonSetupFlags
Cabal.replCommonFlags
          (IO ReplFlags -> Version -> IO ReplFlags
forall a b. a -> b -> a
const (ReplFlags -> IO ReplFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ReplFlags
replFlags'))
          ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs)

    -- No .cabal file in the current directory: just start the REPL (possibly
    -- using the sandbox package DB).
    onNoPkgDesc :: IO ()
onNoPkgDesc = do
      let configFlags :: ConfigFlags
configFlags = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
      (Compiler
comp, Platform
platform, ProgramDb
programDb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags
      ProgramDb
programDb' <-
        Verbosity
-> [(FilePath, FilePath)]
-> [(FilePath, [FilePath])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms
          Verbosity
verbosity
          (ReplFlags -> [(FilePath, FilePath)]
replProgramPaths ReplFlags
replFlags)
          (ReplFlags -> [(FilePath, [FilePath])]
replProgramArgs ReplFlags
replFlags)
          ProgramDb
programDb
      Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Verbosity
-> ProgramDb -> Compiler -> Platform -> PackageDBStack -> IO ()
startInterpreter
          Verbosity
verbosity
          ProgramDb
programDb'
          Compiler
comp
          Platform
platform
          (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags)

  (CabalException -> IO ())
-> (RelativePath Pkg 'File -> IO ())
-> Either CabalException (RelativePath Pkg 'File)
-> IO ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (IO () -> CabalException -> IO ()
forall a b. a -> b -> a
const IO ()
onNoPkgDesc) (IO () -> RelativePath Pkg 'File -> IO ()
forall a b. a -> b -> a
const IO ()
onPkgDesc) Either CabalException (RelativePath Pkg 'File)
pkgDesc

installAction
  :: ( ConfigFlags
     , ConfigExFlags
     , InstallFlags
     , HaddockFlags
     , TestFlags
     , BenchmarkFlags
     )
  -> [String]
  -> Action
installAction :: (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
 BenchmarkFlags)
-> [FilePath] -> Action
installAction (ConfigFlags
configFlags, ConfigExFlags
_, InstallFlags
installFlags, HaddockFlags
_, TestFlags
_, BenchmarkFlags
_) [FilePath]
_ GlobalFlags
globalFlags
  | Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (InstallFlags -> Flag Bool
installOnly InstallFlags
installFlags) = do
      let common :: CommonSetupFlags
common = ConfigFlags -> CommonSetupFlags
configCommonFlags ConfigFlags
configFlags
          verb :: Verbosity
verb = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common)
      SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verb GlobalFlags
globalFlags
      SymbolicPath Pkg ('Dir Dist)
dist <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
      let setupOpts :: SetupScriptOptions
setupOpts = SetupScriptOptions
defaultSetupScriptOptions{useDistPref = dist}
      Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI
     (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
      BenchmarkFlags)
-> ((ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags,
     TestFlags, BenchmarkFlags)
    -> CommonSetupFlags)
-> (Version
    -> IO
         (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
          BenchmarkFlags))
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
        Verbosity
verb
        SetupScriptOptions
setupOpts
        Maybe PackageDescription
forall a. Maybe a
Nothing
        CommandUI
  (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
   BenchmarkFlags)
installCommand
        (CommonSetupFlags
-> (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags,
    TestFlags, BenchmarkFlags)
-> CommonSetupFlags
forall a b. a -> b -> a
const CommonSetupFlags
common)
        (IO
  (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
   BenchmarkFlags)
-> Version
-> IO
     (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
      BenchmarkFlags)
forall a b. a -> b -> a
const ((ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
 BenchmarkFlags)
-> IO
     (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags,
      BenchmarkFlags)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConfigFlags
forall a. Monoid a => a
mempty, ConfigExFlags
forall a. Monoid a => a
mempty, InstallFlags
forall a. Monoid a => a
mempty, HaddockFlags
forall a. Monoid a => a
mempty, TestFlags
forall a. Monoid a => a
mempty, BenchmarkFlags
forall a. Monoid a => a
mempty)))
        ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [])
installAction
  ( ConfigFlags
configFlags
    , ConfigExFlags
configExFlags
    , InstallFlags
installFlags
    , HaddockFlags
haddockFlags
    , TestFlags
testFlags
    , BenchmarkFlags
benchmarkFlags
    )
  [FilePath]
extraArgs
  GlobalFlags
globalFlags = do
    let common :: CommonSetupFlags
common = ConfigFlags -> CommonSetupFlags
configCommonFlags ConfigFlags
configFlags
        verb :: Verbosity
verb = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
    SavedConfig
config <-
      Flag Bool -> SavedConfig -> SavedConfig
updateInstallDirs (ConfigFlags -> Flag Bool
configUserInstall ConfigFlags
configFlags)
        (SavedConfig -> SavedConfig) -> IO SavedConfig -> IO SavedConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verb GlobalFlags
globalFlags

    SymbolicPath Pkg ('Dir Dist)
dist <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (Flag (SymbolicPath Pkg ('Dir Dist))
 -> IO (SymbolicPath Pkg ('Dir Dist)))
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common

    do
      [UserTarget]
targets <- Verbosity -> [FilePath] -> IO [UserTarget]
readUserTargets Verbosity
verb [FilePath]
extraArgs

      let configFlags' :: ConfigFlags
configFlags' =
            InstallFlags -> ConfigFlags -> ConfigFlags
maybeForceTests InstallFlags
installFlags' (ConfigFlags -> ConfigFlags) -> ConfigFlags -> ConfigFlags
forall a b. (a -> b) -> a -> b
$
              SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
                ConfigFlags -> ConfigFlags -> ConfigFlags
forall a. Monoid a => a -> a -> a
`mappend` ConfigFlags
configFlags
                  { configCommonFlags =
                      (configCommonFlags configFlags)
                        { setupDistPref = toFlag dist
                        }
                  }
          configExFlags' :: ConfigExFlags
configExFlags' =
            ConfigExFlags
defaultConfigExFlags
              ConfigExFlags -> ConfigExFlags -> ConfigExFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> ConfigExFlags
savedConfigureExFlags SavedConfig
config
              ConfigExFlags -> ConfigExFlags -> ConfigExFlags
forall a. Monoid a => a -> a -> a
`mappend` ConfigExFlags
configExFlags
          installFlags' :: InstallFlags
installFlags' =
            InstallFlags
defaultInstallFlags
              InstallFlags -> InstallFlags -> InstallFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> InstallFlags
savedInstallFlags SavedConfig
config
              InstallFlags -> InstallFlags -> InstallFlags
forall a. Monoid a => a -> a -> a
`mappend` InstallFlags
installFlags
          haddockFlags' :: HaddockFlags
haddockFlags' =
            HaddockFlags
defaultHaddockFlags
              HaddockFlags -> HaddockFlags -> HaddockFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> HaddockFlags
savedHaddockFlags SavedConfig
config
              HaddockFlags -> HaddockFlags -> HaddockFlags
forall a. Monoid a => a -> a -> a
`mappend` HaddockFlags
haddockFlags
                { haddockCommonFlags =
                    (haddockCommonFlags haddockFlags)
                      { setupDistPref = toFlag dist
                      }
                }
          testFlags' :: TestFlags
testFlags' =
            TestFlags
Cabal.defaultTestFlags
              TestFlags -> TestFlags -> TestFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> TestFlags
savedTestFlags SavedConfig
config
              TestFlags -> TestFlags -> TestFlags
forall a. Monoid a => a -> a -> a
`mappend` TestFlags
testFlags
                { testCommonFlags =
                    (testCommonFlags testFlags)
                      { setupDistPref = toFlag dist
                      }
                }
          benchmarkFlags' :: BenchmarkFlags
benchmarkFlags' =
            BenchmarkFlags
Cabal.defaultBenchmarkFlags
              BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> BenchmarkFlags
savedBenchmarkFlags SavedConfig
config
              BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
forall a. Monoid a => a -> a -> a
`mappend` BenchmarkFlags
benchmarkFlags
                { benchmarkCommonFlags =
                    (benchmarkCommonFlags benchmarkFlags)
                      { setupDistPref = toFlag dist
                      }
                }
          globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
      (Compiler
comp, Platform
platform, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags'

      -- TODO: Redesign ProgramDB API to prevent such problems as #2241 in the
      -- future.
      ProgramDb
progdb' <- Verbosity -> ProgramDb -> IO ProgramDb
configureAllKnownPrograms Verbosity
verb ProgramDb
progdb

      Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verb GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
        Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> ConfigFlags
-> ConfigExFlags
-> InstallFlags
-> HaddockFlags
-> TestFlags
-> BenchmarkFlags
-> [UserTarget]
-> IO ()
install
          Verbosity
verb
          (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags'))
          RepoContext
repoContext
          Compiler
comp
          Platform
platform
          ProgramDb
progdb'
          GlobalFlags
globalFlags'
          ConfigFlags
configFlags'
          ConfigExFlags
configExFlags'
          InstallFlags
installFlags'
          HaddockFlags
haddockFlags'
          TestFlags
testFlags'
          BenchmarkFlags
benchmarkFlags'
          [UserTarget]
targets
    where
      -- '--run-tests' implies '--enable-tests'.
      maybeForceTests :: InstallFlags -> ConfigFlags -> ConfigFlags
maybeForceTests InstallFlags
installFlags' ConfigFlags
configFlags' =
        if Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (InstallFlags -> Flag Bool
installRunTests InstallFlags
installFlags')
          then ConfigFlags
configFlags'{configTests = toFlag True}
          else ConfigFlags
configFlags'

testAction
  :: (BuildFlags, TestFlags)
  -> [String]
  -> GlobalFlags
  -> IO ()
testAction :: (BuildFlags, TestFlags) -> [FilePath] -> Action
testAction (BuildFlags
buildFlags, TestFlags
testFlags) [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (CommonSetupFlags -> Flag Verbosity
setupVerbosity (CommonSetupFlags -> Flag Verbosity)
-> CommonSetupFlags -> Flag Verbosity
forall a b. (a -> b) -> a -> b
$ BuildFlags -> CommonSetupFlags
buildCommonFlags BuildFlags
buildFlags)
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist)))
-> CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
forall a b. (a -> b) -> a -> b
$ TestFlags -> CommonSetupFlags
testCommonFlags TestFlags
testFlags)
  let buildFlags' :: BuildFlags
buildFlags' =
        BuildFlags
buildFlags
          { buildCommonFlags =
              (buildCommonFlags buildFlags)
                { setupVerbosity = setupVerbosity $ testCommonFlags testFlags
                }
          }
      checkFlags :: Check (ConfigFlags, b)
checkFlags = (Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
-> Check (ConfigFlags, b)
forall a. (Any -> a -> IO (Any, a)) -> Check a
Check ((Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
 -> Check (ConfigFlags, b))
-> (Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
-> Check (ConfigFlags, b)
forall a b. (a -> b) -> a -> b
$ \Any
_ flags :: (ConfigFlags, b)
flags@(ConfigFlags
configFlags, b
configExFlags) ->
        if Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (ConfigFlags -> Flag Bool
configTests ConfigFlags
configFlags)
          then (Any, (ConfigFlags, b)) -> IO (Any, (ConfigFlags, b))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Any
forall a. Monoid a => a
mempty, (ConfigFlags, b)
flags)
          else do
            Verbosity -> FilePath -> IO ()
info Verbosity
verbosity FilePath
"reconfiguring to enable tests"
            let flags' :: (ConfigFlags, b)
flags' =
                  ( ConfigFlags
configFlags{configTests = toFlag True}
                  , b
configExFlags
                  )
            (Any, (ConfigFlags, b)) -> IO (Any, (ConfigFlags, b))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
True, (ConfigFlags, b)
flags')

  SavedConfig
_ <-
    ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
      (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
      Verbosity
verbosity
      SymbolicPath Pkg ('Dir Dist)
distPref
      (BuildFlags -> Flag (Maybe Int)
buildNumJobs BuildFlags
buildFlags')
      Check (ConfigFlags, ConfigExFlags)
forall {b}. Check (ConfigFlags, b)
checkFlags
      []
      GlobalFlags
globalFlags
      SavedConfig
config
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    let setupOptions :: SetupScriptOptions
setupOptions = SetupScriptOptions
defaultSetupScriptOptions{useDistPref = distPref}
        testFlags' :: TestFlags
testFlags' =
          TestFlags
testFlags
            { testCommonFlags =
                (testCommonFlags testFlags){setupDistPref = toFlag distPref}
            }
        mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
testWorkingDir TestFlags
testFlags

    -- The package was just configured, so the LBI must be available.
    ComponentNames
names <-
      Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist)
-> FilePath
-> (Component -> Bool)
-> IO ComponentNames
componentNamesFromLBI
        Verbosity
verbosity
        Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
        SymbolicPath Pkg ('Dir Dist)
distPref
        FilePath
"test suites"
        (\Component
c -> case Component
c of LBI.CTest{} -> Bool
True; Component
_ -> Bool
False)
    let extraArgs' :: [FilePath]
extraArgs'
          | [FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
extraArgs = case ComponentNames
names of
              ComponentNames
ComponentNamesUnknown -> []
              ComponentNames [ComponentName]
names' ->
                [ UnqualComponentName -> FilePath
Make.unUnqualComponentName UnqualComponentName
name
                | LBI.CTestName UnqualComponentName
name <- [ComponentName]
names'
                ]
          | Bool
otherwise = [FilePath]
extraArgs

    Verbosity
-> SavedConfig
-> SymbolicPath Pkg ('Dir Dist)
-> BuildFlags
-> [FilePath]
-> IO ()
build Verbosity
verbosity SavedConfig
config SymbolicPath Pkg ('Dir Dist)
distPref BuildFlags
buildFlags' [FilePath]
extraArgs'
    Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI TestFlags
-> (TestFlags -> CommonSetupFlags)
-> (Version -> IO TestFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
      Verbosity
verbosity
      SetupScriptOptions
setupOptions
      Maybe PackageDescription
forall a. Maybe a
Nothing
      CommandUI TestFlags
Cabal.testCommand
      TestFlags -> CommonSetupFlags
Cabal.testCommonFlags
      (IO TestFlags -> Version -> IO TestFlags
forall a b. a -> b -> a
const (TestFlags -> IO TestFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TestFlags
testFlags'))
      ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs')

data ComponentNames
  = ComponentNamesUnknown
  | ComponentNames [LBI.ComponentName]

-- | Return the names of all buildable components matching a given predicate.
componentNamesFromLBI
  :: Verbosity
  -> Maybe (SymbolicPath CWD (Dir Pkg))
  -- ^ working directory
  -> SymbolicPath Pkg (Dir Dist)
  -> String
  -> (LBI.Component -> Bool)
  -> IO ComponentNames
componentNamesFromLBI :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist)
-> FilePath
-> (Component -> Bool)
-> IO ComponentNames
componentNamesFromLBI Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Dist)
distPref FilePath
targetsDescr Component -> Bool
compPred = do
  Either ConfigStateFileError LocalBuildInfo
eLBI <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist)
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetPersistBuildConfig Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Dist)
distPref
  case Either ConfigStateFileError LocalBuildInfo
eLBI of
    Left ConfigStateFileError
err -> case ConfigStateFileError
err of
      -- Note: the build config could have been generated by a custom setup
      -- script built against a different Cabal version, so it's crucial that
      -- we ignore the bad version error here.
      ConfigStateFileBadVersion PackageIdentifier
_ PackageIdentifier
_ Either ConfigStateFileError LocalBuildInfo
_ -> ComponentNames -> IO ComponentNames
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ComponentNames
ComponentNamesUnknown
      ConfigStateFileError
_ -> Verbosity -> CabalInstallException -> IO ComponentNames
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ComponentNames)
-> CabalInstallException -> IO ComponentNames
forall a b. (a -> b) -> a -> b
$ FilePath -> CabalInstallException
ConfigStateFileException (ConfigStateFileError -> FilePath
forall a. Show a => a -> FilePath
show ConfigStateFileError
err)
    Right LocalBuildInfo
lbi -> do
      let pkgDescr :: PackageDescription
pkgDescr = LocalBuildInfo -> PackageDescription
LBI.localPkgDescr LocalBuildInfo
lbi
          names :: [ComponentName]
names =
            (Component -> ComponentName) -> [Component] -> [ComponentName]
forall a b. (a -> b) -> [a] -> [b]
map Component -> ComponentName
LBI.componentName
              ([Component] -> [ComponentName])
-> ([Component] -> [Component]) -> [Component] -> [ComponentName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Component -> Bool) -> [Component] -> [Component]
forall a. (a -> Bool) -> [a] -> [a]
filter (BuildInfo -> Bool
buildable (BuildInfo -> Bool)
-> (Component -> BuildInfo) -> Component -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Component -> BuildInfo
LBI.componentBuildInfo)
              ([Component] -> [Component])
-> ([Component] -> [Component]) -> [Component] -> [Component]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Component -> Bool) -> [Component] -> [Component]
forall a. (a -> Bool) -> [a] -> [a]
filter Component -> Bool
compPred
              ([Component] -> [ComponentName]) -> [Component] -> [ComponentName]
forall a b. (a -> b) -> a -> b
$ PackageDescription -> [Component]
LBI.pkgComponents PackageDescription
pkgDescr
      if [ComponentName] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ComponentName]
names
        then do
          Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
            FilePath
"Package has no buildable "
              FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
targetsDescr
              FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"."
          IO ComponentNames
forall a. IO a
exitSuccess -- See #3215.
        else ComponentNames -> IO ComponentNames
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ComponentNames -> IO ComponentNames)
-> ComponentNames -> IO ComponentNames
forall a b. (a -> b) -> a -> b
$! ([ComponentName] -> ComponentNames
ComponentNames [ComponentName]
names)

benchmarkAction
  :: (BuildFlags, BenchmarkFlags)
  -> [String]
  -> GlobalFlags
  -> IO ()
benchmarkAction :: (BuildFlags, BenchmarkFlags) -> [FilePath] -> Action
benchmarkAction
  (BuildFlags
buildFlags, BenchmarkFlags
benchmarkFlags)
  [FilePath]
extraArgs
  GlobalFlags
globalFlags = do
    let verbosity :: Verbosity
verbosity =
          Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault
            Verbosity
normal
            (CommonSetupFlags -> Flag Verbosity
setupVerbosity (CommonSetupFlags -> Flag Verbosity)
-> CommonSetupFlags -> Flag Verbosity
forall a b. (a -> b) -> a -> b
$ BuildFlags -> CommonSetupFlags
buildCommonFlags BuildFlags
buildFlags)

    SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
    SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist)))
-> CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
forall a b. (a -> b) -> a -> b
$ BenchmarkFlags -> CommonSetupFlags
benchmarkCommonFlags BenchmarkFlags
benchmarkFlags)
    let buildFlags' :: BuildFlags
buildFlags' =
          BuildFlags
buildFlags
            { buildCommonFlags =
                (buildCommonFlags buildFlags)
                  { setupVerbosity = setupVerbosity $ benchmarkCommonFlags benchmarkFlags
                  }
            }

    let checkFlags :: Check (ConfigFlags, b)
checkFlags = (Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
-> Check (ConfigFlags, b)
forall a. (Any -> a -> IO (Any, a)) -> Check a
Check ((Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
 -> Check (ConfigFlags, b))
-> (Any -> (ConfigFlags, b) -> IO (Any, (ConfigFlags, b)))
-> Check (ConfigFlags, b)
forall a b. (a -> b) -> a -> b
$ \Any
_ flags :: (ConfigFlags, b)
flags@(ConfigFlags
configFlags, b
configExFlags) ->
          if Bool -> Flag Bool -> Bool
forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (ConfigFlags -> Flag Bool
configBenchmarks ConfigFlags
configFlags)
            then (Any, (ConfigFlags, b)) -> IO (Any, (ConfigFlags, b))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Any
forall a. Monoid a => a
mempty, (ConfigFlags, b)
flags)
            else do
              Verbosity -> FilePath -> IO ()
info Verbosity
verbosity FilePath
"reconfiguring to enable benchmarks"
              let flags' :: (ConfigFlags, b)
flags' =
                    ( ConfigFlags
configFlags{configBenchmarks = toFlag True}
                    , b
configExFlags
                    )
              (Any, (ConfigFlags, b)) -> IO (Any, (ConfigFlags, b))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
True, (ConfigFlags, b)
flags')

    SavedConfig
config' <-
      ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
        (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
        Verbosity
verbosity
        SymbolicPath Pkg ('Dir Dist)
distPref
        (BuildFlags -> Flag (Maybe Int)
buildNumJobs BuildFlags
buildFlags')
        Check (ConfigFlags, ConfigExFlags)
forall {b}. Check (ConfigFlags, b)
checkFlags
        []
        GlobalFlags
globalFlags
        SavedConfig
config
    Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      let setupOptions :: SetupScriptOptions
setupOptions = SetupScriptOptions
defaultSetupScriptOptions{useDistPref = distPref}
          benchmarkFlags' :: BenchmarkFlags
benchmarkFlags' =
            BenchmarkFlags
benchmarkFlags
              { benchmarkCommonFlags =
                  (benchmarkCommonFlags benchmarkFlags)
                    { setupDistPref = toFlag distPref
                    }
              }
          mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ BenchmarkFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
benchmarkWorkingDir BenchmarkFlags
benchmarkFlags

      -- The package was just configured, so the LBI must be available.
      ComponentNames
names <-
        Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist)
-> FilePath
-> (Component -> Bool)
-> IO ComponentNames
componentNamesFromLBI
          Verbosity
verbosity
          Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
          SymbolicPath Pkg ('Dir Dist)
distPref
          FilePath
"benchmarks"
          (\Component
c -> case Component
c of LBI.CBench{} -> Bool
True; Component
_ -> Bool
False)
      let extraArgs' :: [FilePath]
extraArgs'
            | [FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
extraArgs = case ComponentNames
names of
                ComponentNames
ComponentNamesUnknown -> []
                ComponentNames [ComponentName]
names' ->
                  [ UnqualComponentName -> FilePath
Make.unUnqualComponentName UnqualComponentName
name
                  | LBI.CBenchName UnqualComponentName
name <- [ComponentName]
names'
                  ]
            | Bool
otherwise = [FilePath]
extraArgs

      Verbosity
-> SavedConfig
-> SymbolicPath Pkg ('Dir Dist)
-> BuildFlags
-> [FilePath]
-> IO ()
build Verbosity
verbosity SavedConfig
config' SymbolicPath Pkg ('Dir Dist)
distPref BuildFlags
buildFlags' [FilePath]
extraArgs'
      Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI BenchmarkFlags
-> (BenchmarkFlags -> CommonSetupFlags)
-> (Version -> IO BenchmarkFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
        Verbosity
verbosity
        SetupScriptOptions
setupOptions
        Maybe PackageDescription
forall a. Maybe a
Nothing
        CommandUI BenchmarkFlags
Cabal.benchmarkCommand
        BenchmarkFlags -> CommonSetupFlags
Cabal.benchmarkCommonFlags
        (IO BenchmarkFlags -> Version -> IO BenchmarkFlags
forall a b. a -> b -> a
const (BenchmarkFlags -> IO BenchmarkFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BenchmarkFlags
benchmarkFlags'))
        ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs')

haddockAction :: HaddockFlags -> [String] -> Action
haddockAction :: HaddockFlags -> [FilePath] -> Action
haddockAction HaddockFlags
haddockFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = HaddockFlags -> CommonSetupFlags
haddockCommonFlags HaddockFlags
haddockFlags
      verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common)
  SavedConfig
config' <-
    ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
      (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
      Verbosity
verbosity
      SymbolicPath Pkg ('Dir Dist)
distPref
      Flag (Maybe Int)
forall a. Flag a
NoFlag
      Check (ConfigFlags, ConfigExFlags)
forall a. Monoid a => a
mempty
      []
      GlobalFlags
globalFlags
      SavedConfig
config
  let mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
setupWorkingDir CommonSetupFlags
common
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    let haddockFlags' :: HaddockFlags
haddockFlags' =
          HaddockFlags
defaultHaddockFlags
            HaddockFlags -> HaddockFlags -> HaddockFlags
forall a. Monoid a => a -> a -> a
`mappend` SavedConfig -> HaddockFlags
savedHaddockFlags SavedConfig
config'
            HaddockFlags -> HaddockFlags -> HaddockFlags
forall a. Monoid a => a -> a -> a
`mappend` HaddockFlags
haddockFlags
              { haddockCommonFlags =
                  (haddockCommonFlags haddockFlags)
                    { setupDistPref = toFlag distPref
                    }
              }
        setupScriptOptions :: SetupScriptOptions
setupScriptOptions =
          SetupScriptOptions
defaultSetupScriptOptions
            { useDistPref = distPref
            }
    Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI HaddockFlags
-> (HaddockFlags -> CommonSetupFlags)
-> (Version -> IO HaddockFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
      Verbosity
verbosity
      SetupScriptOptions
setupScriptOptions
      Maybe PackageDescription
forall a. Maybe a
Nothing
      CommandUI HaddockFlags
haddockCommand
      HaddockFlags -> CommonSetupFlags
haddockCommonFlags
      (IO HaddockFlags -> Version -> IO HaddockFlags
forall a b. a -> b -> a
const (HaddockFlags -> IO HaddockFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return HaddockFlags
haddockFlags'))
      ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (HaddockFlags -> Flag HaddockTarget
haddockForHackage HaddockFlags
haddockFlags Flag HaddockTarget -> Flag HaddockTarget -> Bool
forall a. Eq a => a -> a -> Bool
== HaddockTarget -> Flag HaddockTarget
forall a. a -> Flag a
Flag HaddockTarget
ForHackage) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      PackageDescription
pkg <- (LocalBuildInfo -> PackageDescription)
-> IO LocalBuildInfo -> IO PackageDescription
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LocalBuildInfo -> PackageDescription
LBI.localPkgDescr (Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist) -> IO LocalBuildInfo
getPersistBuildConfig Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Dist)
distPref)
      let dest :: FilePath
dest = SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref FilePath -> FilePath -> FilePath
</> FilePath
name FilePath -> FilePath -> FilePath
<.> FilePath
"tar.gz"
          name :: FilePath
name = PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
display (PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-docs"
          docDir :: FilePath
docDir = SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref FilePath -> FilePath -> FilePath
</> FilePath
"doc" FilePath -> FilePath -> FilePath
</> FilePath
"html"
      FilePath -> FilePath -> FilePath -> IO ()
createTarGzFile FilePath
dest FilePath
docDir FilePath
name
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Documentation tarball created: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
dest

cleanAction :: CleanFlags -> [String] -> Action
cleanAction :: CleanFlags -> [FilePath] -> Action
cleanAction CleanFlags
cleanFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = CleanFlags -> CommonSetupFlags
cleanCommonFlags CleanFlags
cleanFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  Either SomeException SavedConfig
load <- IO SavedConfig -> IO (Either SomeException SavedConfig)
forall e a. Exception e => IO a -> IO (Either e a)
try (Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags)
  let config :: SavedConfig
config = (SomeException -> SavedConfig)
-> (SavedConfig -> SavedConfig)
-> Either SomeException SavedConfig
-> SavedConfig
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\(SomeException e
_) -> SavedConfig
forall a. Monoid a => a
mempty) SavedConfig -> SavedConfig
forall a. a -> a
id Either SomeException SavedConfig
load
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (Flag (SymbolicPath Pkg ('Dir Dist))
 -> IO (SymbolicPath Pkg ('Dir Dist)))
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common
  let setupScriptOptions :: SetupScriptOptions
setupScriptOptions =
        SetupScriptOptions
defaultSetupScriptOptions
          { useDistPref = distPref
          , useWin32CleanHack = True
          }
      cleanFlags' :: CleanFlags
cleanFlags' =
        CleanFlags
cleanFlags
          { cleanCommonFlags =
              (cleanCommonFlags cleanFlags)
                { setupDistPref = toFlag distPref
                }
          }
  Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI CleanFlags
-> (CleanFlags -> CommonSetupFlags)
-> (Version -> IO CleanFlags)
-> (Version -> [FilePath])
-> IO ()
forall flags.
Verbosity
-> SetupScriptOptions
-> Maybe PackageDescription
-> CommandUI flags
-> (flags -> CommonSetupFlags)
-> (Version -> IO flags)
-> (Version -> [FilePath])
-> IO ()
setupWrapper
    Verbosity
verbosity
    SetupScriptOptions
setupScriptOptions
    Maybe PackageDescription
forall a. Maybe a
Nothing
    CommandUI CleanFlags
cleanCommand
    CleanFlags -> CommonSetupFlags
cleanCommonFlags
    (IO CleanFlags -> Version -> IO CleanFlags
forall a b. a -> b -> a
const (CleanFlags -> IO CleanFlags
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CleanFlags
cleanFlags'))
    ([FilePath] -> Version -> [FilePath]
forall a b. a -> b -> a
const [FilePath]
extraArgs)

listAction :: ListFlags -> [String] -> Action
listAction :: ListFlags -> [FilePath] -> Action
listAction ListFlags
listFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ListFlags -> Flag Verbosity
listVerbosity ListFlags
listFlags)
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  let configFlags' :: ConfigFlags
configFlags' = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
      configFlags :: ConfigFlags
configFlags =
        ConfigFlags
configFlags'
          { configPackageDBs =
              configPackageDBs configFlags'
                `mappend` listPackageDBs listFlags
          , configHcPath = listHcPath listFlags
          }
      globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
  Maybe (Compiler, ProgramDb)
compProgdb <-
    if ListFlags -> Bool
listNeedsCompiler ListFlags
listFlags
      then do
        (Compiler
comp, Platform
_, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags
        Maybe (Compiler, ProgramDb) -> IO (Maybe (Compiler, ProgramDb))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Compiler, ProgramDb) -> Maybe (Compiler, ProgramDb)
forall a. a -> Maybe a
Just (Compiler
comp, ProgramDb
progdb))
      else Maybe (Compiler, ProgramDb) -> IO (Maybe (Compiler, ProgramDb))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Compiler, ProgramDb)
forall a. Maybe a
Nothing
  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
    Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Maybe (Compiler, ProgramDb)
-> ListFlags
-> [FilePath]
-> IO ()
List.list
      Verbosity
verbosity
      (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags))
      RepoContext
repoContext
      Maybe (Compiler, ProgramDb)
compProgdb
      ListFlags
listFlags
      [FilePath]
extraArgs

infoAction :: InfoFlags -> [String] -> Action
infoAction :: InfoFlags -> [FilePath] -> Action
infoAction InfoFlags
infoFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (InfoFlags -> Flag Verbosity
infoVerbosity InfoFlags
infoFlags)
  [UserTarget]
targets <- Verbosity -> [FilePath] -> IO [UserTarget]
readUserTargets Verbosity
verbosity [FilePath]
extraArgs
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  let configFlags' :: ConfigFlags
configFlags' = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
      configFlags :: ConfigFlags
configFlags =
        ConfigFlags
configFlags'
          { configPackageDBs =
              configPackageDBs configFlags'
                `mappend` infoPackageDBs infoFlags
          }
      globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
  (Compiler
comp, Platform
_, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAuxEx ConfigFlags
configFlags
  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
    Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> ProgramDb
-> GlobalFlags
-> InfoFlags
-> [UserTarget]
-> IO ()
List.info
      Verbosity
verbosity
      (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags))
      RepoContext
repoContext
      Compiler
comp
      ProgramDb
progdb
      GlobalFlags
globalFlags'
      InfoFlags
infoFlags
      [UserTarget]
targets

fetchAction :: FetchFlags -> [String] -> Action
fetchAction :: FetchFlags -> [FilePath] -> Action
fetchAction FetchFlags
fetchFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (FetchFlags -> Flag Verbosity
fetchVerbosity FetchFlags
fetchFlags)
  [UserTarget]
targets <- Verbosity -> [FilePath] -> IO [UserTarget]
readUserTargets Verbosity
verbosity [FilePath]
extraArgs
  SavedConfig
config <- Verbosity -> Flag FilePath -> IO SavedConfig
loadConfig Verbosity
verbosity (GlobalFlags -> Flag FilePath
globalConfigFile GlobalFlags
globalFlags)
  let configFlags :: ConfigFlags
configFlags = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
      globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
  (Compiler
comp, Platform
platform, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags
  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
    Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> FetchFlags
-> [UserTarget]
-> IO ()
fetch
      Verbosity
verbosity
      (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags))
      RepoContext
repoContext
      Compiler
comp
      Platform
platform
      ProgramDb
progdb
      GlobalFlags
globalFlags'
      FetchFlags
fetchFlags
      [UserTarget]
targets

freezeAction :: FreezeFlags -> [String] -> Action
freezeAction :: FreezeFlags -> [FilePath] -> Action
freezeAction FreezeFlags
freezeFlags [FilePath]
_extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (FreezeFlags -> Flag Verbosity
freezeVerbosity FreezeFlags
freezeFlags)
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config Flag (SymbolicPath Pkg ('Dir Dist))
forall a. Flag a
NoFlag
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    let configFlags :: ConfigFlags
configFlags = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
        globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
    (Compiler
comp, Platform
platform, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags

    Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
      Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> FreezeFlags
-> IO ()
freeze
        Verbosity
verbosity
        (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags))
        RepoContext
repoContext
        Compiler
comp
        Platform
platform
        ProgramDb
progdb
        GlobalFlags
globalFlags'
        FreezeFlags
freezeFlags

genBoundsAction :: FreezeFlags -> [String] -> GlobalFlags -> IO ()
genBoundsAction :: FreezeFlags -> [FilePath] -> Action
genBoundsAction FreezeFlags
freezeFlags [FilePath]
_extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (FreezeFlags -> Flag Verbosity
freezeVerbosity FreezeFlags
freezeFlags)
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config Flag (SymbolicPath Pkg ('Dir Dist))
forall a. Flag a
NoFlag
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    let configFlags :: ConfigFlags
configFlags = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
        globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
    (Compiler
comp, Platform
platform, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
configFlags

    Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
      Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> FreezeFlags
-> IO ()
genBounds
        Verbosity
verbosity
        (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
configFlags))
        RepoContext
repoContext
        Compiler
comp
        Platform
platform
        ProgramDb
progdb
        GlobalFlags
globalFlags'
        FreezeFlags
freezeFlags

uploadAction :: UploadFlags -> [String] -> Action
uploadAction :: UploadFlags -> [FilePath] -> Action
uploadAction UploadFlags
uploadFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  SavedConfig
config <- Verbosity -> Flag FilePath -> IO SavedConfig
loadConfig Verbosity
verbosity (GlobalFlags -> Flag FilePath
globalConfigFile GlobalFlags
globalFlags)
  let uploadFlags' :: UploadFlags
uploadFlags' = SavedConfig -> UploadFlags
savedUploadFlags SavedConfig
config UploadFlags -> UploadFlags -> UploadFlags
forall a. Monoid a => a -> a -> a
`mappend` UploadFlags
uploadFlags
      globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
      tarfiles :: [FilePath]
tarfiles = [FilePath]
extraArgs
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
tarfiles Bool -> Bool -> Bool
&& Bool -> Bool
not (Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (UploadFlags -> Flag Bool
uploadDoc UploadFlags
uploadFlags'))) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalInstallException
UploadAction
  [FilePath] -> IO ()
checkTarFiles [FilePath]
extraArgs
  Maybe Password
maybe_password <-
    case UploadFlags -> Flag [FilePath]
uploadPasswordCmd UploadFlags
uploadFlags' of
      Flag (FilePath
xs : [FilePath]
xss) ->
        Password -> Maybe Password
forall a. a -> Maybe a
Just (Password -> Maybe Password)
-> (FilePath -> Password) -> FilePath -> Maybe Password
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Password
Password
          (FilePath -> Maybe Password) -> IO FilePath -> IO (Maybe Password)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Verbosity -> ProgramInvocation -> IO FilePath
getProgramInvocationOutput
            Verbosity
verbosity
            (FilePath -> [FilePath] -> ProgramInvocation
simpleProgramInvocation FilePath
xs [FilePath]
xss)
      Flag [FilePath]
_ -> Maybe Password -> IO (Maybe Password)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Password -> IO (Maybe Password))
-> Maybe Password -> IO (Maybe Password)
forall a b. (a -> b) -> a -> b
$ Flag Password -> Maybe Password
forall a. Flag a -> Maybe a
flagToMaybe (Flag Password -> Maybe Password)
-> Flag Password -> Maybe Password
forall a b. (a -> b) -> a -> b
$ UploadFlags -> Flag Password
uploadPassword UploadFlags
uploadFlags'
  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext -> do
    if Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (UploadFlags -> Flag Bool
uploadDoc UploadFlags
uploadFlags')
      then do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([FilePath] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FilePath]
tarfiles Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
          Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalInstallException
UploadActionDocumentation
        FilePath
tarfile <- IO FilePath
-> (FilePath -> IO FilePath) -> Maybe FilePath -> IO FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (SavedConfig -> IO FilePath
generateDocTarball SavedConfig
config) FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe FilePath -> IO FilePath) -> Maybe FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath] -> Maybe FilePath
forall a. [a] -> Maybe a
listToMaybe [FilePath]
tarfiles
        Verbosity
-> RepoContext
-> Maybe Token
-> Maybe Username
-> Maybe Password
-> IsCandidate
-> FilePath
-> IO ()
Upload.uploadDoc
          Verbosity
verbosity
          RepoContext
repoContext
          (Flag Token -> Maybe Token
forall a. Flag a -> Maybe a
flagToMaybe (Flag Token -> Maybe Token) -> Flag Token -> Maybe Token
forall a b. (a -> b) -> a -> b
$ UploadFlags -> Flag Token
uploadToken UploadFlags
uploadFlags')
          (Flag Username -> Maybe Username
forall a. Flag a -> Maybe a
flagToMaybe (Flag Username -> Maybe Username)
-> Flag Username -> Maybe Username
forall a b. (a -> b) -> a -> b
$ UploadFlags -> Flag Username
uploadUsername UploadFlags
uploadFlags')
          Maybe Password
maybe_password
          (Flag IsCandidate -> IsCandidate
forall a. WithCallStack (Flag a -> a)
fromFlag (UploadFlags -> Flag IsCandidate
uploadCandidate UploadFlags
uploadFlags'))
          FilePath
tarfile
      else do
        Verbosity
-> RepoContext
-> Maybe Token
-> Maybe Username
-> Maybe Password
-> IsCandidate
-> [FilePath]
-> IO ()
Upload.upload
          Verbosity
verbosity
          RepoContext
repoContext
          (Flag Token -> Maybe Token
forall a. Flag a -> Maybe a
flagToMaybe (Flag Token -> Maybe Token) -> Flag Token -> Maybe Token
forall a b. (a -> b) -> a -> b
$ UploadFlags -> Flag Token
uploadToken UploadFlags
uploadFlags')
          (Flag Username -> Maybe Username
forall a. Flag a -> Maybe a
flagToMaybe (Flag Username -> Maybe Username)
-> Flag Username -> Maybe Username
forall a b. (a -> b) -> a -> b
$ UploadFlags -> Flag Username
uploadUsername UploadFlags
uploadFlags')
          Maybe Password
maybe_password
          (Flag IsCandidate -> IsCandidate
forall a. WithCallStack (Flag a -> a)
fromFlag (UploadFlags -> Flag IsCandidate
uploadCandidate UploadFlags
uploadFlags'))
          [FilePath]
tarfiles
  where
    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (UploadFlags -> Flag Verbosity
uploadVerbosity UploadFlags
uploadFlags)
    checkTarFiles :: [FilePath] -> IO ()
checkTarFiles [FilePath]
tarfiles
      | Bool -> Bool
not ([FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
otherFiles) =
          Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> CabalInstallException
UploadActionOnlyArchives [FilePath]
otherFiles
      | Bool
otherwise =
          [IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
            [ do
              Bool
exists <- FilePath -> IO Bool
doesFileExist FilePath
tarfile
              Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> CabalInstallException
FileNotFound FilePath
tarfile
            | FilePath
tarfile <- [FilePath]
tarfiles
            ]
      where
        otherFiles :: [FilePath]
otherFiles = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
isTarGzFile) [FilePath]
tarfiles
        isTarGzFile :: FilePath -> Bool
isTarGzFile FilePath
file = case FilePath -> (FilePath, FilePath)
splitExtension FilePath
file of
          (FilePath
file', FilePath
".gz") -> FilePath -> FilePath
takeExtension FilePath
file' FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".tar"
          (FilePath, FilePath)
_ -> Bool
False
    generateDocTarball :: SavedConfig -> IO FilePath
generateDocTarball SavedConfig
config = do
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath
"No documentation tarball specified. "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Building a documentation tarball with default settings...\n"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"If you need to customise Haddock options, "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"run 'haddock --for-hackage' first "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"to generate a documentation tarball."
      HaddockFlags -> [FilePath] -> Action
haddockAction
        (HaddockFlags
defaultHaddockFlags{haddockForHackage = Flag ForHackage})
        []
        GlobalFlags
globalFlags
      SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config Flag (SymbolicPath Pkg ('Dir Dist))
forall a. Flag a
NoFlag
      let mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ ConfigFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
configWorkingDir (ConfigFlags -> Flag (SymbolicPath CWD ('Dir Pkg)))
-> ConfigFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
config
      PackageDescription
pkg <- (LocalBuildInfo -> PackageDescription)
-> IO LocalBuildInfo -> IO PackageDescription
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LocalBuildInfo -> PackageDescription
LBI.localPkgDescr (Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist) -> IO LocalBuildInfo
getPersistBuildConfig Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Dist)
distPref)
      FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref FilePath -> FilePath -> FilePath
</> PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
display (PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-docs" FilePath -> FilePath -> FilePath
<.> FilePath
"tar.gz"

checkAction :: CheckFlags -> [String] -> Action
checkAction :: CheckFlags -> [FilePath] -> Action
checkAction CheckFlags
checkFlags [FilePath]
extraArgs GlobalFlags
_globalFlags = do
  let verbosityFlag :: Flag Verbosity
verbosityFlag = CheckFlags -> Flag Verbosity
checkVerbosity CheckFlags
checkFlags
      verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag Flag Verbosity
verbosityFlag
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
extraArgs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$
      [FilePath] -> CabalInstallException
CheckAction [FilePath]
extraArgs
  Bool
allOk <- Verbosity -> [FilePath] -> IO Bool
Check.check (Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag Flag Verbosity
verbosityFlag) (CheckFlags -> [FilePath]
checkIgnore CheckFlags
checkFlags)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
allOk IO ()
forall a. IO a
exitFailure

formatAction :: Flag Verbosity -> [String] -> Action
formatAction :: Flag Verbosity -> [FilePath] -> Action
formatAction Flag Verbosity
verbosityFlag [FilePath]
extraArgs GlobalFlags
_globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag Flag Verbosity
verbosityFlag
  SymbolicPath Pkg 'File
path <- case [FilePath]
extraArgs of
    [] -> RelativePath Pkg 'File -> SymbolicPath Pkg 'File
forall from (to :: FileOrDir).
RelativePath from to -> SymbolicPath from to
relativeSymbolicPath (RelativePath Pkg 'File -> SymbolicPath Pkg 'File)
-> IO (RelativePath Pkg 'File) -> IO (SymbolicPath Pkg 'File)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> IO (RelativePath Pkg 'File)
tryFindPackageDesc Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing
    (FilePath
p : [FilePath]
_) -> SymbolicPath Pkg 'File -> IO (SymbolicPath Pkg 'File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SymbolicPath Pkg 'File -> IO (SymbolicPath Pkg 'File))
-> SymbolicPath Pkg 'File -> IO (SymbolicPath Pkg 'File)
forall a b. (a -> b) -> a -> b
$ FilePath -> SymbolicPath Pkg 'File
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath FilePath
p
  GenericPackageDescription
pkgDesc <- HasCallStack =>
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File
-> IO GenericPackageDescription
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File
-> IO GenericPackageDescription
readGenericPackageDescription Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing SymbolicPath Pkg 'File
path
  -- Uses 'writeFileAtomic' under the hood.
  FilePath -> GenericPackageDescription -> IO ()
writeGenericPackageDescription (SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg 'File
path) GenericPackageDescription
pkgDesc

reportAction :: ReportFlags -> [String] -> Action
reportAction :: ReportFlags -> [FilePath] -> Action
reportAction ReportFlags
reportFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ReportFlags -> Flag Verbosity
reportVerbosity ReportFlags
reportFlags)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
extraArgs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$
      [FilePath] -> CabalInstallException
ReportAction [FilePath]
extraArgs
  SavedConfig
config <- Verbosity -> Flag FilePath -> IO SavedConfig
loadConfig Verbosity
verbosity (GlobalFlags -> Flag FilePath
globalConfigFile GlobalFlags
globalFlags)
  let globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
      reportFlags' :: ReportFlags
reportFlags' = SavedConfig -> ReportFlags
savedReportFlags SavedConfig
config ReportFlags -> ReportFlags -> ReportFlags
forall a. Monoid a => a -> a -> a
`mappend` ReportFlags
reportFlags

  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
    Verbosity
-> RepoContext
-> Maybe Token
-> Maybe Username
-> Maybe Password
-> IO ()
Upload.report
      Verbosity
verbosity
      RepoContext
repoContext
      (Flag Token -> Maybe Token
forall a. Flag a -> Maybe a
flagToMaybe (Flag Token -> Maybe Token) -> Flag Token -> Maybe Token
forall a b. (a -> b) -> a -> b
$ ReportFlags -> Flag Token
reportToken ReportFlags
reportFlags')
      (Flag Username -> Maybe Username
forall a. Flag a -> Maybe a
flagToMaybe (Flag Username -> Maybe Username)
-> Flag Username -> Maybe Username
forall a b. (a -> b) -> a -> b
$ ReportFlags -> Flag Username
reportUsername ReportFlags
reportFlags')
      (Flag Password -> Maybe Password
forall a. Flag a -> Maybe a
flagToMaybe (Flag Password -> Maybe Password)
-> Flag Password -> Maybe Password
forall a b. (a -> b) -> a -> b
$ ReportFlags -> Flag Password
reportPassword ReportFlags
reportFlags')

runAction :: BuildFlags -> [String] -> Action
runAction :: BuildFlags -> [FilePath] -> Action
runAction BuildFlags
buildFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let common :: CommonSetupFlags
common = BuildFlags -> CommonSetupFlags
buildCommonFlags BuildFlags
buildFlags
      verbosity :: Verbosity
verbosity = Verbosity -> Flag Verbosity -> Verbosity
forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  SymbolicPath Pkg ('Dir Dist)
distPref <- SavedConfig
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
findSavedDistPref SavedConfig
config (Flag (SymbolicPath Pkg ('Dir Dist))
 -> IO (SymbolicPath Pkg ('Dir Dist)))
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> IO (SymbolicPath Pkg ('Dir Dist))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common
  SavedConfig
config' <-
    ((ConfigFlags, ConfigExFlags) -> [FilePath] -> Action)
-> Verbosity
-> SymbolicPath Pkg ('Dir Dist)
-> Flag (Maybe Int)
-> Check (ConfigFlags, ConfigExFlags)
-> [FilePath]
-> GlobalFlags
-> SavedConfig
-> IO SavedConfig
reconfigure
      (ConfigFlags, ConfigExFlags) -> [FilePath] -> Action
configureAction
      Verbosity
verbosity
      SymbolicPath Pkg ('Dir Dist)
distPref
      (BuildFlags -> Flag (Maybe Int)
buildNumJobs BuildFlags
buildFlags)
      Check (ConfigFlags, ConfigExFlags)
forall a. Monoid a => a
mempty
      []
      GlobalFlags
globalFlags
      SavedConfig
config
  let mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Flag a -> Maybe a
flagToMaybe (Flag (SymbolicPath CWD ('Dir Pkg))
 -> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
setupWorkingDir CommonSetupFlags
common
  Verbosity
-> FilePath -> GlobalFlags -> SavedConfig -> IO () -> IO ()
nixShell Verbosity
verbosity (SymbolicPath Pkg ('Dir Dist) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Dist)
distPref) GlobalFlags
globalFlags SavedConfig
config (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    LocalBuildInfo
lbi <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Dist) -> IO LocalBuildInfo
getPersistBuildConfig Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Dist)
distPref
    (Executable
exe, [FilePath]
exeArgs) <- Verbosity
-> LocalBuildInfo -> [FilePath] -> IO (Executable, [FilePath])
splitRunArgs Verbosity
verbosity LocalBuildInfo
lbi [FilePath]
extraArgs

    Verbosity
-> SavedConfig
-> SymbolicPath Pkg ('Dir Dist)
-> BuildFlags
-> [FilePath]
-> IO ()
build Verbosity
verbosity SavedConfig
config' SymbolicPath Pkg ('Dir Dist)
distPref BuildFlags
buildFlags [FilePath
"exe:" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
display (Executable -> UnqualComponentName
exeName Executable
exe)]
    Verbosity -> LocalBuildInfo -> Executable -> [FilePath] -> IO ()
run Verbosity
verbosity LocalBuildInfo
lbi Executable
exe [FilePath]
exeArgs

getAction :: GetFlags -> [String] -> Action
getAction :: GetFlags -> [FilePath] -> Action
getAction GetFlags
getFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (GetFlags -> Flag Verbosity
getVerbosity GetFlags
getFlags)
  [UserTarget]
targets <- Verbosity -> [FilePath] -> IO [UserTarget]
readUserTargets Verbosity
verbosity [FilePath]
extraArgs
  SavedConfig
config <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
  let globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags
  Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity (SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
config) ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
    Verbosity
-> RepoContext -> GlobalFlags -> GetFlags -> [UserTarget] -> IO ()
get
      Verbosity
verbosity
      RepoContext
repoContext
      GlobalFlags
globalFlags'
      GetFlags
getFlags
      [UserTarget]
targets

unpackAction :: GetFlags -> [String] -> Action
unpackAction :: GetFlags -> [FilePath] -> Action
unpackAction GetFlags
getFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  GetFlags -> [FilePath] -> Action
getAction GetFlags
getFlags [FilePath]
extraArgs GlobalFlags
globalFlags

initAction :: InitFlags -> [String] -> Action
initAction :: InitFlags -> [FilePath] -> Action
initAction InitFlags
initFlags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  -- it takes the first value within extraArgs (if there's one)
  -- and uses it as the root directory for the new project
  case [FilePath]
extraArgs of
    [] -> IO ()
initAction'
    [FilePath
projectDir] -> do
      Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
projectDir
      FilePath -> IO () -> IO ()
forall a. FilePath -> IO a -> IO a
withCurrentDirectory FilePath
projectDir IO ()
initAction'
    [FilePath]
_ -> Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalInstallException
InitAction
  where
    initAction' :: IO ()
initAction' = do
      SavedConfig
confFlags <- Verbosity -> GlobalFlags -> IO SavedConfig
loadConfigOrSandboxConfig Verbosity
verbosity GlobalFlags
globalFlags
      -- override with `--with-compiler` from CLI if available
      let confFlags' :: ConfigFlags
confFlags' = SavedConfig -> ConfigFlags
savedConfigureFlags SavedConfig
confFlags ConfigFlags -> ConfigFlags -> ConfigFlags
forall a. Monoid a => a -> a -> a
`mappend` ConfigFlags
compFlags
          initFlags' :: InitFlags
initFlags' = SavedConfig -> InitFlags
savedInitFlags SavedConfig
confFlags InitFlags -> InitFlags -> InitFlags
forall a. Monoid a => a -> a -> a
`mappend` InitFlags
initFlags
          globalFlags' :: GlobalFlags
globalFlags' = SavedConfig -> GlobalFlags
savedGlobalFlags SavedConfig
confFlags GlobalFlags -> GlobalFlags -> GlobalFlags
forall a. Monoid a => a -> a -> a
`mappend` GlobalFlags
globalFlags

      (Compiler
comp, Platform
_, ProgramDb
progdb) <- ConfigFlags -> IO (Compiler, Platform, ProgramDb)
configCompilerAux' ConfigFlags
confFlags'

      Verbosity -> GlobalFlags -> (RepoContext -> IO ()) -> IO ()
forall a. Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
withRepoContext Verbosity
verbosity GlobalFlags
globalFlags' ((RepoContext -> IO ()) -> IO ())
-> (RepoContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \RepoContext
repoContext ->
        Verbosity
-> PackageDBStackCWD
-> RepoContext
-> Compiler
-> ProgramDb
-> InitFlags
-> IO ()
initCmd
          Verbosity
verbosity
          (Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageDBStack -> PackageDBStackCWD
interpretPackageDBStack Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. Maybe a
Nothing (ConfigFlags -> PackageDBStack
configPackageDB' ConfigFlags
confFlags'))
          RepoContext
repoContext
          Compiler
comp
          ProgramDb
progdb
          InitFlags
initFlags'

    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (InitFlags -> Flag Verbosity
initVerbosity InitFlags
initFlags)
    compFlags :: ConfigFlags
compFlags = ConfigFlags
forall a. Monoid a => a
mempty{configHcPath = initHcPath initFlags}

userConfigAction :: UserConfigFlags -> [String] -> Action
userConfigAction :: UserConfigFlags -> [FilePath] -> Action
userConfigAction UserConfigFlags
ucflags [FilePath]
extraArgs GlobalFlags
globalFlags = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (UserConfigFlags -> Flag Verbosity
userConfigVerbosity UserConfigFlags
ucflags)
      frc :: Bool
frc = Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (UserConfigFlags -> Flag Bool
userConfigForce UserConfigFlags
ucflags)
      extraLines :: [FilePath]
extraLines = Flag [FilePath] -> [FilePath]
forall a. WithCallStack (Flag a -> a)
fromFlag (UserConfigFlags -> Flag [FilePath]
userConfigAppendLines UserConfigFlags
ucflags)
  case [FilePath]
extraArgs of
    (FilePath
"init" : [FilePath]
_) -> do
      FilePath
path <- IO FilePath
configFile
      Bool
fileExists <- FilePath -> IO Bool
doesFileExist FilePath
path
      if (Bool -> Bool
not Bool
fileExists Bool -> Bool -> Bool
|| (Bool
fileExists Bool -> Bool -> Bool
&& Bool
frc))
        then IO SavedConfig -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO SavedConfig -> IO ()) -> IO SavedConfig -> IO ()
forall a b. (a -> b) -> a -> b
$ Verbosity -> [FilePath] -> FilePath -> IO SavedConfig
createDefaultConfigFile Verbosity
verbosity [FilePath]
extraLines FilePath
path
        else Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> CabalInstallException
UserConfigAction FilePath
path
    (FilePath
"diff" : [FilePath]
_) -> (FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ FilePath -> IO ()
putStrLn ([FilePath] -> IO ()) -> IO [FilePath] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> GlobalFlags -> [FilePath] -> IO [FilePath]
userConfigDiff Verbosity
verbosity GlobalFlags
globalFlags [FilePath]
extraLines
    (FilePath
"update" : [FilePath]
_) -> Verbosity -> GlobalFlags -> [FilePath] -> IO ()
userConfigUpdate Verbosity
verbosity GlobalFlags
globalFlags [FilePath]
extraLines
    -- Error handling.
    [] -> Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalInstallException
SpecifySubcommand
    [FilePath]
_ -> Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> CabalInstallException
UnknownUserConfigSubcommand [FilePath]
extraArgs
  where
    configFile :: IO FilePath
configFile = Flag FilePath -> IO FilePath
getConfigFilePath (GlobalFlags -> Flag FilePath
globalConfigFile GlobalFlags
globalFlags)

-- | Used as an entry point when cabal-install needs to invoke itself
-- as a setup script. This can happen e.g. when doing parallel builds.
actAsSetupAction :: ActAsSetupFlags -> [String] -> Action
actAsSetupAction :: ActAsSetupFlags -> [FilePath] -> Action
actAsSetupAction ActAsSetupFlags
actAsSetupFlags [FilePath]
args GlobalFlags
_globalFlags =
  let bt :: BuildType
bt = Flag BuildType -> BuildType
forall a. WithCallStack (Flag a -> a)
fromFlag (ActAsSetupFlags -> Flag BuildType
actAsSetupBuildType ActAsSetupFlags
actAsSetupFlags)
   in case BuildType
bt of
        BuildType
Simple -> [FilePath] -> IO ()
Simple.defaultMainArgs [FilePath]
args
        BuildType
Configure ->
          SetupHooks -> [FilePath] -> IO ()
Simple.defaultMainWithSetupHooksArgs
            SetupHooks
Simple.autoconfSetupHooks
            [FilePath]
args
        BuildType
Make -> [FilePath] -> IO ()
Make.defaultMainArgs [FilePath]
args
        BuildType
Hooks -> FilePath -> IO ()
forall a. HasCallStack => FilePath -> a
error FilePath
"actAsSetupAction Hooks"
        BuildType
Custom -> FilePath -> IO ()
forall a. HasCallStack => FilePath -> a
error FilePath
"actAsSetupAction Custom"

manpageAction :: [CommandSpec action] -> ManpageFlags -> [String] -> Action
manpageAction :: forall action.
[CommandSpec action] -> ManpageFlags -> [FilePath] -> Action
manpageAction [CommandSpec action]
commands ManpageFlags
flags [FilePath]
extraArgs GlobalFlags
_ = do
  let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ManpageFlags -> Flag Verbosity
manpageVerbosity ManpageFlags
flags)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
extraArgs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Verbosity -> CabalInstallException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalInstallException -> IO ()) -> CabalInstallException -> IO ()
forall a b. (a -> b) -> a -> b
$
      [FilePath] -> CabalInstallException
ManpageAction [FilePath]
extraArgs
  FilePath
pname <- IO FilePath
getProgName
  let cabalCmd :: FilePath
cabalCmd =
        if FilePath -> FilePath
takeExtension FilePath
pname FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".exe"
          then FilePath -> FilePath
dropExtension FilePath
pname
          else FilePath
pname
  FilePath -> [CommandSpec action] -> ManpageFlags -> IO ()
forall a. FilePath -> [CommandSpec a] -> ManpageFlags -> IO ()
manpageCmd FilePath
cabalCmd [CommandSpec action]
commands ManpageFlags
flags