2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
10 -- Module : Distribution.Simple.Setup.Config
11 -- Copyright : Isaac Jones 2003-2004
15 -- Maintainer : cabal-devel@haskell.org
16 -- Portability : portable
18 -- Definition of the configure command-line options.
19 -- See: @Distribution.Simple.Setup@
20 module Distribution
.Simple
.Setup
.Config
36 import Distribution
.Compat
.Prelude
hiding (get
)
39 import qualified Distribution
.Compat
.CharParsing
as P
40 import Distribution
.Compiler
41 import Distribution
.ModuleName
42 import Distribution
.PackageDescription
43 import Distribution
.Parsec
44 import Distribution
.Pretty
45 import Distribution
.ReadE
46 import Distribution
.Simple
.Command
hiding (boolOpt
, boolOpt
')
47 import Distribution
.Simple
.Compiler
48 import Distribution
.Simple
.Flag
49 import Distribution
.Simple
.InstallDirs
50 import Distribution
.Simple
.Program
51 import Distribution
.Simple
.Utils
52 import Distribution
.Types
.ComponentId
53 import Distribution
.Types
.DumpBuildInfo
54 import Distribution
.Types
.GivenComponent
55 import Distribution
.Types
.Module
56 import Distribution
.Types
.PackageVersionConstraint
57 import Distribution
.Utils
.NubList
58 import Distribution
.Verbosity
59 import qualified Text
.PrettyPrint
as Disp
61 import Distribution
.Compat
.Semigroup
(Last
' (..), Option
' (..))
62 import Distribution
.Compat
.Stack
64 import Distribution
.Simple
.Setup
.Common
66 -- ------------------------------------------------------------
70 -- ------------------------------------------------------------
72 -- | Flags to @configure@ command.
74 -- IMPORTANT: every time a new flag is added, 'D.C.Setup.filterConfigureFlags'
76 -- IMPORTANT: every time a new flag is added, it should be added to the Eq instance
77 data ConfigFlags
= ConfigFlags
78 { -- This is the same hack as in 'buildArgs' and 'copyArgs'.
79 -- TODO: Stop using this eventually when 'UserHooks' gets changed
80 configArgs
:: [String]
81 , -- FIXME: the configPrograms is only here to pass info through to configure
82 -- because the type of configure is constrained by the UserHooks.
83 -- when we change UserHooks next we should pass the initial
84 -- ProgramDb directly and not via ConfigFlags
85 configPrograms_
:: Option
' (Last
' ProgramDb
)
86 -- ^ All programs that
88 , configProgramPaths
:: [(String, FilePath)]
89 -- ^ user specified programs paths
90 , configProgramArgs
:: [(String, [String])]
91 -- ^ user specified programs args
92 , configProgramPathExtra
:: NubList
FilePath
94 , configHcFlavor
:: Flag CompilerFlavor
95 -- ^ The \"flavor\" of the
96 -- compiler, e.g. GHC.
97 , configHcPath
:: Flag
FilePath
98 -- ^ given compiler location
99 , configHcPkg
:: Flag
FilePath
100 -- ^ given hc-pkg location
101 , configVanillaLib
:: Flag
Bool
102 -- ^ Enable vanilla library
103 , configProfLib
:: Flag
Bool
104 -- ^ Enable profiling in the library
105 , configSharedLib
:: Flag
Bool
106 -- ^ Build shared library
107 , configStaticLib
:: Flag
Bool
108 -- ^ Build static library
109 , configDynExe
:: Flag
Bool
110 -- ^ Enable dynamic linking of the
112 , configFullyStaticExe
:: Flag
Bool
113 -- ^ Enable fully static linking of the
115 , configProfExe
:: Flag
Bool
116 -- ^ Enable profiling in the
118 , configProf
:: Flag
Bool
119 -- ^ Enable profiling in the library
121 , configProfDetail
:: Flag ProfDetailLevel
122 -- ^ Profiling detail level
123 -- in the library and executables.
124 , configProfLibDetail
:: Flag ProfDetailLevel
125 -- ^ Profiling detail level
127 , configConfigureArgs
:: [String]
128 -- ^ Extra arguments to @configure@
129 , configOptimization
:: Flag OptimisationLevel
130 -- ^ Enable optimization.
131 , configProgPrefix
:: Flag PathTemplate
132 -- ^ Installed executable prefix.
133 , configProgSuffix
:: Flag PathTemplate
134 -- ^ Installed executable suffix.
135 , configInstallDirs
:: InstallDirs
(Flag PathTemplate
)
138 , configScratchDir
:: Flag
FilePath
139 , configExtraLibDirs
:: [FilePath]
140 -- ^ path to search for extra libraries
141 , configExtraLibDirsStatic
:: [FilePath]
142 -- ^ path to search for extra
143 -- libraries when linking
144 -- fully static executables
145 , configExtraFrameworkDirs
:: [FilePath]
146 -- ^ path to search for extra
147 -- frameworks (OS X only)
148 , configExtraIncludeDirs
:: [FilePath]
149 -- ^ path to search for header files
150 , configIPID
:: Flag
String
151 -- ^ explicit IPID to be used
152 , configCID
:: Flag ComponentId
153 -- ^ explicit CID to be used
154 , configDeterministic
:: Flag
Bool
155 -- ^ be as deterministic as possible
156 -- (e.g., invariant over GHC, database,
157 -- etc). Used by the test suite
158 , configDistPref
:: Flag
FilePath
160 , configCabalFilePath
:: Flag
FilePath
161 -- ^ Cabal file to use
162 , configVerbosity
:: Flag Verbosity
164 , configUserInstall
:: Flag
Bool
165 -- ^ The --user\/--global flag
166 , configPackageDBs
:: [Maybe PackageDB
]
167 -- ^ Which package DBs to use
168 , configGHCiLib
:: Flag
Bool
169 -- ^ Enable compiling library for GHCi
170 , configSplitSections
:: Flag
Bool
171 -- ^ Enable -split-sections with GHC
172 , configSplitObjs
:: Flag
Bool
173 -- ^ Enable -split-objs with GHC
174 , configStripExes
:: Flag
Bool
175 -- ^ Enable executable stripping
176 , configStripLibs
:: Flag
Bool
177 -- ^ Enable library stripping
178 , configConstraints
:: [PackageVersionConstraint
]
179 -- ^ Additional constraints for
181 , configDependencies
:: [GivenComponent
]
182 -- ^ The packages depended on which already exist
183 , configPromisedDependencies
:: [GivenComponent
]
184 -- ^ The packages depended on which doesn't yet exist (i.e. promised).
185 -- Promising dependencies enables us to configure components in parallel,
186 -- and avoids expensive builds if they are not necessary.
187 -- For example, in multi-repl mode, we don't want to build dependencies that
188 -- are loaded into the interactive session, since we have to build them again.
189 , configInstantiateWith
:: [(ModuleName
, Module
)]
190 -- ^ The requested Backpack instantiation. If empty, either this
191 -- package does not use Backpack, or we just want to typecheck
192 -- the indefinite package.
193 , configConfigurationsFlags
:: FlagAssignment
194 , configTests
:: Flag
Bool
195 -- ^ Enable test suite compilation
196 , configBenchmarks
:: Flag
Bool
197 -- ^ Enable benchmark compilation
198 , configCoverage
:: Flag
Bool
199 -- ^ Enable program coverage
200 , configLibCoverage
:: Flag
Bool
201 -- ^ Enable program coverage (deprecated)
202 , configExactConfiguration
:: Flag
Bool
203 -- ^ All direct dependencies and flags are provided on the command line by
204 -- the user via the '--dependency' and '--flags' options.
205 , configFlagError
:: Flag
String
206 -- ^ Halt and show an error message indicating an error in flag assignment
207 , configRelocatable
:: Flag
Bool
208 -- ^ Enable relocatable package built
209 , configDebugInfo
:: Flag DebugInfoLevel
210 -- ^ Emit debug info.
211 , configDumpBuildInfo
:: Flag DumpBuildInfo
212 -- ^ Should we dump available build information on build?
213 -- Dump build information to disk before attempting to build,
214 -- tooling can parse these files and use them to compile the
215 -- source files themselves.
216 , configUseResponseFiles
:: Flag
Bool
217 -- ^ Whether to use response files at all. They're used for such tools
218 -- as haddock, or ld.
219 , configAllowDependingOnPrivateLibs
:: Flag
Bool
220 -- ^ Allow depending on private sublibraries. This is used by external
221 -- tools (like cabal-install) so they can add multiple-public-libraries
222 -- compatibility to older ghcs by checking visibility externally.
224 deriving (Generic
, Read, Show, Typeable
)
226 instance Binary ConfigFlags
227 instance Structured ConfigFlags
229 -- | More convenient version of 'configPrograms'. Results in an
230 -- 'error' if internal invariant is violated.
231 configPrograms
:: WithCallStack
(ConfigFlags
-> ProgramDb
)
233 fromMaybe (error "FIXME: remove configPrograms")
238 instance Eq ConfigFlags
where
240 -- configPrograms skipped: not user specified, has no Eq instance
241 equal configProgramPaths
242 && equal configProgramArgs
243 && equal configProgramPathExtra
244 && equal configHcFlavor
245 && equal configHcPath
247 && equal configVanillaLib
248 && equal configProfLib
249 && equal configSharedLib
250 && equal configStaticLib
251 && equal configDynExe
252 && equal configFullyStaticExe
253 && equal configProfExe
255 && equal configProfDetail
256 && equal configProfLibDetail
257 && equal configConfigureArgs
258 && equal configOptimization
259 && equal configProgPrefix
260 && equal configProgSuffix
261 && equal configInstallDirs
262 && equal configScratchDir
263 && equal configExtraLibDirs
264 && equal configExtraLibDirsStatic
265 && equal configExtraIncludeDirs
267 && equal configDeterministic
268 && equal configDistPref
269 && equal configVerbosity
270 && equal configUserInstall
271 && equal configPackageDBs
272 && equal configGHCiLib
273 && equal configSplitSections
274 && equal configSplitObjs
275 && equal configStripExes
276 && equal configStripLibs
277 && equal configConstraints
278 && equal configDependencies
279 && equal configPromisedDependencies
280 && equal configConfigurationsFlags
282 && equal configBenchmarks
283 && equal configCoverage
284 && equal configLibCoverage
285 && equal configExactConfiguration
286 && equal configFlagError
287 && equal configRelocatable
288 && equal configDebugInfo
289 && equal configDumpBuildInfo
290 && equal configUseResponseFiles
292 equal f
= on
(==) f a b
294 configAbsolutePaths
:: ConfigFlags
-> IO ConfigFlags
295 configAbsolutePaths f
=
296 (\v -> f
{configPackageDBs
= v
})
298 (maybe (return Nothing
) (liftM Just
. absolutePackageDBPath
))
301 {- FOURMOLU_DISABLE -}
302 defaultConfigFlags
:: ProgramDb
-> ConfigFlags
303 defaultConfigFlags progDb
=
306 , configPrograms_
= Option
' (Just
(Last
' progDb
))
307 , configHcFlavor
= maybe NoFlag Flag defaultCompilerFlavor
308 , configVanillaLib
= Flag
True
309 , configProfLib
= NoFlag
310 , configSharedLib
= NoFlag
311 , configStaticLib
= NoFlag
312 , configDynExe
= Flag
False
313 , configFullyStaticExe
= Flag
False
314 , configProfExe
= NoFlag
315 , configProf
= NoFlag
316 , configProfDetail
= NoFlag
317 , configProfLibDetail
= NoFlag
318 , configOptimization
= Flag NormalOptimisation
319 , configProgPrefix
= Flag
(toPathTemplate
"")
320 , configProgSuffix
= Flag
(toPathTemplate
"")
321 , configDistPref
= NoFlag
322 , configCabalFilePath
= NoFlag
323 , configVerbosity
= Flag normal
324 , configUserInstall
= Flag
False -- TODO: reverse this
325 #if defined
(mingw32_HOST_OS
)
326 -- See #8062 and GHC #21019.
327 , configGHCiLib
= Flag
False
329 , configGHCiLib
= NoFlag
331 , configSplitSections
= Flag
False
332 , configSplitObjs
= Flag
False -- takes longer, so turn off by default
333 , configStripExes
= NoFlag
334 , configStripLibs
= NoFlag
335 , configTests
= Flag
False
336 , configBenchmarks
= Flag
False
337 , configCoverage
= Flag
False
338 , configLibCoverage
= NoFlag
339 , configExactConfiguration
= Flag
False
340 , configFlagError
= NoFlag
341 , configRelocatable
= Flag
False
342 , configDebugInfo
= Flag NoDebugInfo
343 , configDumpBuildInfo
= NoFlag
344 , configUseResponseFiles
= NoFlag
346 {- FOURMOLU_ENABLE -}
348 configureCommand
:: ProgramDb
-> CommandUI ConfigFlags
349 configureCommand progDb
=
351 { commandName
= "configure"
352 , commandSynopsis
= "Prepare to build the package."
353 , commandDescription
= Just
$ \_
->
355 "Configure how the package is built by setting "
356 ++ "package (and other) flags.\n"
358 ++ "The configuration affects several other commands, "
359 ++ "including build, test, bench, run, repl.\n"
360 , commandNotes
= Just
$ \_pname
-> programFlagsDescription progDb
361 , commandUsage
= \pname
->
362 "Usage: " ++ pname
++ " configure [FLAGS]\n"
363 , commandDefaultFlags
= defaultConfigFlags progDb
364 , commandOptions
= \showOrParseArgs
->
365 configureOptions showOrParseArgs
370 (\v fs
-> fs
{configProgramPaths
= v
})
375 (\v fs
-> fs
{configProgramArgs
= v
})
380 (\v fs
-> fs
{configProgramArgs
= v
})
383 -- | Inverse to 'dispModSubstEntry'.
384 parsecModSubstEntry
:: ParsecParser
(ModuleName
, Module
)
385 parsecModSubstEntry
= do
391 -- | Pretty-print a single entry of a module substitution.
392 dispModSubstEntry
:: (ModuleName
, Module
) -> Disp
.Doc
393 dispModSubstEntry
(k
, v
) = pretty k
<<>> Disp
.char
'=' <<>> pretty v
395 configureOptions
:: ShowOrParseArgs
-> [OptionField ConfigFlags
]
396 configureOptions showOrParseArgs
=
399 (\v flags
-> flags
{configVerbosity
= v
})
402 (\d flags
-> flags
{configDistPref
= d
})
409 (\v flags
-> flags
{configHcFlavor
= v
})
411 [ (Flag GHC
, ("g", ["ghc"]), "compile with GHC")
412 , (Flag GHCJS
, ([], ["ghcjs"]), "compile with GHCJS")
413 , (Flag UHC
, ([], ["uhc"]), "compile with UHC")
414 , -- "haskell-suite" compiler id string will be replaced
415 -- by a more specific one during the configure stage
417 ( Flag
(HaskellSuite
"haskell-suite")
418 , ([], ["haskell-suite"])
419 , "compile with a haskell-suite compiler"
426 "use this Cabal file"
428 (\v flags
-> flags
{configCabalFilePath
= v
})
433 "give the path to a particular compiler"
435 (\v flags
-> flags
{configHcPath
= v
})
440 "give the path to the package tool"
442 (\v flags
-> flags
{configHcPkg
= v
})
445 ++ map liftInstallDirs installDirsOptions
449 "prefix to be applied to installed executables"
451 (\v flags
-> flags
{configProgPrefix
= v
})
452 (reqPathTemplateArgFlag
"PREFIX")
456 "suffix to be applied to installed executables"
458 (\v flags
-> flags
{configProgSuffix
= v
})
459 (reqPathTemplateArgFlag
"SUFFIX")
465 (\v flags
-> flags
{configVanillaLib
= v
})
469 ["library-profiling"]
472 (\v flags
-> flags
{configProfLib
= v
})
479 (\v flags
-> flags
{configSharedLib
= v
})
486 (\v flags
-> flags
{configStaticLib
= v
})
490 ["executable-dynamic"]
491 "Executable dynamic linking"
493 (\v flags
-> flags
{configDynExe
= v
})
497 ["executable-static"]
498 "Executable fully static linking"
500 (\v flags
-> flags
{configFullyStaticExe
= v
})
505 "Executable and library profiling"
507 (\v flags
-> flags
{configProf
= v
})
511 ["executable-profiling"]
512 "Executable profiling (DEPRECATED)"
514 (\v flags
-> flags
{configProfExe
= v
})
519 ( "Profiling detail level for executable and library (default, "
520 ++ "none, exported-functions, toplevel-functions, all-functions, late)."
523 (\v flags
-> flags
{configProfDetail
= v
})
526 (Flag
. flagToProfDetailLevel
)
527 showProfDetailLevelFlag
531 ["library-profiling-detail"]
532 "Profiling detail level for libraries only."
534 (\v flags
-> flags
{configProfLibDetail
= v
})
537 (Flag
. flagToProfDetailLevel
)
538 showProfDetailLevelFlag
543 (\v flags
-> flags
{configOptimization
= v
})
546 (show NoOptimisation
, Flag
. flagToOptimisationLevel
)
548 Flag NoOptimisation
-> []
549 Flag NormalOptimisation
-> [Nothing
]
550 Flag MaximumOptimisation
-> [Just
"2"]
554 ["enable-optimization", "enable-optimisation"]
555 "Build with optimization (n is 0--2, default is 1)"
557 (Flag NoOptimisation
)
559 ["disable-optimization", "disable-optimisation"]
560 "Build without optimization"
565 (\v flags
-> flags
{configDebugInfo
= v
})
568 (Flag
. flagToDebugInfoLevel
)
570 Flag NoDebugInfo
-> []
571 Flag MinimalDebugInfo
-> [Just
"1"]
572 Flag NormalDebugInfo
-> [Nothing
]
573 Flag MaximalDebugInfo
-> [Just
"3"]
577 ["enable-debug-info"]
578 "Emit debug info (n is 0--3, default is 0)"
582 ["disable-debug-info"]
583 "Don't emit debug info"
588 (\v flags
-> flags
{configDumpBuildInfo
= v
})
592 ["enable-build-info"]
593 "Enable build information generation during project building"
595 (Flag NoDumpBuildInfo
)
597 ["disable-build-info"]
598 "Disable build information generation during project building"
603 "compile library for use with GHCi"
605 (\v flags
-> flags
{configGHCiLib
= v
})
610 "compile library code such that unneeded definitions can be dropped from the final executable (GHC 7.8+)"
612 (\v flags
-> flags
{configSplitSections
= v
})
617 "split library into smaller objects to reduce binary sizes (GHC 6.6+)"
619 (\v flags
-> flags
{configSplitObjs
= v
})
623 ["executable-stripping"]
624 "strip executables upon installation to reduce binary sizes"
626 (\v flags
-> flags
{configStripExes
= v
})
630 ["library-stripping"]
631 "strip libraries upon installation to reduce binary sizes"
633 (\v flags
-> flags
{configStripLibs
= v
})
638 "Extra option for configure"
640 (\v flags
-> flags
{configConfigureArgs
= v
})
641 (reqArg
' "OPT" (\x
-> [x
]) id)
645 "doing a per-user installation"
647 (\v flags
-> flags
{configUserInstall
= v
})
648 (boolOpt
' ([], ["user"]) ([], ["global"]))
652 ( "Append the given package database to the list of package"
653 ++ " databases used (to satisfy dependencies and register into)."
654 ++ " May be a specific file, 'global' or 'user'. The initial list"
655 ++ " is ['global'], ['global', 'user'], or ['global', $sandbox],"
656 ++ " depending on context. Use 'clear' to reset the list to empty."
657 ++ " See the user guide for details."
660 (\v flags
-> flags
{configPackageDBs
= v
})
661 (reqArg
' "DB" readPackageDbList showPackageDbList
)
665 "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."
666 configConfigurationsFlags
667 (\v flags
-> flags
{configConfigurationsFlags
= v
})
670 (parsecToReadE
(\err
-> "Invalid flag assignment: " ++ err
) legacyParsecFlagAssignment
)
671 legacyShowFlagAssignment
'
675 ["extra-include-dirs"]
676 "A list of directories to search for header files"
677 configExtraIncludeDirs
678 (\v flags
-> flags
{configExtraIncludeDirs
= v
})
679 (reqArg
' "PATH" (\x
-> [x
]) id)
683 "Try to be as deterministic as possible (used by the test suite)"
685 (\v flags
-> flags
{configDeterministic
= v
})
690 "Installed package ID to compile this package as"
692 (\v flags
-> flags
{configIPID
= v
})
697 "Installed component ID to compile this component as"
698 (fmap prettyShow
. configCID
)
699 (\v flags
-> flags
{configCID
= fmap mkComponentId v
})
704 "A list of directories to search for external libraries"
706 (\v flags
-> flags
{configExtraLibDirs
= v
})
707 (reqArg
' "PATH" (\x
-> [x
]) id)
710 ["extra-lib-dirs-static"]
711 "A list of directories to search for external libraries when linking fully static executables"
712 configExtraLibDirsStatic
713 (\v flags
-> flags
{configExtraLibDirsStatic
= v
})
714 (reqArg
' "PATH" (\x
-> [x
]) id)
717 ["extra-framework-dirs"]
718 "A list of directories to search for external frameworks (OS X only)"
719 configExtraFrameworkDirs
720 (\v flags
-> flags
{configExtraFrameworkDirs
= v
})
721 (reqArg
' "PATH" (\x
-> [x
]) id)
725 "A list of directories to search for required programs (in addition to the normal search locations)"
726 configProgramPathExtra
727 (\v flags
-> flags
{configProgramPathExtra
= v
})
728 (reqArg
' "PATH" (\x
-> toNubList
[x
]) fromNubList
)
732 "A list of additional constraints on the dependencies."
734 (\v flags
-> flags
{configConstraints
= v
})
737 (parsecToReadE
(const "dependency expected") ((\x
-> [x
]) `
fmap` parsec
))
743 "A list of exact dependencies. E.g., --dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
745 (\v flags
-> flags
{configDependencies
= v
})
747 "NAME[:COMPONENT_NAME]=CID"
748 (parsecToReadE
(const "dependency expected") ((\x
-> [x
]) `
fmap` parsecGivenComponent
))
749 (map prettyGivenComponent
)
753 ["promised-dependency"]
754 "A list of promised dependencies. E.g., --promised-dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
755 configPromisedDependencies
756 (\v flags
-> flags
{configPromisedDependencies
= v
})
758 "NAME[:COMPONENT_NAME]=CID"
759 (parsecToReadE
(const "dependency expected") ((\x
-> [x
]) `
fmap` parsecGivenComponent
))
760 (map prettyGivenComponent
)
765 "A mapping of signature names to concrete module instantiations."
766 configInstantiateWith
767 (\v flags
-> flags
{configInstantiateWith
= v
})
770 (parsecToReadE
("Cannot parse module substitution: " ++) (fmap (: []) parsecModSubstEntry
))
771 (map (Disp
.renderStyle defaultStyle
. dispModSubstEntry
))
776 "dependency checking and compilation for test suites listed in the package description file."
778 (\v flags
-> flags
{configTests
= v
})
783 "build package with Haskell Program Coverage. (GHC only)"
785 (\v flags
-> flags
{configCoverage
= v
})
790 "build package with Haskell Program Coverage. (GHC only) (DEPRECATED)"
792 (\v flags
-> flags
{configLibCoverage
= v
})
796 ["exact-configuration"]
797 "All direct dependencies and flags are provided on the command line."
798 configExactConfiguration
799 (\v flags
-> flags
{configExactConfiguration
= v
})
804 "dependency checking and compilation for benchmarks listed in the package description file."
806 (\v flags
-> flags
{configBenchmarks
= v
})
811 "building a package that is relocatable. (GHC only)"
813 (\v flags
-> flags
{configRelocatable
= v
})
818 "enable workaround for old versions of programs like \"ar\" that do not support @file arguments"
819 configUseResponseFiles
820 (\v flags
-> flags
{configUseResponseFiles
= v
})
821 (boolOpt
' ([], ["disable-response-files"]) ([], []))
824 ["allow-depending-on-private-libs"]
825 ( "Allow depending on private libraries. "
826 ++ "If set, the library visibility check MUST be done externally."
828 configAllowDependingOnPrivateLibs
829 (\v flags
-> flags
{configAllowDependingOnPrivateLibs
= v
})
834 liftOption configInstallDirs
(\v flags
-> flags
{configInstallDirs
= v
})
836 reqPathTemplateArgFlag title _sf _lf d get set
=
842 (fmap fromPathTemplate
. get
)
843 (set
. fmap toPathTemplate
)
845 readPackageDbList
:: String -> [Maybe PackageDB
]
846 readPackageDbList str
= [readPackageDb str
]
848 -- | Parse a PackageDB stack entry
851 readPackageDb
:: String -> Maybe PackageDB
852 readPackageDb
"clear" = Nothing
853 readPackageDb
"global" = Just GlobalPackageDB
854 readPackageDb
"user" = Just UserPackageDB
855 readPackageDb other
= Just
(SpecificPackageDB other
)
857 showPackageDbList
:: [Maybe PackageDB
] -> [String]
858 showPackageDbList
= map showPackageDb
860 -- | Show a PackageDB stack entry
863 showPackageDb
:: Maybe PackageDB
-> String
864 showPackageDb Nothing
= "clear"
865 showPackageDb
(Just GlobalPackageDB
) = "global"
866 showPackageDb
(Just UserPackageDB
) = "user"
867 showPackageDb
(Just
(SpecificPackageDB db
)) = db
869 showProfDetailLevelFlag
:: Flag ProfDetailLevel
-> [String]
870 showProfDetailLevelFlag NoFlag
= []
871 showProfDetailLevelFlag
(Flag dl
) = [showProfDetailLevel dl
]
873 parsecGivenComponent
:: ParsecParser GivenComponent
874 parsecGivenComponent
= do
876 ln
<- P
.option LMainLibName
$ do
880 if unUnqualComponentName ucn
== unPackageName pn
885 return $ GivenComponent pn ln cid
887 prettyGivenComponent
:: GivenComponent
-> String
888 prettyGivenComponent
(GivenComponent pn cn cid
) =
892 LSubLibName n
-> ":" ++ prettyShow n
896 installDirsOptions
:: [OptionField
(InstallDirs
(Flag PathTemplate
))]
901 "bake this prefix in preparation of installation"
903 (\v flags
-> flags
{prefix
= v
})
908 "installation directory for executables"
910 (\v flags
-> flags
{bindir
= v
})
915 "installation directory for libraries"
917 (\v flags
-> flags
{libdir
= v
})
922 "subdirectory of libdir in which libs are installed"
924 (\v flags
-> flags
{libsubdir
= v
})
929 "installation directory for dynamic libraries"
931 (\v flags
-> flags
{dynlibdir
= v
})
936 "installation directory for program executables"
938 (\v flags
-> flags
{libexecdir
= v
})
943 "subdirectory of libexecdir in which private executables are installed"
945 (\v flags
-> flags
{libexecsubdir
= v
})
950 "installation directory for read-only data"
952 (\v flags
-> flags
{datadir
= v
})
957 "subdirectory of datadir in which data files are installed"
959 (\v flags
-> flags
{datasubdir
= v
})
964 "installation directory for documentation"
966 (\v flags
-> flags
{docdir
= v
})
971 "installation directory for HTML documentation"
973 (\v flags
-> flags
{htmldir
= v
})
978 "installation directory for haddock interfaces"
980 (\v flags
-> flags
{haddockdir
= v
})
985 "installation directory for configuration files"
987 (\v flags
-> flags
{sysconfdir
= v
})
991 installDirArg _sf _lf d get set
=
997 (fmap fromPathTemplate
. get
)
998 (set
. fmap toPathTemplate
)
1000 emptyConfigFlags
:: ConfigFlags
1001 emptyConfigFlags
= mempty
1003 instance Monoid ConfigFlags
where
1007 instance Semigroup ConfigFlags
where
1010 -- | Arguments to pass to a @configure@ script, e.g. generated by
1012 configureArgs
:: Bool -> ConfigFlags
-> [String]
1013 configureArgs bcHack flags
=
1015 ++ optFlag
"with-hc-pkg" configHcPkg
1016 ++ optFlag
' "prefix" prefix
1017 ++ optFlag
' "bindir" bindir
1018 ++ optFlag
' "libdir" libdir
1019 ++ optFlag
' "libexecdir" libexecdir
1020 ++ optFlag
' "datadir" datadir
1021 ++ optFlag
' "sysconfdir" sysconfdir
1022 ++ configConfigureArgs flags
1024 hc_flag
= case (configHcFlavor flags
, configHcPath flags
) of
1025 (_
, Flag hc_path
) -> [hc_flag_name
++ hc_path
]
1026 (Flag hc
, NoFlag
) -> [hc_flag_name
++ prettyShow hc
]
1027 (NoFlag
, NoFlag
) -> []
1029 -- TODO kill off thic bc hack when defaultUserHooks is removed.
1030 | bcHack
= "--with-hc="
1031 |
otherwise = "--with-compiler="
1032 optFlag name config_field
= case config_field flags
of
1033 Flag p
-> ["--" ++ name
++ "=" ++ p
]
1035 optFlag
' name config_field
=
1038 ( fmap fromPathTemplate