{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Distribution.Simple (
module Distribution.Package,
module Distribution.Version,
module Distribution.License,
module Distribution.Simple.Compiler,
module Language.Haskell.Extension,
defaultMain, defaultMainNoRead, defaultMainArgs,
UserHooks(..), Args,
defaultMainWithHooks, defaultMainWithHooksArgs,
defaultMainWithHooksNoRead, defaultMainWithHooksNoReadArgs,
simpleUserHooks,
autoconfUserHooks,
emptyUserHooks,
) where
import Control.Exception (try)
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Simple.Compiler
import Distribution.Simple.UserHooks
import Distribution.Package
import Distribution.PackageDescription
import Distribution.PackageDescription.Configuration
import Distribution.Simple.Program
import Distribution.Simple.Program.Db
import Distribution.Simple.PreProcess
import Distribution.Simple.Setup
import Distribution.Simple.Command
import Distribution.Simple.Build
import Distribution.Simple.SrcDist
import Distribution.Simple.Register
import Distribution.Simple.Configure
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.Bench
import Distribution.Simple.BuildPaths
import Distribution.Simple.Test
import Distribution.Simple.Install
import Distribution.Simple.Haddock
import Distribution.Simple.Utils
import Distribution.Utils.NubList
import Distribution.Verbosity
import Language.Haskell.Extension
import Distribution.Version
import Distribution.License
import Distribution.Pretty
import Distribution.System (buildPlatform)
import System.Environment (getArgs, getProgName)
import System.Directory (removeFile, doesFileExist
,doesDirectoryExist, removeDirectoryRecursive)
import System.FilePath (searchPathSeparator, takeDirectory, (</>),
splitDirectories, dropDrive)
#ifdef mingw32_HOST_OS
import System.FilePath (normalise, splitDrive)
#endif
import Distribution.Compat.ResponseFile (expandResponse)
import Distribution.Compat.Directory (makeAbsolute)
import Distribution.Compat.Environment (getEnvironment)
import Distribution.Compat.GetShortPathName (getShortPathName)
import Data.List (unionBy, (\\))
import Distribution.PackageDescription.Parsec
defaultMain :: IO ()
defaultMain :: IO ()
defaultMain = IO [String]
getArgs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
simpleUserHooks
defaultMainArgs :: [String] -> IO ()
defaultMainArgs :: [String] -> IO ()
defaultMainArgs = UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
simpleUserHooks
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks UserHooks
hooks = IO [String]
getArgs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
defaultMainWithHooksArgs = UserHooks -> [String] -> IO ()
defaultMainHelper
defaultMainNoRead :: GenericPackageDescription -> IO ()
defaultMainNoRead :: GenericPackageDescription -> IO ()
defaultMainNoRead = UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead UserHooks
simpleUserHooks
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
defaultMainWithHooksNoRead UserHooks
hooks GenericPackageDescription
pkg_descr =
IO [String]
getArgs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks { readDesc :: IO (Maybe GenericPackageDescription)
readDesc = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just GenericPackageDescription
pkg_descr) }
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
defaultMainWithHooksNoReadArgs UserHooks
hooks GenericPackageDescription
pkg_descr =
UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks { readDesc :: IO (Maybe GenericPackageDescription)
readDesc = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just GenericPackageDescription
pkg_descr) }
defaultMainHelper :: UserHooks -> Args -> IO ()
defaultMainHelper :: UserHooks -> [String] -> IO ()
defaultMainHelper UserHooks
hooks [String]
args = forall a. IO a -> IO a
topHandler forall a b. (a -> b) -> a -> b
$ do
[String]
args' <- [String] -> IO [String]
expandResponse [String]
args
case forall a action.
CommandUI a
-> [Command action]
-> [String]
-> CommandParse (a, CommandParse action)
commandsRun (forall action. [Command action] -> CommandUI GlobalFlags
globalCommand [Command (IO ())]
commands) [Command (IO ())]
commands [String]
args' of
CommandHelp String -> String
help -> (String -> String) -> IO ()
printHelp String -> String
help
CommandList [String]
opts -> [String] -> IO ()
printOptionsList [String]
opts
CommandErrors [String]
errs -> forall {b}. [String] -> IO b
printErrors [String]
errs
CommandReadyToGo (GlobalFlags
flags, CommandParse (IO ())
commandParse) ->
case CommandParse (IO ())
commandParse of
CommandParse (IO ())
_ | forall a. WithCallStack (Flag a -> a)
fromFlag (GlobalFlags -> Flag Bool
globalVersion GlobalFlags
flags) -> IO ()
printVersion
| 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 -> 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 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO ()
putStr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
help
printOptionsList :: [String] -> IO ()
printOptionsList = String -> IO ()
putStr forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines
printErrors :: [String] -> IO b
printErrors [String]
errs = do
String -> IO ()
putStr (forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
errs)
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
printNumericVersion :: IO ()
printNumericVersion = String -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ forall a. Pretty a => a -> String
prettyShow Version
cabalVersion
printVersion :: IO ()
printVersion = String -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ String
"Cabal library version "
forall a. [a] -> [a] -> [a]
++ 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 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 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()
,ProgramDb -> CommandUI BuildFlags
buildCommand ProgramDb
progs forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> BuildFlags -> [String] -> IO ()
buildAction UserHooks
hooks
,ProgramDb -> CommandUI ShowBuildInfoFlags
showBuildInfoCommand ProgramDb
progs forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> ShowBuildInfoFlags -> [String] -> IO ()
showBuildInfoAction UserHooks
hooks
,ProgramDb -> CommandUI ReplFlags
replCommand ProgramDb
progs forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> ReplFlags -> [String] -> IO ()
replAction UserHooks
hooks
,CommandUI InstallFlags
installCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> InstallFlags -> [String] -> IO ()
installAction UserHooks
hooks
,CommandUI CopyFlags
copyCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> CopyFlags -> [String] -> IO ()
copyAction UserHooks
hooks
,CommandUI HaddockFlags
haddockCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> HaddockFlags -> [String] -> IO ()
haddockAction UserHooks
hooks
,CommandUI CleanFlags
cleanCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> CleanFlags -> [String] -> IO ()
cleanAction UserHooks
hooks
,CommandUI SDistFlags
sdistCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> SDistFlags -> [String] -> IO ()
sdistAction UserHooks
hooks
,CommandUI HscolourFlags
hscolourCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> HscolourFlags -> [String] -> IO ()
hscolourAction UserHooks
hooks
,CommandUI RegisterFlags
registerCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> RegisterFlags -> [String] -> IO ()
registerAction UserHooks
hooks
,CommandUI RegisterFlags
unregisterCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> RegisterFlags -> [String] -> IO ()
unregisterAction UserHooks
hooks
,CommandUI TestFlags
testCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> TestFlags -> [String] -> IO ()
testAction UserHooks
hooks
,CommandUI BenchmarkFlags
benchmarkCommand forall flags action.
CommandUI flags -> (flags -> [String] -> action) -> Command action
`commandAddAction` UserHooks -> BenchmarkFlags -> [String] -> IO ()
benchAction UserHooks
hooks
]
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 = forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy (\PPSuffixHandler
x PPSuffixHandler
y -> forall a b. (a, b) -> a
fst PPSuffixHandler
x forall a. Eq a => a -> a -> Bool
== 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 :: Flag String
configDistPref = forall a. a -> Flag a
toFlag String
distPref
, configArgs :: [String]
configArgs = [String]
args }
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
(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'
let localbuildinfo :: LocalBuildInfo
localbuildinfo = LocalBuildInfo
localbuildinfo0 {
pkgDescrFile :: Maybe String
pkgDescrFile = Maybe String
mb_pd_file,
extraConfigArgs :: [String]
extraConfigArgs = [String]
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
forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
localbuildinfo
where
verbosity :: 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return (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 -> 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
forall (m :: * -> *) a. Monad m => a -> m a
return (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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
buildDistPref = forall a. a -> Flag a
toFlag String
distPref
, buildCabalFilePath :: Flag String
buildCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
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)
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
(forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi { withPrograms :: ProgramDb
withPrograms = ProgramDb
progs })
UserHooks
hooks BuildFlags
flags' { buildArgs :: [String]
buildArgs = [String]
args } [String]
args
showBuildInfoAction :: UserHooks -> ShowBuildInfoFlags -> Args -> IO ()
showBuildInfoAction :: UserHooks -> ShowBuildInfoFlags -> [String] -> IO ()
showBuildInfoAction UserHooks
hooks (ShowBuildInfoFlags BuildFlags
flags Maybe String
fileOutput) [String]
args = do
String
distPref <- Flag String -> IO String
findDistPrefOrDefault (BuildFlags -> Flag String
buildDistPref BuildFlags
flags)
let verbosity :: Verbosity
verbosity = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
buildDistPref = forall a. a -> Flag a
toFlag String
distPref
, buildCabalFilePath :: Flag String
buildCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
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)
HookedBuildInfo
pbi <- UserHooks -> [String] -> BuildFlags -> IO HookedBuildInfo
preBuild UserHooks
hooks [String]
args BuildFlags
flags'
let lbi' :: LocalBuildInfo
lbi' = LocalBuildInfo
lbi { withPrograms :: ProgramDb
withPrograms = ProgramDb
progs }
pkg_descr0 :: PackageDescription
pkg_descr0 = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi'
pkg_descr :: PackageDescription
pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
String
buildInfoString <- PackageDescription -> LocalBuildInfo -> BuildFlags -> IO String
showBuildInfo PackageDescription
pkg_descr LocalBuildInfo
lbi' BuildFlags
flags
case Maybe String
fileOutput of
Maybe String
Nothing -> String -> IO ()
putStr String
buildInfoString
Just String
fp -> String -> String -> IO ()
writeFile String
fp String
buildInfoString
UserHooks
-> [String]
-> BuildFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postBuild UserHooks
hooks [String]
args BuildFlags
flags' PackageDescription
pkg_descr LocalBuildInfo
lbi'
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 = forall a. WithCallStack (Flag a -> a)
fromFlag forall a b. (a -> b) -> a -> b
$ ReplFlags -> Flag Verbosity
replVerbosity ReplFlags
flags
flags' :: ReplFlags
flags' = ReplFlags
flags { replDistPref :: Flag String
replDistPref = forall a. a -> Flag a
toFlag String
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)
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 :: ProgramDb
withPrograms = ProgramDb
progs
, localPkgDescr :: PackageDescription
localPkgDescr = PackageDescription
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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
hscolourDistPref = forall a. a -> Flag a
toFlag String
distPref
, hscolourCabalFilePath :: Flag String
hscolourCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)}
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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
haddockDistPref = forall a. a -> Flag a
toFlag String
distPref
, haddockCabalFilePath :: Flag String
haddockCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
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)
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
(forall (m :: * -> *) a. Monad m => a -> m a
return LocalBuildInfo
lbi { withPrograms :: ProgramDb
withPrograms = ProgramDb
progs })
UserHooks
hooks HaddockFlags
flags' { haddockArgs :: [String]
haddockArgs = [String]
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 :: Flag String
cleanDistPref = forall a. a -> Flag a
toFlag String
distPref
, cleanCabalFilePath :: Flag String
cleanCabalFilePath = case Either ConfigStateFileError LocalBuildInfo
elbi of
Left ConfigStateFileError
_ -> forall a. Monoid a => a
mempty
Right LocalBuildInfo
lbi -> 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 forall a. Maybe a
Nothing
let pkg_descr0 :: PackageDescription
pkg_descr0 = GenericPackageDescription -> PackageDescription
flattenPackageDescription GenericPackageDescription
ppd
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 = 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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
copyDistPref = forall a. a -> Flag a
toFlag String
distPref
, copyCabalFilePath :: Flag String
copyCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)}
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 :: [String]
copyArgs = [String]
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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
installDistPref = forall a. a -> Flag a
toFlag String
distPref
, installCabalFilePath :: Flag String
installCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)}
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
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 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 = 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 = forall a. WithCallStack (Flag a -> a)
fromFlag forall a b. (a -> b) -> a -> b
$ TestFlags -> Flag Verbosity
testVerbosity TestFlags
flags
flags' :: TestFlags
flags' = TestFlags
flags { testDistPref :: Flag String
testDistPref = forall a. a -> Flag a
toFlag String
distPref }
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 = forall a. WithCallStack (Flag a -> a)
fromFlag forall a b. (a -> b) -> a -> b
$ BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity BenchmarkFlags
flags
flags' :: BenchmarkFlags
flags' = BenchmarkFlags
flags { benchmarkDistPref :: Flag String
benchmarkDistPref = forall a. a -> Flag a
toFlag String
distPref }
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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
regDistPref = forall a. a -> Flag a
toFlag String
distPref
, regCabalFilePath :: Flag String
regCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)}
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 :: [String]
regArgs = [String]
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 = forall a. WithCallStack (Flag a -> a)
fromFlag 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 :: Flag String
regDistPref = forall a. a -> Flag a
toFlag String
distPref
, regCabalFilePath :: Flag String
regCabalFilePath = forall a. Maybe a -> Flag a
maybeToFlag (LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi)}
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 =
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 :: PackageDescription
localPkgDescr = PackageDescription
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)]
_)
= forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ String
"The buildinfo contains info for a library, "
forall a. [a] -> [a] -> [a]
++ String
"but the package does not have a library."
sanityCheckHookedBuildInfo Verbosity
verbosity PackageDescription
pkg_descr (Maybe BuildInfo
_, [(UnqualComponentName, BuildInfo)]
hookExes)
| UnqualComponentName
exe1 : [UnqualComponentName]
_ <- [UnqualComponentName]
nonExistant
= forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ String
"The buildinfo contains info for an executable called '"
forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
exe1 forall a. [a] -> [a] -> [a]
++ String
"' but the package does not have a "
forall a. [a] -> [a] -> [a]
++ String
"executable with that name."
where
pkgExeNames :: [UnqualComponentName]
pkgExeNames = forall a. Eq a => [a] -> [a]
nub (forall a b. (a -> b) -> [a] -> [b]
map Executable -> UnqualComponentName
exeName (PackageDescription -> [Executable]
executables PackageDescription
pkg_descr))
hookExeNames :: [UnqualComponentName]
hookExeNames = forall a. Eq a => [a] -> [a]
nub (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(UnqualComponentName, BuildInfo)]
hookExes)
nonExistant :: [UnqualComponentName]
nonExistant = [UnqualComponentName]
hookExeNames forall a. Eq a => [a] -> [a] -> [a]
\\ [UnqualComponentName]
pkgExeNames
sanityCheckHookedBuildInfo Verbosity
_ PackageDescription
_ HookedBuildInfo
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
tryGetBuildConfig :: UserHooks -> Verbosity -> FilePath
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetBuildConfig :: UserHooks
-> Verbosity
-> String
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetBuildConfig UserHooks
u Verbosity
v = forall e a. Exception e => IO a -> IO (Either e a)
try forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
u Verbosity
v
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
let lbi :: LocalBuildInfo
lbi = LocalBuildInfo
lbi_wo_programs {
withPrograms :: ProgramDb
withPrograms = [Program] -> ProgramDb -> ProgramDb
restoreProgramDb
([Program]
builtinPrograms forall a. [a] -> [a] -> [a]
++ UserHooks -> [Program]
hookedPrograms UserHooks
hooks)
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi_wo_programs)
}
case LocalBuildInfo -> Maybe String
pkgDescrFile LocalBuildInfo
lbi of
Maybe String
Nothing -> 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 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 forall a b. (a -> b) -> a -> b
$ String
pkg_descr_file forall a. [a] -> [a] -> [a]
++ String
" has been changed. "
forall a. [a] -> [a] -> [a]
++ String
"Re-configuring with most recently used options. "
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 {
configPrograms_ :: Option' (Last' ProgramDb)
configPrograms_ = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Program] -> ProgramDb -> ProgramDb
restoreProgramDb
([Program]
builtinPrograms forall a. [a] -> [a] -> [a]
++ UserHooks -> [Program]
hookedPrograms UserHooks
hooks))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ConfigFlags -> Option' (Last' ProgramDb)
configPrograms_ ConfigFlags
cFlags,
configVerbosity :: Flag Verbosity
configVerbosity = forall a. a -> Flag a
Flag Verbosity
verbosity
}
UserHooks -> ConfigFlags -> [String] -> IO LocalBuildInfo
configureAction UserHooks
hooks ConfigFlags
cFlags' (LocalBuildInfo -> [String]
extraConfigArgs LocalBuildInfo
lbi)
clean :: PackageDescription -> CleanFlags -> IO ()
clean :: PackageDescription -> CleanFlags -> IO ()
clean PackageDescription
pkg_descr CleanFlags
flags = do
let distPref :: String
distPref = forall a. a -> Flag a -> a
fromFlagOrDefault String
defaultDistPref 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 forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Bool
cleanSaveConf CleanFlags
flags)
then String -> IO (Maybe LocalBuildInfo)
maybeGetPersistBuildConfig String
distPref
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
String -> IO () -> IO ()
chattyTry String
"removing dist/" forall a b. (a -> b) -> a -> b
$ do
Bool
exists <- String -> IO Bool
doesDirectoryExist String
distPref
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
exists (String -> IO ()
removeDirectoryRecursive String
distPref)
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)
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 forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFile forall a b. (a -> b) -> a -> b
$ String -> IO ()
removeFile String
fname
verbosity :: Verbosity
verbosity = forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Verbosity
cleanVerbosity CleanFlags
flags)
simpleUserHooks :: UserHooks
simpleUserHooks :: UserHooks
simpleUserHooks =
UserHooks
emptyUserHooks {
confHook :: (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags -> IO LocalBuildInfo
confHook = (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags -> IO LocalBuildInfo
configure,
postConf :: [String]
-> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
postConf = forall {p}.
p -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
finalChecks,
buildHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
buildHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
defaultBuildHook,
replHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
replHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
defaultReplHook,
copyHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
copyHook = \PackageDescription
desc LocalBuildInfo
lbi UserHooks
_ CopyFlags
f -> PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install PackageDescription
desc LocalBuildInfo
lbi CopyFlags
f,
testHook :: [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
testHook = [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
defaultTestHook,
benchHook :: [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchHook = [String]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
defaultBenchHook,
instHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
instHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
defaultInstallHook,
cleanHook :: PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()
cleanHook = \PackageDescription
p ()
_ UserHooks
_ CleanFlags
f -> PackageDescription -> CleanFlags -> IO ()
clean PackageDescription
p CleanFlags
f,
hscolourHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
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
-> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
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 :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
regHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
defaultRegHook,
unregHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
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 = forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
flags)
autoconfUserHooks :: UserHooks
autoconfUserHooks :: UserHooks
autoconfUserHooks
= UserHooks
simpleUserHooks
{
postConf :: [String]
-> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
postConf = [String]
-> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
defaultPostConf,
preBuild :: [String] -> BuildFlags -> IO HookedBuildInfo
preBuild = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHookWithArgs BuildFlags -> Flag Verbosity
buildVerbosity BuildFlags -> Flag String
buildDistPref,
preCopy :: [String] -> CopyFlags -> IO HookedBuildInfo
preCopy = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHookWithArgs CopyFlags -> Flag Verbosity
copyVerbosity CopyFlags -> Flag String
copyDistPref,
preClean :: [String] -> CleanFlags -> IO HookedBuildInfo
preClean = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook CleanFlags -> Flag Verbosity
cleanVerbosity CleanFlags -> Flag String
cleanDistPref,
preInst :: [String] -> InstallFlags -> IO HookedBuildInfo
preInst = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook InstallFlags -> Flag Verbosity
installVerbosity InstallFlags -> Flag String
installDistPref,
preHscolour :: [String] -> HscolourFlags -> IO HookedBuildInfo
preHscolour = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook HscolourFlags -> Flag Verbosity
hscolourVerbosity HscolourFlags -> Flag String
hscolourDistPref,
preHaddock :: [String] -> HaddockFlags -> IO HookedBuildInfo
preHaddock = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHookWithArgs HaddockFlags -> Flag Verbosity
haddockVerbosity HaddockFlags -> Flag String
haddockDistPref,
preReg :: [String] -> RegisterFlags -> IO HookedBuildInfo
preReg = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags -> Flag String
regDistPref,
preUnreg :: [String] -> RegisterFlags -> IO HookedBuildInfo
preUnreg = forall a.
(a -> Flag Verbosity)
-> (a -> Flag String) -> [String] -> a -> IO HookedBuildInfo
readHook RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags -> Flag String
regDistPref
}
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 = forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
flags)
baseDir :: LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi' = forall a. a -> Maybe a -> a
fromMaybe String
""
(String -> String
takeDirectory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi')
Bool
confExists <- String -> IO Bool
doesFileExist forall a b. (a -> b) -> a -> b
$ (LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi) String -> String -> String
</> String
"configure"
if Bool
confExists
then Verbosity -> Bool -> ConfigFlags -> LocalBuildInfo -> IO ()
runConfigureScript Verbosity
verbosity
Bool
backwardsCompatHack ConfigFlags
flags LocalBuildInfo
lbi
else forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity String
"configure script not found."
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 :: PackageDescription
localPkgDescr = PackageDescription
pkg_descr' }
UserHooks
-> [String]
-> ConfigFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
postConf UserHooks
simpleUserHooks [String]
args ConfigFlags
flags PackageDescription
pkg_descr' LocalBuildInfo
lbi'
backwardsCompatHack :: Bool
backwardsCompatHack = Bool
False
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 = 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 = forall a. WithCallStack (Flag a -> a)
fromFlag (a -> Flag Verbosity
get_verbosity a
flags)
runConfigureScript :: Verbosity -> Bool -> ConfigFlags -> LocalBuildInfo
-> IO ()
runConfigureScript :: Verbosity -> Bool -> ConfigFlags -> LocalBuildInfo -> IO ()
runConfigureScript Verbosity
verbosity Bool
backwardsCompatHack ConfigFlags
flags LocalBuildInfo
lbi = do
[(String, String)]
env <- IO [(String, String)]
getEnvironment
let programDb :: ProgramDb
programDb = LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi
(String
ccProg, [String]
ccFlags) <- Verbosity -> ProgramDb -> IO (String, [String])
configureCCompiler Verbosity
verbosity ProgramDb
programDb
String
ccProgShort <- String -> IO String
getShortPathName String
ccProg
String
configureFile <- String -> IO String
makeAbsolute forall a b. (a -> b) -> a -> b
$
forall a. a -> Maybe a -> a
fromMaybe String
"." (String -> String
takeDirectory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi) String -> String -> String
</> String
"configure"
let configureFile' :: String
configureFile' = String -> String
toUnix String
configureFile
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [(Char, String)]
badAutoconfCharacters forall a b. (a -> b) -> a -> b
$ \(Char
c, String
cname) ->
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Char
c forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String -> String
dropDrive String
configureFile') forall a b. (a -> b) -> a -> b
$
Verbosity -> String -> IO ()
warn Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"The path to the './configure' script, '", String
configureFile'
, String
"', contains the character '", [Char
c], String
"' (", String
cname, String
")."
, String
" This may cause the script to fail with an obscure error, or for"
, String
" building the package to fail later."
]
let extraPath :: [String]
extraPath = forall a. NubList a -> [a]
fromNubList forall a b. (a -> b) -> a -> b
$ ConfigFlags -> NubList String
configProgramPathExtra ConfigFlags
flags
let cflagsEnv :: String
cflagsEnv = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([String] -> String
unwords [String]
ccFlags) (forall a. [a] -> [a] -> [a]
++ (String
" " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
ccFlags))
forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"CFLAGS" [(String, String)]
env
spSep :: String
spSep = [Char
searchPathSeparator]
pathEnv :: String
pathEnv = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. [a] -> [[a]] -> [a]
intercalate String
spSep [String]
extraPath)
((forall a. [a] -> [[a]] -> [a]
intercalate String
spSep [String]
extraPath forall a. [a] -> [a] -> [a]
++ String
spSep)forall a. [a] -> [a] -> [a]
++) forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"PATH" [(String, String)]
env
overEnv :: [(String, Maybe String)]
overEnv = (String
"CFLAGS", forall a. a -> Maybe a
Just String
cflagsEnv) forall a. a -> [a] -> [a]
:
[(String
"PATH", forall a. a -> Maybe a
Just String
pathEnv) | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
extraPath)]
hp :: Platform
hp = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
maybeHostFlag :: [String]
maybeHostFlag = if Platform
hp forall a. Eq a => a -> a -> Bool
== Platform
buildPlatform then [] else [String
"--host=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. Pretty a => a -> Doc
pretty Platform
hp)]
args' :: [String]
args' = String
configureFile'forall a. a -> [a] -> [a]
:[String]
args forall a. [a] -> [a] -> [a]
++ [String
"CC=" forall a. [a] -> [a] -> [a]
++ String
ccProgShort] forall a. [a] -> [a] -> [a]
++ [String]
maybeHostFlag
shProg :: Program
shProg = String -> Program
simpleProgram String
"sh"
progDb :: ProgramDb
progDb = (ProgramSearchPath -> ProgramSearchPath) -> ProgramDb -> ProgramDb
modifyProgramSearchPath
(\ProgramSearchPath
p -> forall a b. (a -> b) -> [a] -> [b]
map String -> ProgramSearchPathEntry
ProgramSearchPathDir [String]
extraPath forall a. [a] -> [a] -> [a]
++ ProgramSearchPath
p) ProgramDb
emptyProgramDb
Maybe ConfiguredProgram
shConfiguredProg <- Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
shProg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Verbosity -> Program -> ProgramDb -> IO ProgramDb
configureProgram Verbosity
verbosity Program
shProg ProgramDb
progDb
case Maybe ConfiguredProgram
shConfiguredProg of
Just ConfiguredProgram
sh -> Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation Verbosity
verbosity forall a b. (a -> b) -> a -> b
$
(ConfiguredProgram -> [String] -> ProgramInvocation
programInvocation (ConfiguredProgram
sh {programOverrideEnv :: [(String, Maybe String)]
programOverrideEnv = [(String, Maybe String)]
overEnv}) [String]
args')
{ progInvokeCwd :: Maybe String
progInvokeCwd = forall a. a -> Maybe a
Just (LocalBuildInfo -> String
buildDir LocalBuildInfo
lbi) }
Maybe ConfiguredProgram
Nothing -> forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity String
notFoundMsg
where
args :: [String]
args = Bool -> ConfigFlags -> [String]
configureArgs Bool
backwardsCompatHack ConfigFlags
flags
notFoundMsg :: String
notFoundMsg = String
"The package has a './configure' script. "
forall a. [a] -> [a] -> [a]
++ String
"If you are on Windows, This requires a "
forall a. [a] -> [a] -> [a]
++ String
"Unix compatibility toolchain such as MinGW+MSYS or Cygwin. "
forall a. [a] -> [a] -> [a]
++ String
"If you are not on Windows, ensure that an 'sh' command "
forall a. [a] -> [a] -> [a]
++ String
"is discoverable in your path."
toUnix :: String -> String
#ifdef mingw32_HOST_OS
toUnix s = let tmp = normalise s
(l, rest) = case splitDrive tmp of
([], x) -> ("/" , x)
(h:_, x) -> ('/':h:"/", x)
parts = splitDirectories rest
in l ++ intercalate "/" parts
#else
toUnix :: String -> String
toUnix String
s = forall a. [a] -> [[a]] -> [a]
intercalate String
"/" forall a b. (a -> b) -> a -> b
$ String -> [String]
splitDirectories String
s
#endif
badAutoconfCharacters :: [(Char, String)]
badAutoconfCharacters :: [(Char, String)]
badAutoconfCharacters =
[ (Char
' ', String
"space")
, (Char
'\t', String
"tab")
, (Char
'\n', String
"newline")
, (Char
'\0', String
"null")
, (Char
'"', String
"double quote")
, (Char
'#', String
"hash")
, (Char
'$', String
"dollar sign")
, (Char
'&', String
"ampersand")
, (Char
'\'', String
"single quote")
, (Char
'(', String
"left bracket")
, (Char
')', String
"right bracket")
, (Char
'*', String
"star")
, (Char
';', String
"semicolon")
, (Char
'<', String
"less-than sign")
, (Char
'=', String
"equals sign")
, (Char
'>', String
"greater-than sign")
, (Char
'?', String
"question mark")
, (Char
'[', String
"left square bracket")
, (Char
'\\', String
"backslash")
, (Char
'`', String
"backtick")
, (Char
'|', String
"pipe")
]
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 -> forall (m :: * -> *) a. Monad m => a -> m a
return HookedBuildInfo
emptyHookedBuildInfo
Just String
infoFile -> do
Verbosity -> String -> IO ()
info Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ String
"Reading parameters from " 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 :: Flag String
copyDistPref = InstallFlags -> Flag String
installDistPref InstallFlags
flags,
copyDest :: Flag CopyDest
copyDest = InstallFlags -> Flag CopyDest
installDest InstallFlags
flags,
copyVerbosity :: Flag Verbosity
copyVerbosity = InstallFlags -> Flag Verbosity
installVerbosity InstallFlags
flags
}
PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install PackageDescription
pkg_descr LocalBuildInfo
localbuildinfo CopyFlags
copyFlags
let registerFlags :: RegisterFlags
registerFlags = RegisterFlags
defaultRegisterFlags {
regDistPref :: Flag String
regDistPref = InstallFlags -> Flag String
installDistPref InstallFlags
flags,
regInPlace :: Flag Bool
regInPlace = InstallFlags -> Flag Bool
installInPlace InstallFlags
flags,
regPackageDB :: Flag PackageDB
regPackageDB = InstallFlags -> Flag PackageDB
installPackageDB InstallFlags
flags,
regVerbosity :: Flag Verbosity
regVerbosity = InstallFlags -> Flag Verbosity
installVerbosity InstallFlags
flags
}
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PackageDescription -> Bool
hasLibs PackageDescription
pkg_descr) 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 (forall a. WithCallStack (Flag a -> a)
fromFlag (RegisterFlags -> Flag Verbosity
regVerbosity RegisterFlags
flags))
String
"Package contains no library to register:" (forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg_descr)