Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / Setup.hs
blobcd8f10aff3c41692aa39cee0f28f35b9b4f92995
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE LambdaCase #-}
6 {-# LANGUAGE RankNTypes #-}
8 -----------------------------------------------------------------------------
10 -- |
11 -- Module : Distribution.Simple.Setup
12 -- Copyright : Isaac Jones 2003-2004
13 -- Duncan Coutts 2007
14 -- License : BSD3
16 -- Maintainer : cabal-devel@haskell.org
17 -- Portability : portable
19 -- This module defines the command line interface for all the Cabal
20 -- commands. For each command (like @configure@, @build@ etc) it defines a type
21 -- that holds all the flags, the default set of flags and a 'CommandUI' that
22 -- maps command line flags to and from the corresponding flags type.
24 -- All the flags types are instances of 'Monoid', see
25 -- <http://www.haskell.org/pipermail/cabal-devel/2007-December/001509.html>
26 -- for an explanation.
28 -- The types defined here get used in the front end and especially in
29 -- @cabal-install@ which has to do quite a bit of manipulating sets of command
30 -- line flags.
32 -- This is actually relatively nice, it works quite well. The main change it
33 -- needs is to unify it with the code for managing sets of fields that can be
34 -- read and written from files. This would allow us to save configure flags in
35 -- config files.
36 module Distribution.Simple.Setup
37 ( GlobalFlags (..)
38 , emptyGlobalFlags
39 , defaultGlobalFlags
40 , globalCommand
41 , ConfigFlags (..)
42 , emptyConfigFlags
43 , defaultConfigFlags
44 , configureCommand
45 , configPrograms
46 , configAbsolutePaths
47 , readPackageDb
48 , readPackageDbList
49 , showPackageDb
50 , showPackageDbList
51 , CopyFlags (..)
52 , emptyCopyFlags
53 , defaultCopyFlags
54 , copyCommand
55 , InstallFlags (..)
56 , emptyInstallFlags
57 , defaultInstallFlags
58 , installCommand
59 , HaddockTarget (..)
60 , HaddockFlags (..)
61 , emptyHaddockFlags
62 , defaultHaddockFlags
63 , haddockCommand
64 , Visibility (..)
65 , HaddockProjectFlags (..)
66 , emptyHaddockProjectFlags
67 , defaultHaddockProjectFlags
68 , haddockProjectCommand
69 , HscolourFlags (..)
70 , emptyHscolourFlags
71 , defaultHscolourFlags
72 , hscolourCommand
73 , BuildFlags (..)
74 , emptyBuildFlags
75 , defaultBuildFlags
76 , buildCommand
77 , DumpBuildInfo (..)
78 , ReplFlags (..)
79 , defaultReplFlags
80 , replCommand
81 , ReplOptions (..)
82 , CleanFlags (..)
83 , emptyCleanFlags
84 , defaultCleanFlags
85 , cleanCommand
86 , RegisterFlags (..)
87 , emptyRegisterFlags
88 , defaultRegisterFlags
89 , registerCommand
90 , unregisterCommand
91 , SDistFlags (..)
92 , emptySDistFlags
93 , defaultSDistFlags
94 , sdistCommand
95 , TestFlags (..)
96 , emptyTestFlags
97 , defaultTestFlags
98 , testCommand
99 , TestShowDetails (..)
100 , BenchmarkFlags (..)
101 , emptyBenchmarkFlags
102 , defaultBenchmarkFlags
103 , benchmarkCommand
104 , CopyDest (..)
105 , configureArgs
106 , configureOptions
107 , configureCCompiler
108 , configureLinker
109 , buildOptions
110 , haddockOptions
111 , haddockProjectOptions
112 , installDirsOptions
113 , testOptions'
114 , benchmarkOptions'
115 , programDbOptions
116 , programDbPaths'
117 , programFlagsDescription
118 , replOptions
119 , splitArgs
120 , defaultDistPref
121 , optionDistPref
122 , Flag (..)
123 , toFlag
124 , fromFlag
125 , fromFlagOrDefault
126 , flagToMaybe
127 , flagToList
128 , maybeToFlag
129 , BooleanFlag (..)
130 , boolOpt
131 , boolOpt'
132 , trueArg
133 , falseArg
134 , optionVerbosity
135 , BuildingWhat (..)
136 , buildingWhatVerbosity
137 , buildingWhatDistPref
138 ) where
140 import GHC.Generics (Generic)
141 import Prelude (FilePath, Show, ($))
143 import Distribution.Simple.Flag
144 import Distribution.Simple.InstallDirs
145 import Distribution.Types.DumpBuildInfo
147 import Distribution.Simple.Setup.Benchmark
148 import Distribution.Simple.Setup.Build
149 import Distribution.Simple.Setup.Clean
150 import Distribution.Simple.Setup.Common
151 import Distribution.Simple.Setup.Config
152 import Distribution.Simple.Setup.Copy
153 import Distribution.Simple.Setup.Global
154 import Distribution.Simple.Setup.Haddock
155 import Distribution.Simple.Setup.Hscolour
156 import Distribution.Simple.Setup.Install
157 import Distribution.Simple.Setup.Register
158 import Distribution.Simple.Setup.Repl
159 import Distribution.Simple.Setup.SDist
160 import Distribution.Simple.Setup.Test
162 import Distribution.Verbosity (Verbosity)
164 -- | What kind of build are we doing?
166 -- Is this a normal build, or is it perhaps for running an interactive
167 -- session or Haddock?
168 data BuildingWhat
169 = -- | A normal build.
170 BuildNormal BuildFlags
171 | -- | Build steps for an interactive session.
172 BuildRepl ReplFlags
173 | -- | Build steps for generating documentation.
174 BuildHaddock HaddockFlags
175 | -- | Build steps for Hscolour.
176 BuildHscolour HscolourFlags
177 deriving (Generic, Show)
179 buildingWhatVerbosity :: BuildingWhat -> Verbosity
180 buildingWhatVerbosity = \case
181 BuildNormal flags -> fromFlag $ buildVerbosity flags
182 BuildRepl flags -> fromFlag $ replVerbosity flags
183 BuildHaddock flags -> fromFlag $ haddockVerbosity flags
184 BuildHscolour flags -> fromFlag $ hscolourVerbosity flags
186 buildingWhatDistPref :: BuildingWhat -> FilePath
187 buildingWhatDistPref = \case
188 BuildNormal flags -> fromFlag $ buildDistPref flags
189 BuildRepl flags -> fromFlag $ replDistPref flags
190 BuildHaddock flags -> fromFlag $ haddockDistPref flags
191 BuildHscolour flags -> fromFlag $ hscolourDistPref flags
193 -- The test cases kinda have to be rewritten from the ground up... :/
194 -- hunitTests :: [Test]
195 -- hunitTests =
196 -- let m = [("ghc", GHC), ("nhc98", NHC), ("hugs", Hugs)]
197 -- (flags, commands', unkFlags, ers)
198 -- = getOpt Permute options ["configure", "foobar", "--prefix=/foo", "--ghc", "--nhc98", "--hugs", "--with-compiler=/comp", "--unknown1", "--unknown2", "--install-prefix=/foo", "--user", "--global"]
199 -- in [TestLabel "very basic option parsing" $ TestList [
200 -- "getOpt flags" ~: "failed" ~:
201 -- [Prefix "/foo", GhcFlag, NhcFlag, HugsFlag,
202 -- WithCompiler "/comp", InstPrefix "/foo", UserFlag, GlobalFlag]
203 -- ~=? flags,
204 -- "getOpt commands" ~: "failed" ~: ["configure", "foobar"] ~=? commands',
205 -- "getOpt unknown opts" ~: "failed" ~:
206 -- ["--unknown1", "--unknown2"] ~=? unkFlags,
207 -- "getOpt errors" ~: "failed" ~: [] ~=? ers],
209 -- TestLabel "test location of various compilers" $ TestList
210 -- ["configure parsing for prefix and compiler flag" ~: "failed" ~:
211 -- (Right (ConfigCmd (Just comp, Nothing, Just "/usr/local"), []))
212 -- ~=? (parseArgs ["--prefix=/usr/local", "--"++name, "configure"])
213 -- | (name, comp) <- m],
215 -- TestLabel "find the package tool" $ TestList
216 -- ["configure parsing for prefix comp flag, withcompiler" ~: "failed" ~:
217 -- (Right (ConfigCmd (Just comp, Just "/foo/comp", Just "/usr/local"), []))
218 -- ~=? (parseArgs ["--prefix=/usr/local", "--"++name,
219 -- "--with-compiler=/foo/comp", "configure"])
220 -- | (name, comp) <- m],
222 -- TestLabel "simpler commands" $ TestList
223 -- [flag ~: "failed" ~: (Right (flagCmd, [])) ~=? (parseArgs [flag])
224 -- | (flag, flagCmd) <- [("build", BuildCmd),
225 -- ("install", InstallCmd Nothing False),
226 -- ("sdist", SDistCmd),
227 -- ("register", RegisterCmd False)]
228 -- ]
229 -- ]
231 {- Testing ideas:
232 * IO to look for hugs and hugs-pkg (which hugs, etc)
233 * quickCheck to test permutations of arguments
234 * what other options can we over-ride with a command-line flag?