{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-----------------------------------------------------------------------------
{-
Work around this warning:
libraries/Cabal/Distribution/Simple.hs:78:0:
    Warning: In the use of `runTests'
             (imported from Distribution.Simple.UserHooks):
             Deprecated: "Please use the new testing interface instead!"
-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}

-- |
-- Module      :  Distribution.Simple
-- Copyright   :  Isaac Jones 2003-2005
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is the command line front end to the Simple build system. When given
-- the parsed command-line args and package information, is able to perform
-- basic commands like configure, build, install, register, etc.
--
-- This module exports the main functions that Setup.hs scripts use. It
-- re-exports the 'UserHooks' type, the standard entry points like
-- 'defaultMain' and 'defaultMainWithHooks' and the predefined sets of
-- 'UserHooks' that custom @Setup.hs@ scripts can extend to add their own
-- behaviour.
--
-- This module isn't called \"Simple\" because it's simple.  Far from
-- it.  It's called \"Simple\" because it does complicated things to
-- simple software.
--
-- The original idea was that there could be different build systems that all
-- presented the same compatible command line interfaces. There is still a
-- "Distribution.Make" system but in practice no packages use it.
module Distribution.Simple
  ( module Distribution.Package
  , module Distribution.Version
  , module Distribution.License
  , module Distribution.Simple.Compiler
  , module Language.Haskell.Extension

    -- * Simple interface
  , defaultMain
  , defaultMainNoRead
  , defaultMainArgs

    -- * Customization
  , UserHooks (..)
  , Args
  , defaultMainWithHooks
  , defaultMainWithHooksArgs
  , defaultMainWithHooksNoRead
  , defaultMainWithHooksNoReadArgs

    -- ** Standard sets of hooks
  , simpleUserHooks
  , autoconfUserHooks
  , emptyUserHooks
  ) where

import Control.Exception (try)

import Distribution.Compat.Prelude
import Prelude ()

-- local

import Distribution.Package
import Distribution.PackageDescription
import Distribution.PackageDescription.Configuration
import Distribution.Simple.Command
import Distribution.Simple.Compiler
import Distribution.Simple.PackageDescription
import Distribution.Simple.PreProcess
import Distribution.Simple.Program
import Distribution.Simple.Setup
import Distribution.Simple.UserHooks

import Distribution.Simple.Build
import Distribution.Simple.Register
import Distribution.Simple.SrcDist

import Distribution.Simple.Configure

import Distribution.License
import Distribution.Pretty
import Distribution.Simple.Bench
import Distribution.Simple.BuildPaths
import Distribution.Simple.ConfigureScript
import Distribution.Simple.Errors
import Distribution.Simple.Haddock
import Distribution.Simple.Install
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.Test
import Distribution.Simple.Utils
import Distribution.Verbosity
import Distribution.Version
import Language.Haskell.Extension

-- Base

import Distribution.Compat.ResponseFile (expandResponse)
import System.Directory
  ( doesDirectoryExist
  , doesFileExist
  , removeDirectoryRecursive
  , removeFile
  )
import System.Environment (getArgs, getProgName)
import System.FilePath (takeDirectory, (</>))

import Data.List (unionBy, (\\))

-- | A simple implementation of @main@ for a Cabal setup script.
-- It reads the package description file using IO, and performs the
-- action specified on the command line.
defaultMain :: IO ()
defaultMain :: IO ()
defaultMain = IO [String]
getArgs IO [String] -> ([String] -> 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
>>= UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
simpleUserHooks

-- | A version of 'defaultMain' that is passed the command line
-- arguments, rather than getting them from the environment.
defaultMainArgs :: [String] -> IO ()
defaultMainArgs :: [String] -> IO ()
defaultMainArgs = UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
simpleUserHooks

-- | A customizable version of 'defaultMain'.
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks UserHooks
hooks = IO [String]
getArgs IO [String] -> ([String] -> 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
>>= UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks

-- | A customizable version of 'defaultMain' that also takes the command
-- line arguments.
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
defaultMainWithHooksArgs = UserHooks -> [String] -> IO ()
defaultMainHelper

-- | Like 'defaultMain', but accepts the package description as input
-- rather than using IO to read it.
defaultMainNoRead :: GenericPackageDescription -> IO ()
defaultMainNoRead :: GenericPackageDescription -> IO ()
defaultMainNoRead = UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead UserHooks
simpleUserHooks

-- | A customizable version of 'defaultMainNoRead'.
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead UserHooks
hooks GenericPackageDescription
pkg_descr =
  IO [String]
getArgs
    IO [String] -> ([String] -> 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
>>= UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks{readDesc = return (Just pkg_descr)}

-- | A customizable version of 'defaultMainNoRead' that also takes the
-- command line arguments.
--
-- @since 2.2.0.0
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
defaultMainWithHooksNoReadArgs UserHooks
hooks GenericPackageDescription
pkg_descr =
  UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks{readDesc = return (Just pkg_descr)}

-- | The central command chooser of the Simple build system,
-- with other defaultMain functions acting as exposed callers,
-- and with 'topHandler' operating as an exceptions handler.
--
-- This uses 'expandResponse' to read response files, preprocessing
-- response files given by "@" prefixes.
--
-- Given hooks and args, this runs 'commandsRun' onto the args,
-- getting 'CommandParse' data back, which is then pattern-matched into
-- IO actions for execution, with arguments applied by the parser.
defaultMainHelper :: UserHooks -> Args -> IO ()
defaultMainHelper :: UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks [String]
args = IO () -> IO ()
forall a. IO a -> IO a
topHandler (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
  [String]
args' <- [String] -> IO [String]
expandResponse [String]
args
  CommandParse (GlobalFlags, CommandParse (IO ()))
command <- CommandUI GlobalFlags
-> [Command (IO ())]
-> [String]
-> IO (CommandParse (GlobalFlags, CommandParse (IO ())))
forall a action.
CommandUI a
-> [Command action]
-> [String]
-> IO (CommandParse (a, CommandParse action))
commandsRun ([Command (IO ())] -> CommandUI GlobalFlags
forall action. [Command action] -> CommandUI GlobalFlags
globalCommand [Command (IO ())]
commands) [Command (IO ())]
commands [String]
args'
  case CommandParse (GlobalFlags, CommandParse (IO ()))
command of
    CommandHelp String -> String
help -> (String -> String) -> IO ()
printHelp String -> String
help
    CommandList [String]
opts -> [String] -> IO ()
printOptionsList [String]
opts
    CommandErrors [String]
errs -> [String] -> IO ()
forall {b}. [String] -> IO b
printErrors [String]
errs
    CommandReadyToGo (GlobalFlags
flags, CommandParse (IO ())
commandParse) ->
      case CommandParse (IO ())
commandParse of
        CommandParse (IO ())
_
          | Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (GlobalFlags -> Flag Bool
globalVersion GlobalFlags
flags) -> IO ()
printVersion
          | Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (GlobalFlags -> Flag Bool
globalNumericVersion GlobalFlags
flags) -> IO ()
printNumericVersion
        CommandHelp String -> String
help -> (String -> String) -> IO ()
printHelp String -> String
help
        CommandList [String]
opts -> [String] -> IO ()
printOptionsList [String]
opts
        CommandErrors [String]
errs -> [String] -> IO ()
forall {b}. [String] -> IO b
printErrors [String]
errs
        CommandReadyToGo IO ()
action -> IO ()
action
  where
    printHelp :: (String -> String) -> IO ()
printHelp String -> String
help = IO String
getProgName IO String -> (String -> 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
>>= String -> IO ()
putStr (String -> IO ()) -> (String -> String) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
help
    printOptionsList :: [String] -> IO ()
printOptionsList = String -> IO ()
putStr (String -> IO ()) -> ([String] -> String) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines
    printErrors :: [String] -> IO b
printErrors [String]
errs = do
      String -> IO ()
putStr (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
errs)
      ExitCode -> IO b
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
    printNumericVersion :: IO ()
printNumericVersion = String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
cabalVersion
    printVersion :: IO ()
printVersion =
      String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
        String
"Cabal library version "
          String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
cabalVersion

    progs :: ProgramDb
progs = [Program] -> ProgramDb -> ProgramDb
addKnownPrograms (UserHooks -> [Program]
hookedPrograms UserHooks
hooks) ProgramDb
defaultProgramDb
    commands :: [Command (IO ())]
commands =
      [ ProgramDb -> CommandUI ConfigFlags
configureCommand ProgramDb
progs
          CommandUI ConfigFlags
-> (ConfigFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` \ConfigFlags
fs [String]
as -> UserHooks -> ConfigFlags -> [String] -> IO LocalBuildInfo
configureAction UserHooks
hooks ConfigFlags
fs [String]
as IO LocalBuildInfo -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      , ProgramDb -> CommandUI BuildFlags
buildCommand ProgramDb
progs CommandUI BuildFlags
-> (BuildFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> BuildFlags -> [String] -> IO ()
buildAction UserHooks
hooks
      , ProgramDb -> CommandUI ReplFlags
replCommand ProgramDb
progs CommandUI ReplFlags
-> (ReplFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> ReplFlags -> [String] -> IO ()
replAction UserHooks
hooks
      , CommandUI InstallFlags
installCommand CommandUI InstallFlags
-> (InstallFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> InstallFlags -> [String] -> IO ()
installAction UserHooks
hooks
      , CommandUI CopyFlags
copyCommand CommandUI CopyFlags
-> (CopyFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> CopyFlags -> [String] -> IO ()
copyAction UserHooks
hooks
      , CommandUI HaddockFlags
haddockCommand CommandUI HaddockFlags
-> (HaddockFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> HaddockFlags -> [String] -> IO ()
haddockAction UserHooks
hooks
      , CommandUI CleanFlags
cleanCommand CommandUI CleanFlags
-> (CleanFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> CleanFlags -> [String] -> IO ()
cleanAction UserHooks
hooks
      , CommandUI SDistFlags
sdistCommand CommandUI SDistFlags
-> (SDistFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> SDistFlags -> [String] -> IO ()
sdistAction UserHooks
hooks
      , CommandUI HscolourFlags
hscolourCommand CommandUI HscolourFlags
-> (HscolourFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> HscolourFlags -> [String] -> IO ()
hscolourAction UserHooks
hooks
      , CommandUI RegisterFlags
registerCommand CommandUI RegisterFlags
-> (RegisterFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> RegisterFlags -> [String] -> IO ()
registerAction UserHooks
hooks
      , CommandUI RegisterFlags
unregisterCommand CommandUI RegisterFlags
-> (RegisterFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> RegisterFlags -> [String] -> IO ()
unregisterAction UserHooks
hooks
      , CommandUI TestFlags
testCommand CommandUI TestFlags
-> (TestFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> TestFlags -> [String] -> IO ()
testAction UserHooks
hooks
      , CommandUI BenchmarkFlags
benchmarkCommand CommandUI BenchmarkFlags
-> (BenchmarkFlags -> [String] -> IO ()) -> Command (IO ())
forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> BenchmarkFlags -> [String] -> IO ()
benchAction UserHooks
hooks
      ]

-- | Combine the preprocessors in the given hooks with the
-- preprocessors built into cabal.
allSuffixHandlers
  :: UserHooks
  -> [PPSuffixHandler]
allSuffixHandlers :: UserHooks -> [PPSuffixHandler]
allSuffixHandlers UserHooks
hooks =
  [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
overridesPP (UserHooks -> [PPSuffixHandler]
hookedPreProcessors UserHooks
hooks) [PPSuffixHandler]
knownSuffixHandlers
  where
    overridesPP :: [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
    overridesPP :: [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
overridesPP = (PPSuffixHandler -> PPSuffixHandler -> Bool)
-> [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy (\PPSuffixHandler
x PPSuffixHandler
y -> PPSuffixHandler -> Suffix
forall a b. (a, b) -> a
fst PPSuffixHandler
x Suffix -> Suffix -> Bool
forall a. Eq a => a -> a -> Bool
== PPSuffixHandler -> Suffix
forall a b. (a, b) -> a
fst PPSuffixHandler
y)

configureAction :: UserHooks -> ConfigFlags -> Args -> IO LocalBuildInfo
configureAction :: UserHooks -> ConfigFlags -> [String] -> IO LocalBuildInfo
configureAction UserHooks
hooks ConfigFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (ConfigFlags -> Flag String
configDistPref ConfigFlags
flags)
  let flags' :: ConfigFlags
flags' =
        ConfigFlags
flags
          { configDistPref = toFlag distPref
          , configArgs = args
          }

  -- See docs for 'HookedBuildInfo'
  HookedBuildInfo
pbi <- UserHooks -> [String] -> ConfigFlags -> IO HookedBuildInfo
preConf UserHooks
hooks [String]
args ConfigFlags
flags'

  (Maybe String
mb_pd_file, GenericPackageDescription
pkg_descr0) <-
    UserHooks
-> Verbosity
-> Maybe String
-> IO (Maybe String, GenericPackageDescription)
confPkgDescr
      UserHooks
hooks
      Verbosity
verbosity
      (Flag String -> Maybe String
forall a. Flag a -> Maybe a
flagToMaybe (ConfigFlags -> Flag String
configCabalFilePath ConfigFlags
flags))

  let epkg_descr :: (GenericPackageDescription, HookedBuildInfo)
epkg_descr = (GenericPackageDescription
pkg_descr0, HookedBuildInfo
pbi)

  LocalBuildInfo
localbuildinfo0 <- UserHooks
-> (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags
-> IO LocalBuildInfo
confHook UserHooks
hooks (GenericPackageDescription, HookedBuildInfo)
epkg_descr ConfigFlags
flags'

  -- remember the .cabal filename if we know it
  -- and all the extra command line args
  let localbuildinfo :: LocalBuildInfo
localbuildinfo =
        LocalBuildInfo
localbuildinfo0
          { pkgDescrFile = mb_pd_file
          , extraConfigArgs = args
          }
  String -> LocalBuildInfo -> IO ()
writePersistBuildConfig String
distPref LocalBuildInfo
localbuildinfo

  let pkg_descr :: PackageDescription
pkg_descr = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
localbuildinfo
  UserHooks
-> [String]
-> ConfigFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postConf UserHooks
hooks [String]
args ConfigFlags
flags' PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo
  LocalBuildInfo -> IO LocalBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
localbuildinfo
  where
    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
flags)

confPkgDescr
  :: UserHooks
  -> Verbosity
  -> Maybe FilePath
  -> IO (Maybe FilePath, GenericPackageDescription)
confPkgDescr :: UserHooks
-> Verbosity
-> Maybe String
-> IO (Maybe String, GenericPackageDescription)
confPkgDescr UserHooks
hooks Verbosity
verbosity Maybe String
mb_path = do
  Maybe GenericPackageDescription
mdescr <- UserHooks -> IO (Maybe GenericPackageDescription)
readDesc UserHooks
hooks
  case Maybe GenericPackageDescription
mdescr of
    Just GenericPackageDescription
descr -> (Maybe String, GenericPackageDescription)
-> IO (Maybe String, GenericPackageDescription)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String
forall a. Maybe a
Nothing, GenericPackageDescription
descr)
    Maybe GenericPackageDescription
Nothing -> do
      String
pdfile <- case Maybe String
mb_path of
        Maybe String
Nothing -> Verbosity -> IO String
defaultPackageDesc Verbosity
verbosity
        Just String
path -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
path
      Verbosity -> String -> IO ()
info Verbosity
verbosity String
"Using Parsec parser"
      GenericPackageDescription
descr <- Verbosity -> String -> IO GenericPackageDescription
readGenericPackageDescription Verbosity
verbosity String
pdfile
      (Maybe String, GenericPackageDescription)
-> IO (Maybe String, GenericPackageDescription)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
pdfile, GenericPackageDescription
descr)

buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
buildAction :: UserHooks -> BuildFlags -> [String] -> IO ()
buildAction UserHooks
hooks BuildFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (BuildFlags -> Flag String
buildDistPref BuildFlags
flags)
  let 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
$ BuildFlags -> Flag Verbosity
buildVerbosity BuildFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: BuildFlags
flags' =
        BuildFlags
flags
          { buildDistPref = toFlag distPref
          , buildCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }

  ProgramDb
progs <-
    Verbosity
-> [(String, String)]
-> [(String, [String])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms
      Verbosity
verbosity
      (BuildFlags -> [(String, String)]
buildProgramPaths BuildFlags
flags')
      (BuildFlags -> [(String, [String])]
buildProgramArgs BuildFlags
flags')
      (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)

  Verbosity
-> (UserHooks -> [String] -> BuildFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> BuildFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> BuildFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> BuildFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> BuildFlags -> IO HookedBuildInfo
preBuild
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BuildFlags
-> IO ()
buildHook
    UserHooks
-> [String]
-> BuildFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postBuild
    (LocalBuildInfo -> IO LocalBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi{withPrograms = progs})
    UserHooks
hooks
    BuildFlags
flags'{buildArgs = args}
    [String]
args

replAction :: UserHooks -> ReplFlags -> Args -> IO ()
replAction :: UserHooks -> ReplFlags -> [String] -> IO ()
replAction UserHooks
hooks ReplFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (ReplFlags -> Flag String
replDistPref ReplFlags
flags)
  let 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
$ ReplFlags -> Flag Verbosity
replVerbosity ReplFlags
flags
      flags' :: ReplFlags
flags' = ReplFlags
flags{replDistPref = toFlag distPref}

  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  ProgramDb
progs <-
    Verbosity
-> [(String, String)]
-> [(String, [String])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms
      Verbosity
verbosity
      (ReplFlags -> [(String, String)]
replProgramPaths ReplFlags
flags')
      (ReplFlags -> [(String, [String])]
replProgramArgs ReplFlags
flags')
      (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)

  -- As far as I can tell, the only reason this doesn't use
  -- 'hookedActionWithArgs' is because the arguments of 'replHook'
  -- takes the args explicitly.  UGH.   -- ezyang
  HookedBuildInfo
pbi <- UserHooks -> [String] -> ReplFlags -> IO HookedBuildInfo
preRepl UserHooks
hooks [String]
args ReplFlags
flags'
  let pkg_descr0 :: PackageDescription
pkg_descr0 = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi
  Verbosity -> PackageDescription -> HookedBuildInfo -> IO ()
sanityCheckHookedBuildInfo Verbosity
verbosity PackageDescription
pkg_descr0 HookedBuildInfo
pbi
  let pkg_descr :: PackageDescription
pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
      lbi' :: LocalBuildInfo
lbi' =
        LocalBuildInfo
lbi
          { withPrograms = progs
          , localPkgDescr = pkg_descr
          }
  UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> ReplFlags
-> [String]
-> IO ()
replHook UserHooks
hooks PackageDescription
pkg_descr LocalBuildInfo
lbi' UserHooks
hooks ReplFlags
flags' [String]
args
  UserHooks
-> [String]
-> ReplFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postRepl UserHooks
hooks [String]
args ReplFlags
flags' PackageDescription
pkg_descr LocalBuildInfo
lbi'

hscolourAction :: UserHooks -> HscolourFlags -> Args -> IO ()
hscolourAction :: UserHooks -> HscolourFlags -> [String] -> IO ()
hscolourAction UserHooks
hooks HscolourFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (HscolourFlags -> Flag String
hscolourDistPref HscolourFlags
flags)
  let 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
$ HscolourFlags -> Flag Verbosity
hscolourVerbosity HscolourFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: HscolourFlags
flags' =
        HscolourFlags
flags
          { hscolourDistPref = toFlag distPref
          , hscolourCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }

  Verbosity
-> (UserHooks -> [String] -> HscolourFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> HscolourFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> HscolourFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> HscolourFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> HscolourFlags -> IO HookedBuildInfo
preHscolour
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> HscolourFlags
-> IO ()
hscolourHook
    UserHooks
-> [String]
-> HscolourFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postHscolour
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    HscolourFlags
flags'
    [String]
args

haddockAction :: UserHooks -> HaddockFlags -> Args -> IO ()
haddockAction :: UserHooks -> HaddockFlags -> [String] -> IO ()
haddockAction UserHooks
hooks HaddockFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (HaddockFlags -> Flag String
haddockDistPref HaddockFlags
flags)
  let 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
$ HaddockFlags -> Flag Verbosity
haddockVerbosity HaddockFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: HaddockFlags
flags' =
        HaddockFlags
flags
          { haddockDistPref = toFlag distPref
          , haddockCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }

  ProgramDb
progs <-
    Verbosity
-> [(String, String)]
-> [(String, [String])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms
      Verbosity
verbosity
      (HaddockFlags -> [(String, String)]
haddockProgramPaths HaddockFlags
flags')
      (HaddockFlags -> [(String, [String])]
haddockProgramArgs HaddockFlags
flags')
      (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)

  Verbosity
-> (UserHooks -> [String] -> HaddockFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> HaddockFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> HaddockFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> HaddockFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> HaddockFlags -> IO HookedBuildInfo
preHaddock
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> HaddockFlags
-> IO ()
haddockHook
    UserHooks
-> [String]
-> HaddockFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postHaddock
    (LocalBuildInfo -> IO LocalBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi{withPrograms = progs})
    UserHooks
hooks
    HaddockFlags
flags'{haddockArgs = args}
    [String]
args

cleanAction :: UserHooks -> CleanFlags -> Args -> IO ()
cleanAction :: UserHooks -> CleanFlags -> [String] -> IO ()
cleanAction UserHooks
hooks CleanFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (CleanFlags -> Flag String
cleanDistPref CleanFlags
flags)

  Either ConfigStateFileError LocalBuildInfo
elbi <- UserHooks
-> Verbosity
-> String
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: CleanFlags
flags' =
        CleanFlags
flags
          { cleanDistPref = toFlag distPref
          , cleanCabalFilePath = case elbi of
              Left ConfigStateFileError
_ -> Flag String
forall a. Monoid a => a
mempty
              Right LocalBuildInfo
lbi -> Maybe String -> Flag String
forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)
          }

  HookedBuildInfo
pbi <- UserHooks -> [String] -> CleanFlags -> IO HookedBuildInfo
preClean UserHooks
hooks [String]
args CleanFlags
flags'

  (Maybe String
_, GenericPackageDescription
ppd) <- UserHooks
-> Verbosity
-> Maybe String
-> IO (Maybe String, GenericPackageDescription)
confPkgDescr UserHooks
hooks Verbosity
verbosity Maybe String
forall a. Maybe a
Nothing
  -- It might seem like we are doing something clever here
  -- but we're really not: if you look at the implementation
  -- of 'clean' in the end all the package description is
  -- used for is to clear out @extra-tmp-files@.  IMO,
  -- the configure script goo should go into @dist@ too!
  --          -- ezyang
  let pkg_descr0 :: PackageDescription
pkg_descr0 = GenericPackageDescription -> PackageDescription
flattenPackageDescription GenericPackageDescription
ppd
  -- We don't sanity check for clean as an error
  -- here would prevent cleaning:
  -- sanityCheckHookedBuildInfo verbosity pkg_descr0 pbi
  let pkg_descr :: PackageDescription
pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0

  UserHooks
-> PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()
cleanHook UserHooks
hooks PackageDescription
pkg_descr () UserHooks
hooks CleanFlags
flags'
  UserHooks
-> [String] -> CleanFlags -> PackageDescription -> () -> IO ()
postClean UserHooks
hooks [String]
args CleanFlags
flags' PackageDescription
pkg_descr ()
  where
    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Verbosity
cleanVerbosity CleanFlags
flags)

copyAction :: UserHooks -> CopyFlags -> Args -> IO ()
copyAction :: UserHooks -> CopyFlags -> [String] -> IO ()
copyAction UserHooks
hooks CopyFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (CopyFlags -> Flag String
copyDistPref CopyFlags
flags)
  let 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
$ CopyFlags -> Flag Verbosity
copyVerbosity CopyFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: CopyFlags
flags' =
        CopyFlags
flags
          { copyDistPref = toFlag distPref
          , copyCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }
  Verbosity
-> (UserHooks -> [String] -> CopyFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> CopyFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> CopyFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> CopyFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> CopyFlags -> IO HookedBuildInfo
preCopy
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> CopyFlags
-> IO ()
copyHook
    UserHooks
-> [String]
-> CopyFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postCopy
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    CopyFlags
flags'{copyArgs = args}
    [String]
args

installAction :: UserHooks -> InstallFlags -> Args -> IO ()
installAction :: UserHooks -> InstallFlags -> [String] -> IO ()
installAction UserHooks
hooks InstallFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (InstallFlags -> Flag String
installDistPref InstallFlags
flags)
  let 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
$ InstallFlags -> Flag Verbosity
installVerbosity InstallFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: InstallFlags
flags' =
        InstallFlags
flags
          { installDistPref = toFlag distPref
          , installCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }
  Verbosity
-> (UserHooks -> [String] -> InstallFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> InstallFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> InstallFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> InstallFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> InstallFlags -> IO HookedBuildInfo
preInst
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> InstallFlags
-> IO ()
instHook
    UserHooks
-> [String]
-> InstallFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postInst
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    InstallFlags
flags'
    [String]
args

-- Since Cabal-3.4 UserHooks are completely ignored
sdistAction :: UserHooks -> SDistFlags -> Args -> IO ()
sdistAction :: UserHooks -> SDistFlags -> [String] -> IO ()
sdistAction UserHooks
_hooks SDistFlags
flags [String]
_args = do
  (Maybe String
_, GenericPackageDescription
ppd) <- UserHooks
-> Verbosity
-> Maybe String
-> IO (Maybe String, GenericPackageDescription)
confPkgDescr UserHooks
emptyUserHooks Verbosity
verbosity Maybe String
forall a. Maybe a
Nothing
  let pkg_descr :: PackageDescription
pkg_descr = GenericPackageDescription -> PackageDescription
flattenPackageDescription GenericPackageDescription
ppd
  PackageDescription
-> SDistFlags -> (String -> String) -> [PPSuffixHandler] -> IO ()
sdist PackageDescription
pkg_descr SDistFlags
flags String -> String
srcPref [PPSuffixHandler]
knownSuffixHandlers
  where
    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (SDistFlags -> Flag Verbosity
sDistVerbosity SDistFlags
flags)

testAction :: UserHooks -> TestFlags -> Args -> IO ()
testAction :: UserHooks -> TestFlags -> [String] -> IO ()
testAction UserHooks
hooks TestFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (TestFlags -> Flag String
testDistPref TestFlags
flags)
  let 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
$ TestFlags -> Flag Verbosity
testVerbosity TestFlags
flags
      flags' :: TestFlags
flags' = TestFlags
flags{testDistPref = toFlag distPref}

  Verbosity
-> (UserHooks -> [String] -> TestFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> TestFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> TestFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> TestFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedActionWithArgs
    Verbosity
verbosity
    UserHooks -> [String] -> TestFlags -> IO HookedBuildInfo
preTest
    UserHooks
-> [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
testHook
    UserHooks
-> [String]
-> TestFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postTest
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    TestFlags
flags'
    [String]
args

benchAction :: UserHooks -> BenchmarkFlags -> Args -> IO ()
benchAction :: UserHooks -> BenchmarkFlags -> [String] -> IO ()
benchAction UserHooks
hooks BenchmarkFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (BenchmarkFlags -> Flag String
benchmarkDistPref BenchmarkFlags
flags)
  let 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
$ BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity BenchmarkFlags
flags
      flags' :: BenchmarkFlags
flags' = BenchmarkFlags
flags{benchmarkDistPref = toFlag distPref}
  Verbosity
-> (UserHooks -> [String] -> BenchmarkFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> BenchmarkFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> BenchmarkFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedActionWithArgs
    Verbosity
verbosity
    UserHooks -> [String] -> BenchmarkFlags -> IO HookedBuildInfo
preBench
    UserHooks
-> [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchHook
    UserHooks
-> [String]
-> BenchmarkFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postBench
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    BenchmarkFlags
flags'
    [String]
args

registerAction :: UserHooks -> RegisterFlags -> Args -> IO ()
registerAction :: UserHooks -> RegisterFlags -> [String] -> IO ()
registerAction UserHooks
hooks RegisterFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (RegisterFlags -> Flag String
regDistPref RegisterFlags
flags)
  let 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
$ RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: RegisterFlags
flags' =
        RegisterFlags
flags
          { regDistPref = toFlag distPref
          , regCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }
  Verbosity
-> (UserHooks -> [String] -> RegisterFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> RegisterFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> RegisterFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> RegisterFlags -> IO HookedBuildInfo
preReg
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> IO ()
regHook
    UserHooks
-> [String]
-> RegisterFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postReg
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    RegisterFlags
flags'{regArgs = args}
    [String]
args

unregisterAction :: UserHooks -> RegisterFlags -> Args -> IO ()
unregisterAction :: UserHooks -> RegisterFlags -> [String] -> IO ()
unregisterAction UserHooks
hooks RegisterFlags
flags [String]
args = do
  String
distPref <- Flag String -> IO String
findDistPrefOrDefault (RegisterFlags -> Flag String
regDistPref RegisterFlags
flags)
  let 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
$ RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags
flags
  LocalBuildInfo
lbi <- UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref
  let flags' :: RegisterFlags
flags' =
        RegisterFlags
flags
          { regDistPref = toFlag distPref
          , regCabalFilePath = maybeToFlag (cabalFilePath lbi)
          }
  Verbosity
-> (UserHooks -> [String] -> RegisterFlags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> RegisterFlags
    -> IO ())
-> (UserHooks
    -> [String]
    -> RegisterFlags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction
    Verbosity
verbosity
    UserHooks -> [String] -> RegisterFlags -> IO HookedBuildInfo
preUnreg
    UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> IO ()
unregHook
    UserHooks
-> [String]
-> RegisterFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postUnreg
    (UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref)
    UserHooks
hooks
    RegisterFlags
flags'
    [String]
args

hookedAction
  :: Verbosity
  -> (UserHooks -> Args -> flags -> IO HookedBuildInfo)
  -> ( UserHooks
       -> PackageDescription
       -> LocalBuildInfo
       -> UserHooks
       -> flags
       -> IO ()
     )
  -> ( UserHooks
       -> Args
       -> flags
       -> PackageDescription
       -> LocalBuildInfo
       -> IO ()
     )
  -> IO LocalBuildInfo
  -> UserHooks
  -> flags
  -> Args
  -> IO ()
hookedAction :: forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedAction Verbosity
verbosity UserHooks -> [String] -> flags -> IO HookedBuildInfo
pre_hook UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> flags
-> IO ()
cmd_hook =
  Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedActionWithArgs
    Verbosity
verbosity
    UserHooks -> [String] -> flags -> IO HookedBuildInfo
pre_hook
    ( \UserHooks
h [String]
_ PackageDescription
pd LocalBuildInfo
lbi UserHooks
uh flags
flags ->
        UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> flags
-> IO ()
cmd_hook UserHooks
h PackageDescription
pd LocalBuildInfo
lbi UserHooks
uh flags
flags
    )

hookedActionWithArgs
  :: Verbosity
  -> (UserHooks -> Args -> flags -> IO HookedBuildInfo)
  -> ( UserHooks
       -> Args
       -> PackageDescription
       -> LocalBuildInfo
       -> UserHooks
       -> flags
       -> IO ()
     )
  -> ( UserHooks
       -> Args
       -> flags
       -> PackageDescription
       -> LocalBuildInfo
       -> IO ()
     )
  -> IO LocalBuildInfo
  -> UserHooks
  -> flags
  -> Args
  -> IO ()
hookedActionWithArgs :: forall flags.
Verbosity
-> (UserHooks -> [String] -> flags -> IO HookedBuildInfo)
-> (UserHooks
    -> [String]
    -> PackageDescription
    -> LocalBuildInfo
    -> UserHooks
    -> flags
    -> IO ())
-> (UserHooks
    -> [String]
    -> flags
    -> PackageDescription
    -> LocalBuildInfo
    -> IO ())
-> IO LocalBuildInfo
-> UserHooks
-> flags
-> [String]
-> IO ()
hookedActionWithArgs
  Verbosity
verbosity
  UserHooks -> [String] -> flags -> IO HookedBuildInfo
pre_hook
  UserHooks
-> [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> flags
-> IO ()
cmd_hook
  UserHooks
-> [String]
-> flags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
post_hook
  IO LocalBuildInfo
get_build_config
  UserHooks
hooks
  flags
flags
  [String]
args = do
    HookedBuildInfo
pbi <- UserHooks -> [String] -> flags -> IO HookedBuildInfo
pre_hook UserHooks
hooks [String]
args flags
flags
    LocalBuildInfo
lbi0 <- IO LocalBuildInfo
get_build_config
    let pkg_descr0 :: PackageDescription
pkg_descr0 = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi0
    Verbosity -> PackageDescription -> HookedBuildInfo -> IO ()
sanityCheckHookedBuildInfo Verbosity
verbosity PackageDescription
pkg_descr0 HookedBuildInfo
pbi
    let pkg_descr :: PackageDescription
pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
        lbi :: LocalBuildInfo
lbi = LocalBuildInfo
lbi0{localPkgDescr = pkg_descr}
    UserHooks
-> [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> flags
-> IO ()
cmd_hook UserHooks
hooks [String]
args PackageDescription
pkg_descr LocalBuildInfo
lbi UserHooks
hooks flags
flags
    UserHooks
-> [String]
-> flags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
post_hook UserHooks
hooks [String]
args flags
flags PackageDescription
pkg_descr LocalBuildInfo
lbi

sanityCheckHookedBuildInfo
  :: Verbosity -> PackageDescription -> HookedBuildInfo -> IO ()
sanityCheckHookedBuildInfo :: Verbosity -> PackageDescription -> HookedBuildInfo -> IO ()
sanityCheckHookedBuildInfo
  Verbosity
verbosity
  (PackageDescription{library :: PackageDescription -> Maybe Library
library = Maybe Library
Nothing})
  (Just BuildInfo
_, [(UnqualComponentName, BuildInfo)]
_) =
    Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ CabalException
NoLibraryForPackage
sanityCheckHookedBuildInfo Verbosity
verbosity PackageDescription
pkg_descr (Maybe BuildInfo
_, [(UnqualComponentName, BuildInfo)]
hookExes)
  | UnqualComponentName
exe1 : [UnqualComponentName]
_ <- [UnqualComponentName]
nonExistant =
      Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> CabalException
SanityCheckHookedBuildInfo UnqualComponentName
exe1
  where
    pkgExeNames :: [UnqualComponentName]
pkgExeNames = [UnqualComponentName] -> [UnqualComponentName]
forall a. Eq a => [a] -> [a]
nub ((Executable -> UnqualComponentName)
-> [Executable] -> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> UnqualComponentName
exeName (PackageDescription -> [Executable]
executables PackageDescription
pkg_descr))
    hookExeNames :: [UnqualComponentName]
hookExeNames = [UnqualComponentName] -> [UnqualComponentName]
forall a. Eq a => [a] -> [a]
nub (((UnqualComponentName, BuildInfo) -> UnqualComponentName)
-> [(UnqualComponentName, BuildInfo)] -> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, BuildInfo) -> UnqualComponentName
forall a b. (a, b) -> a
fst [(UnqualComponentName, BuildInfo)]
hookExes)
    nonExistant :: [UnqualComponentName]
nonExistant = [UnqualComponentName]
hookExeNames [UnqualComponentName]
-> [UnqualComponentName] -> [UnqualComponentName]
forall a. Eq a => [a] -> [a] -> [a]
\\ [UnqualComponentName]
pkgExeNames
sanityCheckHookedBuildInfo Verbosity
_ PackageDescription
_ HookedBuildInfo
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Try to read the 'localBuildInfoFile'
tryGetBuildConfig
  :: UserHooks
  -> Verbosity
  -> FilePath
  -> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetBuildConfig :: UserHooks
-> Verbosity
-> String
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetBuildConfig UserHooks
u Verbosity
v = IO LocalBuildInfo
-> IO (Either ConfigStateFileError LocalBuildInfo)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO LocalBuildInfo
 -> IO (Either ConfigStateFileError LocalBuildInfo))
-> (String -> IO LocalBuildInfo)
-> String
-> IO (Either ConfigStateFileError LocalBuildInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
u Verbosity
v

-- | Read the 'localBuildInfoFile' or throw an exception.
getBuildConfig :: UserHooks -> Verbosity -> FilePath -> IO LocalBuildInfo
getBuildConfig :: UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref = do
  LocalBuildInfo
lbi_wo_programs <- String -> IO LocalBuildInfo
getPersistBuildConfig String
distPref
  -- Restore info about unconfigured programs, since it is not serialized
  let lbi :: LocalBuildInfo
lbi =
        LocalBuildInfo
lbi_wo_programs
          { withPrograms =
              restoreProgramDb
                (builtinPrograms ++ hookedPrograms hooks)
                (withPrograms lbi_wo_programs)
          }

  case LocalBuildInfo -> Maybe String
pkgDescrFile LocalBuildInfo
lbi of
    Maybe String
Nothing -> LocalBuildInfo -> IO LocalBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi
    Just String
pkg_descr_file -> do
      Bool
outdated <- String -> String -> IO Bool
checkPersistBuildConfigOutdated String
distPref String
pkg_descr_file
      if Bool
outdated
        then String -> LocalBuildInfo -> IO LocalBuildInfo
reconfigure String
pkg_descr_file LocalBuildInfo
lbi
        else LocalBuildInfo -> IO LocalBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi
  where
    reconfigure :: FilePath -> LocalBuildInfo -> IO LocalBuildInfo
    reconfigure :: String -> LocalBuildInfo -> IO LocalBuildInfo
reconfigure String
pkg_descr_file LocalBuildInfo
lbi = do
      Verbosity -> String -> IO ()
notice Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
        String
pkg_descr_file
          String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" has been changed. "
          String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Re-configuring with most recently used options. "
          String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"If this fails, please run configure manually.\n"
      let cFlags :: ConfigFlags
cFlags = LocalBuildInfo -> ConfigFlags
configFlags LocalBuildInfo
lbi
      let cFlags' :: ConfigFlags
cFlags' =
            ConfigFlags
cFlags
              { -- Since the list of unconfigured programs is not serialized,
                -- restore it to the same value as normally used at the beginning
                -- of a configure run:
                configPrograms_ =
                  fmap
                    ( restoreProgramDb
                        (builtinPrograms ++ hookedPrograms hooks)
                    )
                    `fmap` configPrograms_ cFlags
              , -- Use the current, not saved verbosity level:
                configVerbosity = Flag verbosity
              }
      UserHooks -> ConfigFlags -> [String] -> IO LocalBuildInfo
configureAction UserHooks
hooks ConfigFlags
cFlags' (LocalBuildInfo -> [String]
extraConfigArgs LocalBuildInfo
lbi)

-- --------------------------------------------------------------------------
-- Cleaning

clean :: PackageDescription -> CleanFlags -> IO ()
clean :: PackageDescription -> CleanFlags -> IO ()
clean PackageDescription
pkg_descr CleanFlags
flags = do
  let distPref :: String
distPref = String -> Flag String -> String
forall a. a -> Flag a -> a
fromFlagOrDefault String
defaultDistPref (Flag String -> String) -> Flag String -> String
forall a b. (a -> b) -> a -> b
$ CleanFlags -> Flag String
cleanDistPref CleanFlags
flags
  Verbosity -> String -> IO ()
notice Verbosity
verbosity String
"cleaning..."

  Maybe LocalBuildInfo
maybeConfig <-
    if Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Bool
cleanSaveConf CleanFlags
flags)
      then String -> IO (Maybe LocalBuildInfo)
maybeGetPersistBuildConfig String
distPref
      else Maybe LocalBuildInfo -> IO (Maybe LocalBuildInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LocalBuildInfo
forall a. Maybe a
Nothing

  -- remove the whole dist/ directory rather than tracking exactly what files
  -- we created in there.
  String -> IO () -> IO ()
chattyTry String
"removing dist/" (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Bool
exists <- String -> IO Bool
doesDirectoryExist String
distPref
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
exists (String -> IO ()
removeDirectoryRecursive String
distPref)

  -- Any extra files the user wants to remove
  (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ String -> IO ()
removeFileOrDirectory (PackageDescription -> [String]
extraTmpFiles PackageDescription
pkg_descr)

  -- If the user wanted to save the config, write it back
  (LocalBuildInfo -> IO ()) -> Maybe LocalBuildInfo -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (String -> LocalBuildInfo -> IO ()
writePersistBuildConfig String
distPref) Maybe LocalBuildInfo
maybeConfig
  where
    removeFileOrDirectory :: FilePath -> IO ()
    removeFileOrDirectory :: String -> IO ()
removeFileOrDirectory String
fname = do
      Bool
isDir <- String -> IO Bool
doesDirectoryExist String
fname
      Bool
isFile <- String -> IO Bool
doesFileExist String
fname
      if Bool
isDir
        then String -> IO ()
removeDirectoryRecursive String
fname
        else Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFile (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
removeFile String
fname
    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Verbosity
cleanVerbosity CleanFlags
flags)

-- --------------------------------------------------------------------------
-- Default hooks

-- | Hooks that correspond to a plain instantiation of the
-- \"simple\" build system
simpleUserHooks :: UserHooks
simpleUserHooks :: UserHooks
simpleUserHooks =
  UserHooks
emptyUserHooks
    { confHook = configure
    , postConf = finalChecks
    , buildHook = defaultBuildHook
    , replHook = defaultReplHook
    , copyHook = \PackageDescription
desc LocalBuildInfo
lbi UserHooks
_ CopyFlags
f -> PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install PackageDescription
desc LocalBuildInfo
lbi CopyFlags
f
    , -- 'install' has correct 'copy' behavior with params
      testHook = defaultTestHook
    , benchHook = defaultBenchHook
    , instHook = defaultInstallHook
    , cleanHook = \PackageDescription
p ()
_ UserHooks
_ CleanFlags
f -> PackageDescription -> CleanFlags -> IO ()
clean PackageDescription
p CleanFlags
f
    , hscolourHook = \PackageDescription
p LocalBuildInfo
l UserHooks
h HscolourFlags
f -> PackageDescription
-> LocalBuildInfo -> [PPSuffixHandler] -> HscolourFlags -> IO ()
hscolour PackageDescription
p LocalBuildInfo
l (UserHooks -> [PPSuffixHandler]
allSuffixHandlers UserHooks
h) HscolourFlags
f
    , haddockHook = \PackageDescription
p LocalBuildInfo
l UserHooks
h HaddockFlags
f -> PackageDescription
-> LocalBuildInfo -> [PPSuffixHandler] -> HaddockFlags -> IO ()
haddock PackageDescription
p LocalBuildInfo
l (UserHooks -> [PPSuffixHandler]
allSuffixHandlers UserHooks
h) HaddockFlags
f
    , regHook = defaultRegHook
    , unregHook = \PackageDescription
p LocalBuildInfo
l UserHooks
_ RegisterFlags
f -> PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO ()
unregister PackageDescription
p LocalBuildInfo
l RegisterFlags
f
    }
  where
    finalChecks :: p -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
finalChecks p
_args ConfigFlags
flags PackageDescription
pkg_descr LocalBuildInfo
lbi =
      PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
checkForeignDeps PackageDescription
pkg_descr LocalBuildInfo
lbi (Verbosity -> Verbosity
lessVerbose Verbosity
verbosity)
      where
        verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
flags)

-- | Basic autoconf 'UserHooks':
--
-- * 'postConf' runs @.\/configure@, if present.
--
-- * the pre-hooks, except for pre-conf, read additional build information from
--   /package/@.buildinfo@, if present.
--
-- Thus @configure@ can use local system information to generate
-- /package/@.buildinfo@ and possibly other files.
autoconfUserHooks :: UserHooks
autoconfUserHooks :: UserHooks
autoconfUserHooks =
  UserHooks
simpleUserHooks
    { postConf = defaultPostConf
    , preBuild = readHookWithArgs buildVerbosity buildDistPref
    , preRepl = readHookWithArgs replVerbosity replDistPref
    , preCopy = readHookWithArgs copyVerbosity copyDistPref
    , preClean = readHook cleanVerbosity cleanDistPref
    , preInst = readHook installVerbosity installDistPref
    , preHscolour = readHook hscolourVerbosity hscolourDistPref
    , preHaddock = readHookWithArgs haddockVerbosity haddockDistPref
    , preReg = readHook regVerbosity regDistPref
    , preUnreg = readHook regVerbosity regDistPref
    , preTest = readHookWithArgs testVerbosity testDistPref
    , preBench = readHookWithArgs benchmarkVerbosity benchmarkDistPref
    }
  where
    defaultPostConf
      :: Args
      -> ConfigFlags
      -> PackageDescription
      -> LocalBuildInfo
      -> IO ()
    defaultPostConf :: [String]
-> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
defaultPostConf [String]
args ConfigFlags
flags PackageDescription
pkg_descr LocalBuildInfo
lbi =
      do
        let verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
flags)
            baseDir :: LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi' =
              String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe
                String
""
                (String -> String
takeDirectory (String -> String) -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi')
        Bool
confExists <- String -> IO Bool
doesFileExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ (LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi) String -> String -> String
</> String
"configure"
        if Bool
confExists
          then
            Verbosity -> ConfigFlags -> LocalBuildInfo -> IO ()
runConfigureScript
              Verbosity
verbosity
              ConfigFlags
flags
              LocalBuildInfo
lbi
          else Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
 Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalException
ConfigureScriptNotFound

        HookedBuildInfo
pbi <- Verbosity -> String -> IO HookedBuildInfo
getHookedBuildInfo Verbosity
verbosity (LocalBuildInfo -> String
buildDir LocalBuildInfo
lbi)
        Verbosity -> PackageDescription -> HookedBuildInfo -> IO ()
sanityCheckHookedBuildInfo Verbosity
verbosity PackageDescription
pkg_descr HookedBuildInfo
pbi
        let pkg_descr' :: PackageDescription
pkg_descr' = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr
            lbi' :: LocalBuildInfo
lbi' = LocalBuildInfo
lbi{localPkgDescr = pkg_descr'}
        UserHooks
-> [String]
-> ConfigFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postConf UserHooks
simpleUserHooks [String]
args ConfigFlags
flags PackageDescription
pkg_descr' LocalBuildInfo
lbi'

    readHookWithArgs
      :: (a -> Flag Verbosity)
      -> (a -> Flag FilePath)
      -> Args
      -> a
      -> IO HookedBuildInfo
    readHookWithArgs :: forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHookWithArgs a -> Flag Verbosity
get_verbosity a -> Flag String
get_dist_pref [String]
_ a
flags = do
      String
dist_dir <- Flag String -> IO String
findDistPrefOrDefault (a -> Flag String
get_dist_pref a
flags)
      Verbosity -> String -> IO HookedBuildInfo
getHookedBuildInfo Verbosity
verbosity (String
dist_dir String -> String -> String
</> String
"build")
      where
        verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (a -> Flag Verbosity
get_verbosity a
flags)

    readHook
      :: (a -> Flag Verbosity)
      -> (a -> Flag FilePath)
      -> Args
      -> a
      -> IO HookedBuildInfo
    readHook :: forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook a -> Flag Verbosity
get_verbosity a -> Flag String
get_dist_pref [String]
a a
flags = do
      [String] -> IO ()
noExtraFlags [String]
a
      String
dist_dir <- Flag String -> IO String
findDistPrefOrDefault (a -> Flag String
get_dist_pref a
flags)
      Verbosity -> String -> IO HookedBuildInfo
getHookedBuildInfo Verbosity
verbosity (String
dist_dir String -> String -> String
</> String
"build")
      where
        verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (a -> Flag Verbosity
get_verbosity a
flags)

getHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo
getHookedBuildInfo :: Verbosity -> String -> IO HookedBuildInfo
getHookedBuildInfo Verbosity
verbosity String
build_dir = do
  Maybe String
maybe_infoFile <- Verbosity -> String -> IO (Maybe String)
findHookedPackageDesc Verbosity
verbosity String
build_dir
  case Maybe String
maybe_infoFile of
    Maybe String
Nothing -> HookedBuildInfo -> IO HookedBuildInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return HookedBuildInfo
emptyHookedBuildInfo
    Just String
infoFile -> do
      Verbosity -> String -> IO ()
info Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Reading parameters from " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
infoFile
      Verbosity -> String -> IO HookedBuildInfo
readHookedBuildInfo Verbosity
verbosity String
infoFile

defaultTestHook
  :: Args
  -> PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> TestFlags
  -> IO ()
defaultTestHook :: [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
defaultTestHook [String]
args PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
_ TestFlags
flags =
  [String]
-> PackageDescription -> LocalBuildInfo -> TestFlags -> IO ()
test [String]
args PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo TestFlags
flags

defaultBenchHook
  :: Args
  -> PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> BenchmarkFlags
  -> IO ()
defaultBenchHook :: [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
defaultBenchHook [String]
args PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
_ BenchmarkFlags
flags =
  [String]
-> PackageDescription -> LocalBuildInfo -> BenchmarkFlags -> IO ()
bench [String]
args PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo BenchmarkFlags
flags

defaultInstallHook
  :: PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> InstallFlags
  -> IO ()
defaultInstallHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
defaultInstallHook PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
_ InstallFlags
flags = do
  let copyFlags :: CopyFlags
copyFlags =
        CopyFlags
defaultCopyFlags
          { copyDistPref = installDistPref flags
          , copyDest = installDest flags
          , copyVerbosity = installVerbosity flags
          }
  PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo CopyFlags
copyFlags
  let registerFlags :: RegisterFlags
registerFlags =
        RegisterFlags
defaultRegisterFlags
          { regDistPref = installDistPref flags
          , regInPlace = installInPlace flags
          , regPackageDB = installPackageDB flags
          , regVerbosity = installVerbosity flags
          }
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PackageDescription -> Bool
hasLibs PackageDescription
pkg_descr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO ()
register PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo RegisterFlags
registerFlags

defaultBuildHook
  :: PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> BuildFlags
  -> IO ()
defaultBuildHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
defaultBuildHook PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
hooks BuildFlags
flags =
  PackageDescription
-> LocalBuildInfo -> BuildFlags -> [PPSuffixHandler] -> IO ()
build PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo BuildFlags
flags (UserHooks -> [PPSuffixHandler]
allSuffixHandlers UserHooks
hooks)

defaultReplHook
  :: PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> ReplFlags
  -> [String]
  -> IO ()
defaultReplHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
defaultReplHook PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
hooks ReplFlags
flags [String]
args =
  PackageDescription
-> LocalBuildInfo
-> ReplFlags
-> [PPSuffixHandler]
-> [String]
-> IO ()
repl PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo ReplFlags
flags (UserHooks -> [PPSuffixHandler]
allSuffixHandlers UserHooks
hooks) [String]
args

defaultRegHook
  :: PackageDescription
  -> LocalBuildInfo
  -> UserHooks
  -> RegisterFlags
  -> IO ()
defaultRegHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
defaultRegHook PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo UserHooks
_ RegisterFlags
flags =
  if PackageDescription -> Bool
hasLibs PackageDescription
pkg_descr
    then PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO ()
register PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo RegisterFlags
flags
    else
      Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage
        (Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags
flags))
        String
"Package contains no library to register:"
        (PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg_descr)