{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# 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 Distribution.Compat.Prelude
import Prelude ()
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
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, (\\))
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
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 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
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
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)}
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)}
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
args' <- [String] -> IO [String]
expandResponse [String]
args
command <- commandsRun (globalCommand commands) commands args'
case 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
]
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
distPref <- Flag String -> IO String
findDistPrefOrDefault (ConfigFlags -> Flag String
configDistPref ConfigFlags
flags)
let flags' =
ConfigFlags
flags
{ configDistPref = toFlag distPref
, configArgs = args
}
pbi <- preConf hooks args flags'
(mb_pd_file, pkg_descr0) <-
confPkgDescr
hooks
verbosity
(flagToMaybe (configCabalFilePath flags))
let epkg_descr = (GenericPackageDescription
pkg_descr0, HookedBuildInfo
pbi)
localbuildinfo0 <- confHook hooks epkg_descr flags'
let localbuildinfo =
LocalBuildInfo
localbuildinfo0
{ pkgDescrFile = mb_pd_file
, extraConfigArgs = args
}
writePersistBuildConfig distPref localbuildinfo
let pkg_descr = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
localbuildinfo
postConf hooks args flags' pkg_descr localbuildinfo
return 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
mdescr <- UserHooks -> IO (Maybe GenericPackageDescription)
readDesc UserHooks
hooks
case 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
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
info verbosity "Using Parsec parser"
descr <- readGenericPackageDescription verbosity pdfile
return (Just pdfile, descr)
buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
buildAction :: UserHooks -> BuildFlags -> [String] -> IO ()
buildAction UserHooks
hooks BuildFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (BuildFlags -> Flag String
buildDistPref BuildFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
BuildFlags
flags
{ buildDistPref = toFlag distPref
, buildCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
progs <-
reconfigurePrograms
verbosity
(buildProgramPaths flags')
(buildProgramArgs flags')
(withPrograms lbi)
hookedAction
verbosity
preBuild
buildHook
postBuild
(return lbi{withPrograms = progs})
hooks
flags'{buildArgs = args}
args
replAction :: UserHooks -> ReplFlags -> Args -> IO ()
replAction :: UserHooks -> ReplFlags -> [String] -> IO ()
replAction UserHooks
hooks ReplFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (ReplFlags -> Flag String
replDistPref ReplFlags
flags)
let 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{replDistPref = toFlag distPref}
lbi <- getBuildConfig hooks verbosity distPref
progs <-
reconfigurePrograms
verbosity
(replProgramPaths flags')
(replProgramArgs flags')
(withPrograms lbi)
pbi <- preRepl hooks args flags'
let pkg_descr0 = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi
sanityCheckHookedBuildInfo verbosity pkg_descr0 pbi
let pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
lbi' =
LocalBuildInfo
lbi
{ withPrograms = progs
, localPkgDescr = pkg_descr
}
replHook hooks pkg_descr lbi' hooks flags' args
postRepl hooks args flags' pkg_descr lbi'
hscolourAction :: UserHooks -> HscolourFlags -> Args -> IO ()
hscolourAction :: UserHooks -> HscolourFlags -> [String] -> IO ()
hscolourAction UserHooks
hooks HscolourFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (HscolourFlags -> Flag String
hscolourDistPref HscolourFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
HscolourFlags
flags
{ hscolourDistPref = toFlag distPref
, hscolourCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
hookedAction
verbosity
preHscolour
hscolourHook
postHscolour
(getBuildConfig hooks verbosity distPref)
hooks
flags'
args
haddockAction :: UserHooks -> HaddockFlags -> Args -> IO ()
haddockAction :: UserHooks -> HaddockFlags -> [String] -> IO ()
haddockAction UserHooks
hooks HaddockFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (HaddockFlags -> Flag String
haddockDistPref HaddockFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
HaddockFlags
flags
{ haddockDistPref = toFlag distPref
, haddockCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
progs <-
reconfigurePrograms
verbosity
(haddockProgramPaths flags')
(haddockProgramArgs flags')
(withPrograms lbi)
hookedAction
verbosity
preHaddock
haddockHook
postHaddock
(return lbi{withPrograms = progs})
hooks
flags'{haddockArgs = args}
args
cleanAction :: UserHooks -> CleanFlags -> Args -> IO ()
cleanAction :: UserHooks -> CleanFlags -> [String] -> IO ()
cleanAction UserHooks
hooks CleanFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (CleanFlags -> Flag String
cleanDistPref CleanFlags
flags)
elbi <- tryGetBuildConfig hooks verbosity distPref
let 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)
}
pbi <- preClean hooks args flags'
(_, ppd) <- confPkgDescr hooks verbosity Nothing
let pkg_descr0 = GenericPackageDescription -> PackageDescription
flattenPackageDescription GenericPackageDescription
ppd
let pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
cleanHook hooks pkg_descr () hooks flags'
postClean hooks args flags' 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
distPref <- Flag String -> IO String
findDistPrefOrDefault (CopyFlags -> Flag String
copyDistPref CopyFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
CopyFlags
flags
{ copyDistPref = toFlag distPref
, copyCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
hookedAction
verbosity
preCopy
copyHook
postCopy
(getBuildConfig hooks verbosity distPref)
hooks
flags'{copyArgs = args}
args
installAction :: UserHooks -> InstallFlags -> Args -> IO ()
installAction :: UserHooks -> InstallFlags -> [String] -> IO ()
installAction UserHooks
hooks InstallFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (InstallFlags -> Flag String
installDistPref InstallFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
InstallFlags
flags
{ installDistPref = toFlag distPref
, installCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
hookedAction
verbosity
preInst
instHook
postInst
(getBuildConfig hooks verbosity distPref)
hooks
flags'
args
sdistAction :: UserHooks -> SDistFlags -> Args -> IO ()
sdistAction :: UserHooks -> SDistFlags -> [String] -> IO ()
sdistAction UserHooks
_hooks SDistFlags
flags [String]
_args = do
(_, ppd) <- UserHooks
-> Verbosity
-> Maybe String
-> IO (Maybe String, GenericPackageDescription)
confPkgDescr UserHooks
emptyUserHooks Verbosity
verbosity Maybe String
forall a. Maybe a
Nothing
let pkg_descr = GenericPackageDescription -> PackageDescription
flattenPackageDescription GenericPackageDescription
ppd
sdist pkg_descr flags srcPref 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
distPref <- Flag String -> IO String
findDistPrefOrDefault (TestFlags -> Flag String
testDistPref TestFlags
flags)
let 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{testDistPref = toFlag distPref}
hookedActionWithArgs
verbosity
preTest
testHook
postTest
(getBuildConfig hooks verbosity distPref)
hooks
flags'
args
benchAction :: UserHooks -> BenchmarkFlags -> Args -> IO ()
benchAction :: UserHooks -> BenchmarkFlags -> [String] -> IO ()
benchAction UserHooks
hooks BenchmarkFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (BenchmarkFlags -> Flag String
benchmarkDistPref BenchmarkFlags
flags)
let 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{benchmarkDistPref = toFlag distPref}
hookedActionWithArgs
verbosity
preBench
benchHook
postBench
(getBuildConfig hooks verbosity distPref)
hooks
flags'
args
registerAction :: UserHooks -> RegisterFlags -> Args -> IO ()
registerAction :: UserHooks -> RegisterFlags -> [String] -> IO ()
registerAction UserHooks
hooks RegisterFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (RegisterFlags -> Flag String
regDistPref RegisterFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
RegisterFlags
flags
{ regDistPref = toFlag distPref
, regCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
hookedAction
verbosity
preReg
regHook
postReg
(getBuildConfig hooks verbosity distPref)
hooks
flags'{regArgs = args}
args
unregisterAction :: UserHooks -> RegisterFlags -> Args -> IO ()
unregisterAction :: UserHooks -> RegisterFlags -> [String] -> IO ()
unregisterAction UserHooks
hooks RegisterFlags
flags [String]
args = do
distPref <- Flag String -> IO String
findDistPrefOrDefault (RegisterFlags -> Flag String
regDistPref RegisterFlags
flags)
let 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
lbi <- getBuildConfig hooks verbosity distPref
let flags' =
RegisterFlags
flags
{ regDistPref = toFlag distPref
, regCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
hookedAction
verbosity
preUnreg
unregHook
postUnreg
(getBuildConfig hooks verbosity distPref)
hooks
flags'
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
pbi <- UserHooks -> [String] -> flags -> IO HookedBuildInfo
pre_hook UserHooks
hooks [String]
args flags
flags
lbi0 <- get_build_config
let pkg_descr0 = LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi0
sanityCheckHookedBuildInfo verbosity pkg_descr0 pbi
let pkg_descr = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr0
lbi = LocalBuildInfo
lbi0{localPkgDescr = pkg_descr}
cmd_hook hooks args pkg_descr lbi hooks flags
post_hook hooks args flags pkg_descr 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 ()
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
getBuildConfig :: UserHooks -> Verbosity -> FilePath -> IO LocalBuildInfo
getBuildConfig :: UserHooks -> Verbosity -> String -> IO LocalBuildInfo
getBuildConfig UserHooks
hooks Verbosity
verbosity String
distPref = do
lbi_wo_programs <- String -> IO LocalBuildInfo
getPersistBuildConfig String
distPref
let lbi =
LocalBuildInfo
lbi_wo_programs
{ withPrograms =
restoreProgramDb
(builtinPrograms ++ hookedPrograms hooks)
(withPrograms lbi_wo_programs)
}
case pkgDescrFile 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
outdated <- String -> String -> IO Bool
checkPersistBuildConfigOutdated String
distPref String
pkg_descr_file
if outdated
then reconfigure pkg_descr_file lbi
else return 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
{
configPrograms_ =
fmap
( restoreProgramDb
(builtinPrograms ++ hookedPrograms hooks)
)
`fmap` configPrograms_ cFlags
,
configVerbosity = Flag 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 = 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..."
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
chattyTry "removing dist/" $ do
exists <- doesDirectoryExist distPref
when exists (removeDirectoryRecursive distPref)
traverse_ removeFileOrDirectory (extraTmpFiles pkg_descr)
traverse_ (writePersistBuildConfig distPref) maybeConfig
where
removeFileOrDirectory :: FilePath -> IO ()
removeFileOrDirectory :: String -> IO ()
removeFileOrDirectory String
fname = do
isDir <- String -> IO Bool
doesDirectoryExist String
fname
isFile <- doesFileExist fname
if isDir
then removeDirectoryRecursive fname
else when isFile $ removeFile fname
verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (CleanFlags -> Flag Verbosity
cleanVerbosity CleanFlags
flags)
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
,
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)
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')
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 confExists
then
runConfigureScript
verbosity
flags
lbi
else dieWithException verbosity ConfigureScriptNotFound
pbi <- getHookedBuildInfo verbosity (buildDir lbi)
sanityCheckHookedBuildInfo verbosity pkg_descr pbi
let pkg_descr' = HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription HookedBuildInfo
pbi PackageDescription
pkg_descr
lbi' = LocalBuildInfo
lbi{localPkgDescr = pkg_descr'}
postConf simpleUserHooks args flags pkg_descr' 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
dist_dir <- Flag String -> IO String
findDistPrefOrDefault (a -> Flag String
get_dist_pref a
flags)
getHookedBuildInfo verbosity (dist_dir </> "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
dist_dir <- Flag String -> IO String
findDistPrefOrDefault (a -> Flag String
get_dist_pref a
flags)
getHookedBuildInfo verbosity (dist_dir </> "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_infoFile <- Verbosity -> String -> IO (Maybe String)
findHookedPackageDesc Verbosity
verbosity String
build_dir
case 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)