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