Merge pull request #10608 from cabalism/doc/makefile-10596
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Config.hs
blob15c1d77f553842696b2ed8c688cc37e713e1a492
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE DeriveDataTypeable #-}
4 {-# LANGUAGE DeriveGeneric #-}
5 {-# LANGUAGE FlexibleContexts #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE RankNTypes #-}
8 {-# LANGUAGE ViewPatterns #-}
10 -----------------------------------------------------------------------------
12 -- |
13 -- Module : Distribution.Simple.Setup.Config
14 -- Copyright : Isaac Jones 2003-2004
15 -- Duncan Coutts 2007
16 -- License : BSD3
18 -- Maintainer : cabal-devel@haskell.org
19 -- Portability : portable
21 -- Definition of the configure command-line options.
22 -- See: @Distribution.Simple.Setup@
23 module Distribution.Simple.Setup.Config
24 ( ConfigFlags
25 ( ConfigCommonFlags
26 , configVerbosity
27 , configDistPref
28 , configCabalFilePath
29 , configWorkingDir
30 , configTargets
31 , ..
33 , emptyConfigFlags
34 , defaultConfigFlags
35 , configureCommand
36 , configPrograms
37 , readPackageDb
38 , readPackageDbList
39 , showPackageDb
40 , showPackageDbList
41 , configureArgs
42 , configureOptions
43 , installDirsOptions
44 ) where
46 import Distribution.Compat.Prelude hiding (get)
47 import Prelude ()
49 import qualified Distribution.Compat.CharParsing as P
50 import Distribution.Compat.Semigroup (Last' (..), Option' (..))
51 import Distribution.Compat.Stack
52 import Distribution.Compiler
53 import Distribution.ModuleName
54 import Distribution.PackageDescription
55 import Distribution.Parsec
56 import Distribution.Pretty
57 import Distribution.ReadE
58 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
59 import Distribution.Simple.Compiler
60 import Distribution.Simple.Flag
61 import Distribution.Simple.InstallDirs
62 import Distribution.Simple.Program
63 import Distribution.Simple.Setup.Common
64 import Distribution.Simple.Utils
65 import Distribution.Types.ComponentId
66 import Distribution.Types.DumpBuildInfo
67 import Distribution.Types.GivenComponent
68 import Distribution.Types.Module
69 import Distribution.Types.PackageVersionConstraint
70 import Distribution.Types.UnitId
71 import Distribution.Utils.NubList
72 import Distribution.Utils.Path
73 import Distribution.Verbosity
75 import qualified Text.PrettyPrint as Disp
77 -- ------------------------------------------------------------
79 -- * Config flags
81 -- ------------------------------------------------------------
83 -- | Flags to @configure@ command.
85 -- IMPORTANT: every time a new flag is added, 'D.C.Setup.filterConfigureFlags'
86 -- should be updated.
87 -- IMPORTANT: every time a new flag is added, it should be added to the Eq instance
88 data ConfigFlags = ConfigFlags
89 { configCommonFlags :: !CommonSetupFlags
90 , -- FIXME: the configPrograms is only here to pass info through to configure
91 -- because the type of configure is constrained by the UserHooks.
92 -- when we change UserHooks next we should pass the initial
93 -- ProgramDb directly and not via ConfigFlags
94 configPrograms_ :: Option' (Last' ProgramDb)
95 -- ^ All programs that
96 -- @cabal@ may run
97 , configProgramPaths :: [(String, FilePath)]
98 -- ^ user specified programs paths
99 , configProgramArgs :: [(String, [String])]
100 -- ^ user specified programs args
101 , configProgramPathExtra :: NubList FilePath
102 -- ^ Extend the $PATH
103 , configHcFlavor :: Flag CompilerFlavor
104 -- ^ The \"flavor\" of the
105 -- compiler, e.g. GHC.
106 , configHcPath :: Flag FilePath
107 -- ^ given compiler location
108 , configHcPkg :: Flag FilePath
109 -- ^ given hc-pkg location
110 , configVanillaLib :: Flag Bool
111 -- ^ Enable vanilla library
112 , configProfLib :: Flag Bool
113 -- ^ Enable profiling in the library
114 , configSharedLib :: Flag Bool
115 -- ^ Build shared library
116 , configStaticLib :: Flag Bool
117 -- ^ Build static library
118 , configDynExe :: Flag Bool
119 -- ^ Enable dynamic linking of the
120 -- executables.
121 , configFullyStaticExe :: Flag Bool
122 -- ^ Enable fully static linking of the
123 -- executables.
124 , configProfExe :: Flag Bool
125 -- ^ Enable profiling in the
126 -- executables.
127 , configProf :: Flag Bool
128 -- ^ Enable profiling in the library
129 -- and executables.
130 , configProfShared :: Flag Bool
131 -- ^ Enable shared profiling objects
132 , configProfDetail :: Flag ProfDetailLevel
133 -- ^ Profiling detail level
134 -- in the library and executables.
135 , configProfLibDetail :: Flag ProfDetailLevel
136 -- ^ Profiling detail level
137 -- in the library
138 , configConfigureArgs :: [String]
139 -- ^ Extra arguments to @configure@
140 , configOptimization :: Flag OptimisationLevel
141 -- ^ Enable optimization.
142 , configProgPrefix :: Flag PathTemplate
143 -- ^ Installed executable prefix.
144 , configProgSuffix :: Flag PathTemplate
145 -- ^ Installed executable suffix.
146 , configInstallDirs :: InstallDirs (Flag PathTemplate)
147 -- ^ Installation
148 -- paths
149 , configScratchDir :: Flag FilePath
150 , configExtraLibDirs :: [SymbolicPath Pkg (Dir Lib)]
151 -- ^ path to search for extra libraries
152 , configExtraLibDirsStatic :: [SymbolicPath Pkg (Dir Lib)]
153 -- ^ path to search for extra
154 -- libraries when linking
155 -- fully static executables
156 , configExtraFrameworkDirs :: [SymbolicPath Pkg (Dir Framework)]
157 -- ^ path to search for extra
158 -- frameworks (OS X only)
159 , configExtraIncludeDirs :: [SymbolicPath Pkg (Dir Include)]
160 -- ^ path to search for header files
161 , configIPID :: Flag String
162 -- ^ explicit IPID to be used
163 , configCID :: Flag ComponentId
164 -- ^ explicit CID to be used
165 , configDeterministic :: Flag Bool
166 -- ^ be as deterministic as possible
167 -- (e.g., invariant over GHC, database,
168 -- etc). Used by the test suite
169 , configUserInstall :: Flag Bool
170 -- ^ The --user\/--global flag
171 , configPackageDBs :: [Maybe PackageDB]
172 -- ^ Which package DBs to use
173 , configGHCiLib :: Flag Bool
174 -- ^ Enable compiling library for GHCi
175 , configSplitSections :: Flag Bool
176 -- ^ Enable -split-sections with GHC
177 , configSplitObjs :: Flag Bool
178 -- ^ Enable -split-objs with GHC
179 , configStripExes :: Flag Bool
180 -- ^ Enable executable stripping
181 , configStripLibs :: Flag Bool
182 -- ^ Enable library stripping
183 , configConstraints :: [PackageVersionConstraint]
184 -- ^ Additional constraints for
185 -- dependencies.
186 , configDependencies :: [GivenComponent]
187 -- ^ The packages depended on which already exist
188 , configPromisedDependencies :: [PromisedComponent]
189 -- ^ The packages depended on which doesn't yet exist (i.e. promised).
190 -- Promising dependencies enables us to configure components in parallel,
191 -- and avoids expensive builds if they are not necessary.
192 -- For example, in multi-repl mode, we don't want to build dependencies that
193 -- are loaded into the interactive session, since we have to build them again.
194 , configInstantiateWith :: [(ModuleName, Module)]
195 -- ^ The requested Backpack instantiation. If empty, either this
196 -- package does not use Backpack, or we just want to typecheck
197 -- the indefinite package.
198 , configConfigurationsFlags :: FlagAssignment
199 , configTests :: Flag Bool
200 -- ^ Enable test suite compilation
201 , configBenchmarks :: Flag Bool
202 -- ^ Enable benchmark compilation
203 , configCoverage :: Flag Bool
204 -- ^ Enable program coverage
205 , configLibCoverage :: Flag Bool
206 -- ^ Enable program coverage (deprecated)
207 , configExactConfiguration :: Flag Bool
208 -- ^ All direct dependencies and flags are provided on the command line by
209 -- the user via the '--dependency' and '--flags' options.
210 , configFlagError :: Flag String
211 -- ^ Halt and show an error message indicating an error in flag assignment
212 , configRelocatable :: Flag Bool
213 -- ^ Enable relocatable package built
214 , configDebugInfo :: Flag DebugInfoLevel
215 -- ^ Emit debug info.
216 , configDumpBuildInfo :: Flag DumpBuildInfo
217 -- ^ Should we dump available build information on build?
218 -- Dump build information to disk before attempting to build,
219 -- tooling can parse these files and use them to compile the
220 -- source files themselves.
221 , configUseResponseFiles :: Flag Bool
222 -- ^ Whether to use response files at all. They're used for such tools
223 -- as haddock, or ld.
224 , configAllowDependingOnPrivateLibs :: Flag Bool
225 -- ^ Allow depending on private sublibraries. This is used by external
226 -- tools (like cabal-install) so they can add multiple-public-libraries
227 -- compatibility to older ghcs by checking visibility externally.
228 , configCoverageFor :: Flag [UnitId]
229 -- ^ The list of libraries to be included in the hpc coverage report for
230 -- testsuites run with @--enable-coverage@. Notably, this list must exclude
231 -- indefinite libraries and instantiations because HPC does not support
232 -- backpack (Nov. 2023).
233 , configIgnoreBuildTools :: Flag Bool
234 -- ^ When this flag is set, all tools declared in `build-tool`s and
235 -- `build-tool-depends` will be ignored. This allows a Cabal package with
236 -- build-tool-dependencies to be built even if the tool is not found.
238 deriving (Generic, Read, Show, Typeable)
240 pattern ConfigCommonFlags
241 :: Flag Verbosity
242 -> Flag (SymbolicPath Pkg (Dir Dist))
243 -> Flag (SymbolicPath CWD (Dir Pkg))
244 -> Flag (SymbolicPath Pkg File)
245 -> [String]
246 -> ConfigFlags
247 pattern ConfigCommonFlags
248 { configVerbosity
249 , configDistPref
250 , configWorkingDir
251 , configCabalFilePath
252 , configTargets
253 } <-
254 ( configCommonFlags ->
255 CommonSetupFlags
256 { setupVerbosity = configVerbosity
257 , setupDistPref = configDistPref
258 , setupWorkingDir = configWorkingDir
259 , setupCabalFilePath = configCabalFilePath
260 , setupTargets = configTargets
264 instance Binary ConfigFlags
265 instance Structured ConfigFlags
267 -- | More convenient version of 'configPrograms'. Results in an
268 -- 'error' if internal invariant is violated.
269 configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
270 configPrograms =
271 fromMaybe (error "FIXME: remove configPrograms")
272 . fmap getLast'
273 . getOption'
274 . configPrograms_
276 instance Eq ConfigFlags where
277 (==) a b =
278 -- configPrograms skipped: not user specified, has no Eq instance
279 equal configCommonFlags
280 && equal configProgramPaths
281 && equal configProgramArgs
282 && equal configProgramPathExtra
283 && equal configHcFlavor
284 && equal configHcPath
285 && equal configHcPkg
286 && equal configVanillaLib
287 && equal configProfLib
288 && equal configSharedLib
289 && equal configStaticLib
290 && equal configDynExe
291 && equal configFullyStaticExe
292 && equal configProfExe
293 && equal configProf
294 && equal configProfDetail
295 && equal configProfShared
296 && equal configProfLibDetail
297 && equal configConfigureArgs
298 && equal configOptimization
299 && equal configProgPrefix
300 && equal configProgSuffix
301 && equal configInstallDirs
302 && equal configScratchDir
303 && equal configExtraLibDirs
304 && equal configExtraLibDirsStatic
305 && equal configExtraIncludeDirs
306 && equal configIPID
307 && equal configDeterministic
308 && equal configUserInstall
309 && equal configPackageDBs
310 && equal configGHCiLib
311 && equal configSplitSections
312 && equal configSplitObjs
313 && equal configStripExes
314 && equal configStripLibs
315 && equal configConstraints
316 && equal configDependencies
317 && equal configPromisedDependencies
318 && equal configConfigurationsFlags
319 && equal configTests
320 && equal configBenchmarks
321 && equal configCoverage
322 && equal configLibCoverage
323 && equal configExactConfiguration
324 && equal configFlagError
325 && equal configRelocatable
326 && equal configDebugInfo
327 && equal configDumpBuildInfo
328 && equal configUseResponseFiles
329 && equal configAllowDependingOnPrivateLibs
330 && equal configCoverageFor
331 && equal configIgnoreBuildTools
332 where
333 equal f = on (==) f a b
335 {- FOURMOLU_DISABLE -}
336 defaultConfigFlags :: ProgramDb -> ConfigFlags
337 defaultConfigFlags progDb =
338 emptyConfigFlags
339 { configCommonFlags = defaultCommonSetupFlags
340 , configPrograms_ = Option' (Just (Last' progDb))
341 , configHcFlavor = maybe NoFlag Flag defaultCompilerFlavor
342 , configVanillaLib = Flag True
343 , configProfLib = NoFlag
344 , configSharedLib = NoFlag
345 , configStaticLib = NoFlag
346 , configDynExe = Flag False
347 , configFullyStaticExe = Flag False
348 , configProfExe = NoFlag
349 , configProf = NoFlag
350 , configProfDetail = NoFlag
351 , configProfLibDetail = NoFlag
352 , configOptimization = Flag NormalOptimisation
353 , configProgPrefix = Flag (toPathTemplate "")
354 , configProgSuffix = Flag (toPathTemplate "")
355 , configUserInstall = Flag False -- TODO: reverse this
356 #if defined(mingw32_HOST_OS)
357 -- See #8062 and GHC #21019.
358 , configGHCiLib = Flag False
359 #else
360 , configGHCiLib = NoFlag
361 #endif
362 , configSplitSections = Flag False
363 , configSplitObjs = Flag False -- takes longer, so turn off by default
364 , configStripExes = NoFlag
365 , configStripLibs = NoFlag
366 , configTests = Flag False
367 , configBenchmarks = Flag False
368 , configCoverage = Flag False
369 , configLibCoverage = NoFlag
370 , configExactConfiguration = Flag False
371 , configFlagError = NoFlag
372 , configRelocatable = Flag False
373 , configDebugInfo = Flag NoDebugInfo
374 , configDumpBuildInfo = NoFlag
375 , configUseResponseFiles = NoFlag
377 {- FOURMOLU_ENABLE -}
379 configureCommand :: ProgramDb -> CommandUI ConfigFlags
380 configureCommand progDb =
381 CommandUI
382 { commandName = "configure"
383 , commandSynopsis = "Prepare to build the package."
384 , commandDescription = Just $ \_ ->
385 wrapText $
386 "Configure how the package is built by setting "
387 ++ "package (and other) flags.\n"
388 ++ "\n"
389 ++ "The configuration affects several other commands, "
390 ++ "including build, test, bench, run, repl.\n"
391 , commandNotes = Just $ \_pname -> programFlagsDescription progDb
392 , commandUsage = \pname ->
393 "Usage: " ++ pname ++ " configure [FLAGS]\n"
394 , commandDefaultFlags = defaultConfigFlags progDb
395 , commandOptions = \showOrParseArgs ->
396 configureOptions showOrParseArgs
397 ++ programDbPaths
398 progDb
399 showOrParseArgs
400 configProgramPaths
401 (\v fs -> fs{configProgramPaths = v})
402 ++ programDbOption
403 progDb
404 showOrParseArgs
405 configProgramArgs
406 (\v fs -> fs{configProgramArgs = v})
407 ++ programDbOptions
408 progDb
409 showOrParseArgs
410 configProgramArgs
411 (\v fs -> fs{configProgramArgs = v})
414 -- | Inverse to 'dispModSubstEntry'.
415 parsecModSubstEntry :: ParsecParser (ModuleName, Module)
416 parsecModSubstEntry = do
417 k <- parsec
418 _ <- P.char '='
419 v <- parsec
420 return (k, v)
422 -- | Pretty-print a single entry of a module substitution.
423 dispModSubstEntry :: (ModuleName, Module) -> Disp.Doc
424 dispModSubstEntry (k, v) = pretty k <<>> Disp.char '=' <<>> pretty v
426 configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
427 configureOptions showOrParseArgs =
428 withCommonSetupOptions
429 configCommonFlags
430 (\c f -> f{configCommonFlags = c})
431 showOrParseArgs
432 [ option
434 ["compiler"]
435 "compiler"
436 configHcFlavor
437 (\v flags -> flags{configHcFlavor = v})
438 ( choiceOpt
439 [ (Flag GHC, ("g", ["ghc"]), "compile with GHC")
440 , (Flag GHCJS, ([], ["ghcjs"]), "compile with GHCJS")
441 , (Flag UHC, ([], ["uhc"]), "compile with UHC")
442 , -- "haskell-suite" compiler id string will be replaced
443 -- by a more specific one during the configure stage
445 ( Flag (HaskellSuite "haskell-suite")
446 , ([], ["haskell-suite"])
447 , "compile with a haskell-suite compiler"
451 , option
453 ["with-compiler"]
454 "give the path to a particular compiler"
455 configHcPath
456 (\v flags -> flags{configHcPath = v})
457 (reqArgFlag "PATH")
458 , option
460 ["with-hc-pkg"]
461 "give the path to the package tool"
462 configHcPkg
463 (\v flags -> flags{configHcPkg = v})
464 (reqArgFlag "PATH")
466 ++ map liftInstallDirs installDirsOptions
467 ++ [ option
469 ["program-prefix"]
470 "prefix to be applied to installed executables"
471 configProgPrefix
472 (\v flags -> flags{configProgPrefix = v})
473 (reqPathTemplateArgFlag "PREFIX")
474 , option
476 ["program-suffix"]
477 "suffix to be applied to installed executables"
478 configProgSuffix
479 (\v flags -> flags{configProgSuffix = v})
480 (reqPathTemplateArgFlag "SUFFIX")
481 , option
483 ["library-vanilla"]
484 "Vanilla libraries"
485 configVanillaLib
486 (\v flags -> flags{configVanillaLib = v})
487 (boolOpt [] [])
488 , option
490 ["library-profiling"]
491 "Library profiling"
492 configProfLib
493 (\v flags -> flags{configProfLib = v})
494 (boolOpt "p" [])
495 , option
497 ["shared"]
498 "Shared library"
499 configSharedLib
500 (\v flags -> flags{configSharedLib = v})
501 (boolOpt [] [])
502 , option
504 ["static"]
505 "Static library"
506 configStaticLib
507 (\v flags -> flags{configStaticLib = v})
508 (boolOpt [] [])
509 , option
511 ["executable-dynamic"]
512 "Executable dynamic linking"
513 configDynExe
514 (\v flags -> flags{configDynExe = v})
515 (boolOpt [] [])
516 , option
518 ["executable-static"]
519 "Executable fully static linking"
520 configFullyStaticExe
521 (\v flags -> flags{configFullyStaticExe = v})
522 (boolOpt [] [])
523 , option
525 ["profiling"]
526 "Executable and library profiling"
527 configProf
528 (\v flags -> flags{configProf = v})
529 (boolOpt [] [])
530 , option
532 ["profiling-shared"]
533 "Build profiling shared libraries"
534 configProfShared
535 (\v flags -> flags{configProfShared = v})
536 (boolOpt [] [])
537 , option
539 ["executable-profiling"]
540 "Executable profiling (DEPRECATED)"
541 configProfExe
542 (\v flags -> flags{configProfExe = v})
543 (boolOpt [] [])
544 , option
546 ["profiling-detail"]
547 ( "Profiling detail level for executable and library (default, "
548 ++ "none, exported-functions, toplevel-functions, all-functions, late)."
550 configProfDetail
551 (\v flags -> flags{configProfDetail = v})
552 ( reqArg'
553 "level"
554 (Flag . flagToProfDetailLevel)
555 showProfDetailLevelFlag
557 , option
559 ["library-profiling-detail"]
560 "Profiling detail level for libraries only."
561 configProfLibDetail
562 (\v flags -> flags{configProfLibDetail = v})
563 ( reqArg'
564 "level"
565 (Flag . flagToProfDetailLevel)
566 showProfDetailLevelFlag
568 , multiOption
569 "optimization"
570 configOptimization
571 (\v flags -> flags{configOptimization = v})
572 [ optArgDef'
574 (show NoOptimisation, Flag . flagToOptimisationLevel)
575 ( \f -> case f of
576 Flag NoOptimisation -> []
577 Flag NormalOptimisation -> [Nothing]
578 Flag MaximumOptimisation -> [Just "2"]
579 _ -> []
582 ["enable-optimization", "enable-optimisation"]
583 "Build with optimization (n is 0--2, default is 1)"
584 , noArg
585 (Flag NoOptimisation)
587 ["disable-optimization", "disable-optimisation"]
588 "Build without optimization"
590 , multiOption
591 "debug-info"
592 configDebugInfo
593 (\v flags -> flags{configDebugInfo = v})
594 [ optArg'
596 (Flag . flagToDebugInfoLevel)
597 ( \f -> case f of
598 Flag NoDebugInfo -> []
599 Flag MinimalDebugInfo -> [Just "1"]
600 Flag NormalDebugInfo -> [Nothing]
601 Flag MaximalDebugInfo -> [Just "3"]
602 _ -> []
605 ["enable-debug-info"]
606 "Emit debug info (n is 0--3, default is 0)"
607 , noArg
608 (Flag NoDebugInfo)
610 ["disable-debug-info"]
611 "Don't emit debug info"
613 , multiOption
614 "build-info"
615 configDumpBuildInfo
616 (\v flags -> flags{configDumpBuildInfo = v})
617 [ noArg
618 (Flag DumpBuildInfo)
620 ["enable-build-info"]
621 "Enable build information generation during project building"
622 , noArg
623 (Flag NoDumpBuildInfo)
625 ["disable-build-info"]
626 "Disable build information generation during project building"
628 , option
630 ["library-for-ghci"]
631 "compile library for use with GHCi"
632 configGHCiLib
633 (\v flags -> flags{configGHCiLib = v})
634 (boolOpt [] [])
635 , option
637 ["split-sections"]
638 "compile library code such that unneeded definitions can be dropped from the final executable (GHC 7.8+)"
639 configSplitSections
640 (\v flags -> flags{configSplitSections = v})
641 (boolOpt [] [])
642 , option
644 ["split-objs"]
645 "split library into smaller objects to reduce binary sizes (GHC 6.6+)"
646 configSplitObjs
647 (\v flags -> flags{configSplitObjs = v})
648 (boolOpt [] [])
649 , option
651 ["executable-stripping"]
652 "strip executables upon installation to reduce binary sizes"
653 configStripExes
654 (\v flags -> flags{configStripExes = v})
655 (boolOpt [] [])
656 , option
658 ["library-stripping"]
659 "strip libraries upon installation to reduce binary sizes"
660 configStripLibs
661 (\v flags -> flags{configStripLibs = v})
662 (boolOpt [] [])
663 , option
665 ["configure-option"]
666 "Extra option for configure"
667 configConfigureArgs
668 (\v flags -> flags{configConfigureArgs = v})
669 (reqArg' "OPT" (\x -> [x]) id)
670 , option
672 ["user-install"]
673 "doing a per-user installation"
674 configUserInstall
675 (\v flags -> flags{configUserInstall = v})
676 (boolOpt' ([], ["user"]) ([], ["global"]))
677 , option
679 ["package-db"]
680 ( "Append the given package database to the list of package"
681 ++ " databases used (to satisfy dependencies and register into)."
682 ++ " May be a specific file, 'global' or 'user'. The initial list"
683 ++ " is ['global'], ['global', 'user'], or ['global', $sandbox],"
684 ++ " depending on context. Use 'clear' to reset the list to empty."
685 ++ " See the user guide for details."
687 configPackageDBs
688 (\v flags -> flags{configPackageDBs = v})
689 (reqArg' "DB" readPackageDbList showPackageDbList)
690 , option
692 ["flags"]
693 "Force values for the given flags in Cabal conditionals in the .cabal file. E.g., --flags=\"debug -usebytestrings\" forces the flag \"debug\" to true and \"usebytestrings\" to false."
694 configConfigurationsFlags
695 (\v flags -> flags{configConfigurationsFlags = v})
696 ( reqArg
697 "FLAGS"
698 (parsecToReadE (\err -> "Invalid flag assignment: " ++ err) legacyParsecFlagAssignment)
699 legacyShowFlagAssignment'
701 , option
703 ["extra-include-dirs"]
704 "A list of directories to search for header files"
705 configExtraIncludeDirs
706 (\v flags -> flags{configExtraIncludeDirs = v})
707 (reqArg' "PATH" (\x -> [makeSymbolicPath x]) (fmap getSymbolicPath))
708 , option
710 ["deterministic"]
711 "Try to be as deterministic as possible (used by the test suite)"
712 configDeterministic
713 (\v flags -> flags{configDeterministic = v})
714 (boolOpt [] [])
715 , option
717 ["ipid"]
718 "Installed package ID to compile this package as"
719 configIPID
720 (\v flags -> flags{configIPID = v})
721 (reqArgFlag "IPID")
722 , option
724 ["cid"]
725 "Installed component ID to compile this component as"
726 (fmap prettyShow . configCID)
727 (\v flags -> flags{configCID = fmap mkComponentId v})
728 (reqArgFlag "CID")
729 , option
731 ["extra-lib-dirs"]
732 "A list of directories to search for external libraries"
733 configExtraLibDirs
734 (\v flags -> flags{configExtraLibDirs = v})
735 (reqArg' "PATH" (\x -> [makeSymbolicPath x]) (fmap getSymbolicPath))
736 , option
738 ["extra-lib-dirs-static"]
739 "A list of directories to search for external libraries when linking fully static executables"
740 configExtraLibDirsStatic
741 (\v flags -> flags{configExtraLibDirsStatic = v})
742 (reqArg' "PATH" (\x -> [makeSymbolicPath x]) (fmap getSymbolicPath))
743 , option
745 ["extra-framework-dirs"]
746 "A list of directories to search for external frameworks (OS X only)"
747 configExtraFrameworkDirs
748 (\v flags -> flags{configExtraFrameworkDirs = v})
749 (reqArg' "PATH" (\x -> [makeSymbolicPath x]) (fmap getSymbolicPath))
750 , option
752 ["extra-prog-path"]
753 "A list of directories to search for required programs (in addition to the normal search locations)"
754 configProgramPathExtra
755 (\v flags -> flags{configProgramPathExtra = v})
756 (reqArg' "PATH" (\x -> toNubList [x]) fromNubList)
757 , option
759 ["constraint"]
760 "A list of additional constraints on the dependencies."
761 configConstraints
762 (\v flags -> flags{configConstraints = v})
763 ( reqArg
764 "DEPENDENCY"
765 (parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsec))
766 (map prettyShow)
768 , option
770 ["dependency"]
771 "A list of exact dependencies. E.g., --dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
772 configDependencies
773 (\v flags -> flags{configDependencies = v})
774 ( reqArg
775 "NAME[:COMPONENT_NAME]=CID"
776 (parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsecGivenComponent))
777 (map prettyGivenComponent)
779 , option
781 ["promised-dependency"]
782 "A list of promised dependencies. E.g., --promised-dependency=\"void-0.5.8=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
783 configPromisedDependencies
784 (\v flags -> flags{configPromisedDependencies = v})
785 ( reqArg
786 "NAME-VER[:COMPONENT_NAME]=CID"
787 (parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsecPromisedComponent))
788 (map prettyPromisedComponent)
790 , option
792 ["instantiate-with"]
793 "A mapping of signature names to concrete module instantiations."
794 configInstantiateWith
795 (\v flags -> flags{configInstantiateWith = v})
796 ( reqArg
797 "NAME=MOD"
798 (parsecToReadE ("Cannot parse module substitution: " ++) (fmap (: []) parsecModSubstEntry))
799 (map (Disp.renderStyle defaultStyle . dispModSubstEntry))
801 , option
803 ["tests"]
804 "dependency checking and compilation for test suites listed in the package description file."
805 configTests
806 (\v flags -> flags{configTests = v})
807 (boolOpt [] [])
808 , option
810 ["coverage"]
811 "build package with Haskell Program Coverage. (GHC only)"
812 configCoverage
813 (\v flags -> flags{configCoverage = v})
814 (boolOpt [] [])
815 , option
817 ["library-coverage"]
818 "build package with Haskell Program Coverage. (GHC only) (DEPRECATED)"
819 configLibCoverage
820 (\v flags -> flags{configLibCoverage = v})
821 (boolOpt [] [])
822 , option
824 ["exact-configuration"]
825 "All direct dependencies and flags are provided on the command line."
826 configExactConfiguration
827 (\v flags -> flags{configExactConfiguration = v})
828 trueArg
829 , option
831 ["benchmarks"]
832 "dependency checking and compilation for benchmarks listed in the package description file."
833 configBenchmarks
834 (\v flags -> flags{configBenchmarks = v})
835 (boolOpt [] [])
836 , option
838 ["relocatable"]
839 "building a package that is relocatable. (GHC only)"
840 configRelocatable
841 (\v flags -> flags{configRelocatable = v})
842 (boolOpt [] [])
843 , option
845 ["response-files"]
846 "enable workaround for old versions of programs like \"ar\" that do not support @file arguments"
847 configUseResponseFiles
848 (\v flags -> flags{configUseResponseFiles = v})
849 (boolOpt' ([], ["disable-response-files"]) ([], []))
850 , option
852 ["allow-depending-on-private-libs"]
853 ( "Allow depending on private libraries. "
854 ++ "If set, the library visibility check MUST be done externally."
856 configAllowDependingOnPrivateLibs
857 (\v flags -> flags{configAllowDependingOnPrivateLibs = v})
858 trueArg
859 , option
861 ["coverage-for"]
862 "A list of unit-ids of libraries to include in the Haskell Program Coverage report."
863 configCoverageFor
864 ( \v flags ->
865 flags
866 { configCoverageFor =
867 mergeListFlag (configCoverageFor flags) v
870 ( reqArg'
871 "UNITID"
872 (Flag . (: []) . fromString)
873 (fmap prettyShow . fromFlagOrDefault [])
875 , option
877 ["ignore-build-tools"]
878 ( "Ignore build tool dependencies. "
879 ++ "If set, declared build tools needn't be found for compilation to proceed."
881 configIgnoreBuildTools
882 (\v flags -> flags{configIgnoreBuildTools = v})
883 trueArg
885 where
886 liftInstallDirs =
887 liftOption configInstallDirs (\v flags -> flags{configInstallDirs = v})
889 reqPathTemplateArgFlag title _sf _lf d get set =
890 reqArgFlag
891 title
895 (fmap fromPathTemplate . get)
896 (set . fmap toPathTemplate)
898 readPackageDbList :: String -> [Maybe PackageDB]
899 readPackageDbList str = [readPackageDb str]
901 -- | Parse a PackageDB stack entry
903 -- @since 3.7.0.0
904 readPackageDb :: String -> Maybe PackageDB
905 readPackageDb "clear" = Nothing
906 readPackageDb "global" = Just GlobalPackageDB
907 readPackageDb "user" = Just UserPackageDB
908 readPackageDb other = Just (SpecificPackageDB (makeSymbolicPath other))
910 showPackageDbList :: [Maybe PackageDB] -> [String]
911 showPackageDbList = map showPackageDb
913 -- | Show a PackageDB stack entry
915 -- @since 3.7.0.0
916 showPackageDb :: Maybe PackageDB -> String
917 showPackageDb Nothing = "clear"
918 showPackageDb (Just GlobalPackageDB) = "global"
919 showPackageDb (Just UserPackageDB) = "user"
920 showPackageDb (Just (SpecificPackageDB db)) = getSymbolicPath db
922 showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
923 showProfDetailLevelFlag NoFlag = []
924 showProfDetailLevelFlag (Flag dl) = [showProfDetailLevel dl]
926 parsecPromisedComponent :: ParsecParser PromisedComponent
927 parsecPromisedComponent = do
928 pn <- parsec
929 ln <- P.option LMainLibName $ do
930 _ <- P.char ':'
931 ucn <- parsec
932 return $
933 if unUnqualComponentName ucn == unPackageName (pkgName pn)
934 then LMainLibName
935 else LSubLibName ucn
936 _ <- P.char '='
937 cid <- parsec
938 return $ PromisedComponent pn ln cid
940 prettyPromisedComponent :: PromisedComponent -> String
941 prettyPromisedComponent (PromisedComponent pn cn cid) =
942 prettyShow pn
943 ++ case cn of
944 LMainLibName -> ""
945 LSubLibName n -> ":" ++ prettyShow n
946 ++ "="
947 ++ prettyShow cid
949 parsecGivenComponent :: ParsecParser GivenComponent
950 parsecGivenComponent = do
951 pn <- parsec
952 ln <- P.option LMainLibName $ do
953 _ <- P.char ':'
954 ucn <- parsec
955 return $
956 if unUnqualComponentName ucn == unPackageName pn
957 then LMainLibName
958 else LSubLibName ucn
959 _ <- P.char '='
960 cid <- parsec
961 return $ GivenComponent pn ln cid
963 prettyGivenComponent :: GivenComponent -> String
964 prettyGivenComponent (GivenComponent pn cn cid) =
965 prettyShow pn
966 ++ case cn of
967 LMainLibName -> ""
968 LSubLibName n -> ":" ++ prettyShow n
969 ++ "="
970 ++ prettyShow cid
972 installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
973 installDirsOptions =
974 [ option
976 ["prefix"]
977 "bake this prefix in preparation of installation"
978 prefix
979 (\v flags -> flags{prefix = v})
980 installDirArg
981 , option
983 ["bindir"]
984 "installation directory for executables"
985 bindir
986 (\v flags -> flags{bindir = v})
987 installDirArg
988 , option
990 ["libdir"]
991 "installation directory for libraries"
992 libdir
993 (\v flags -> flags{libdir = v})
994 installDirArg
995 , option
997 ["libsubdir"]
998 "subdirectory of libdir in which libs are installed"
999 libsubdir
1000 (\v flags -> flags{libsubdir = v})
1001 installDirArg
1002 , option
1004 ["dynlibdir"]
1005 "installation directory for dynamic libraries"
1006 dynlibdir
1007 (\v flags -> flags{dynlibdir = v})
1008 installDirArg
1009 , option
1011 ["libexecdir"]
1012 "installation directory for program executables"
1013 libexecdir
1014 (\v flags -> flags{libexecdir = v})
1015 installDirArg
1016 , option
1018 ["libexecsubdir"]
1019 "subdirectory of libexecdir in which private executables are installed"
1020 libexecsubdir
1021 (\v flags -> flags{libexecsubdir = v})
1022 installDirArg
1023 , option
1025 ["datadir"]
1026 "installation directory for read-only data"
1027 datadir
1028 (\v flags -> flags{datadir = v})
1029 installDirArg
1030 , option
1032 ["datasubdir"]
1033 "subdirectory of datadir in which data files are installed"
1034 datasubdir
1035 (\v flags -> flags{datasubdir = v})
1036 installDirArg
1037 , option
1039 ["docdir"]
1040 "installation directory for documentation"
1041 docdir
1042 (\v flags -> flags{docdir = v})
1043 installDirArg
1044 , option
1046 ["htmldir"]
1047 "installation directory for HTML documentation"
1048 htmldir
1049 (\v flags -> flags{htmldir = v})
1050 installDirArg
1051 , option
1053 ["haddockdir"]
1054 "installation directory for haddock interfaces"
1055 haddockdir
1056 (\v flags -> flags{haddockdir = v})
1057 installDirArg
1058 , option
1060 ["sysconfdir"]
1061 "installation directory for configuration files"
1062 sysconfdir
1063 (\v flags -> flags{sysconfdir = v})
1064 installDirArg
1066 where
1067 installDirArg _sf _lf d get set =
1068 reqArgFlag
1069 "DIR"
1073 (fmap fromPathTemplate . get)
1074 (set . fmap toPathTemplate)
1076 emptyConfigFlags :: ConfigFlags
1077 emptyConfigFlags = mempty
1079 instance Monoid ConfigFlags where
1080 mempty = gmempty
1081 mappend = (<>)
1083 instance Semigroup ConfigFlags where
1084 (<>) = gmappend
1086 -- | Arguments to pass to a @configure@ script, e.g. generated by
1087 -- @autoconf@.
1088 configureArgs :: Bool -> ConfigFlags -> [String]
1089 configureArgs bcHack flags =
1090 hc_flag
1091 ++ optFlag "with-hc-pkg" configHcPkg
1092 ++ optFlag' "prefix" prefix
1093 ++ optFlag' "bindir" bindir
1094 ++ optFlag' "libdir" libdir
1095 ++ optFlag' "libexecdir" libexecdir
1096 ++ optFlag' "datadir" datadir
1097 ++ optFlag' "sysconfdir" sysconfdir
1098 ++ configConfigureArgs flags
1099 where
1100 hc_flag = case (configHcFlavor flags, configHcPath flags) of
1101 (_, Flag hc_path) -> [hc_flag_name ++ hc_path]
1102 (Flag hc, NoFlag) -> [hc_flag_name ++ prettyShow hc]
1103 (NoFlag, NoFlag) -> []
1104 hc_flag_name
1105 -- TODO kill off thic bc hack when defaultUserHooks is removed.
1106 | bcHack = "--with-hc="
1107 | otherwise = "--with-compiler="
1108 optFlag name config_field = case config_field flags of
1109 Flag p -> ["--" ++ name ++ "=" ++ p]
1110 NoFlag -> []
1111 optFlag' name config_field =
1112 optFlag
1113 name
1114 ( fmap fromPathTemplate
1115 . config_field
1116 . configInstallDirs