Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Haddock.hs
blob3efc6640bd2e3d88d03e7d8106f61463978c84de
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.Setup.Haddock
11 -- Copyright : Isaac Jones 2003-2004
12 -- Duncan Coutts 2007
13 -- License : BSD3
15 -- Maintainer : cabal-devel@haskell.org
16 -- Portability : portable
18 -- Definition of the haddock command-line options.
19 -- See: @Distribution.Simple.Setup@
20 module Distribution.Simple.Setup.Haddock
21 ( HaddockTarget (..)
22 , HaddockFlags (..)
23 , emptyHaddockFlags
24 , defaultHaddockFlags
25 , haddockCommand
26 , Visibility (..)
27 , HaddockProjectFlags (..)
28 , emptyHaddockProjectFlags
29 , defaultHaddockProjectFlags
30 , haddockProjectCommand
31 , haddockOptions
32 , haddockProjectOptions
33 ) where
35 import Distribution.Compat.Prelude hiding (get)
36 import Prelude ()
38 import qualified Distribution.Compat.CharParsing as P
39 import Distribution.Parsec
40 import Distribution.Pretty
41 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
42 import Distribution.Simple.Flag
43 import Distribution.Simple.InstallDirs
44 import Distribution.Simple.Program
45 import Distribution.Verbosity
46 import qualified Text.PrettyPrint as Disp
48 import Distribution.Simple.Setup.Common
50 -- ------------------------------------------------------------
52 -- * Haddock flags
54 -- ------------------------------------------------------------
56 -- | When we build haddock documentation, there are two cases:
58 -- 1. We build haddocks only for the current development version,
59 -- intended for local use and not for distribution. In this case,
60 -- we store the generated documentation in @<dist>/doc/html/<package name>@.
62 -- 2. We build haddocks for intended for uploading them to hackage.
63 -- In this case, we need to follow the layout that hackage expects
64 -- from documentation tarballs, and we might also want to use different
65 -- flags than for development builds, so in this case we store the generated
66 -- documentation in @<dist>/doc/html/<package id>-docs@.
67 data HaddockTarget = ForHackage | ForDevelopment deriving (Eq, Show, Generic, Typeable)
69 instance Binary HaddockTarget
70 instance Structured HaddockTarget
72 instance Pretty HaddockTarget where
73 pretty ForHackage = Disp.text "for-hackage"
74 pretty ForDevelopment = Disp.text "for-development"
76 instance Parsec HaddockTarget where
77 parsec =
78 P.choice
79 [ P.try $ P.string "for-hackage" >> return ForHackage
80 , P.string "for-development" >> return ForDevelopment
83 data HaddockFlags = HaddockFlags
84 { haddockProgramPaths :: [(String, FilePath)]
85 , haddockProgramArgs :: [(String, [String])]
86 , haddockHoogle :: Flag Bool
87 , haddockHtml :: Flag Bool
88 , haddockHtmlLocation :: Flag String
89 , haddockForHackage :: Flag HaddockTarget
90 , haddockExecutables :: Flag Bool
91 , haddockTestSuites :: Flag Bool
92 , haddockBenchmarks :: Flag Bool
93 , haddockForeignLibs :: Flag Bool
94 , haddockInternal :: Flag Bool
95 , haddockCss :: Flag FilePath
96 , haddockLinkedSource :: Flag Bool
97 , haddockQuickJump :: Flag Bool
98 , haddockHscolourCss :: Flag FilePath
99 , haddockContents :: Flag PathTemplate
100 , haddockIndex :: Flag PathTemplate
101 , haddockDistPref :: Flag FilePath
102 , haddockKeepTempFiles :: Flag Bool
103 , haddockVerbosity :: Flag Verbosity
104 , haddockCabalFilePath :: Flag FilePath
105 , haddockBaseUrl :: Flag String
106 , haddockLib :: Flag String
107 , haddockOutputDir :: Flag FilePath
108 , haddockArgs :: [String]
110 deriving (Show, Generic, Typeable)
112 defaultHaddockFlags :: HaddockFlags
113 defaultHaddockFlags =
114 HaddockFlags
115 { haddockProgramPaths = mempty
116 , haddockProgramArgs = []
117 , haddockHoogle = Flag False
118 , haddockHtml = Flag False
119 , haddockHtmlLocation = NoFlag
120 , haddockForHackage = NoFlag
121 , haddockExecutables = Flag False
122 , haddockTestSuites = Flag False
123 , haddockBenchmarks = Flag False
124 , haddockForeignLibs = Flag False
125 , haddockInternal = Flag False
126 , haddockCss = NoFlag
127 , haddockLinkedSource = Flag False
128 , haddockQuickJump = Flag False
129 , haddockHscolourCss = NoFlag
130 , haddockContents = NoFlag
131 , haddockDistPref = NoFlag
132 , haddockKeepTempFiles = Flag False
133 , haddockVerbosity = Flag normal
134 , haddockCabalFilePath = mempty
135 , haddockIndex = NoFlag
136 , haddockBaseUrl = NoFlag
137 , haddockLib = NoFlag
138 , haddockOutputDir = NoFlag
139 , haddockArgs = mempty
142 haddockCommand :: CommandUI HaddockFlags
143 haddockCommand =
144 CommandUI
145 { commandName = "haddock"
146 , commandSynopsis = "Generate Haddock HTML documentation."
147 , commandDescription = Just $ \_ ->
148 "Requires the program haddock, version 2.x.\n"
149 , commandNotes = Nothing
150 , commandUsage =
151 usageAlternatives "haddock" $
152 [ "[FLAGS]"
153 , "COMPONENTS [FLAGS]"
155 , commandDefaultFlags = defaultHaddockFlags
156 , commandOptions = \showOrParseArgs ->
157 haddockOptions showOrParseArgs
158 ++ programDbPaths
159 progDb
160 ParseArgs
161 haddockProgramPaths
162 (\v flags -> flags{haddockProgramPaths = v})
163 ++ programDbOption
164 progDb
165 showOrParseArgs
166 haddockProgramArgs
167 (\v fs -> fs{haddockProgramArgs = v})
168 ++ programDbOptions
169 progDb
170 ParseArgs
171 haddockProgramArgs
172 (\v flags -> flags{haddockProgramArgs = v})
174 where
175 progDb =
176 addKnownProgram haddockProgram $
177 addKnownProgram ghcProgram $
178 emptyProgramDb
180 haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
181 haddockOptions showOrParseArgs =
182 [ optionVerbosity
183 haddockVerbosity
184 (\v flags -> flags{haddockVerbosity = v})
185 , optionDistPref
186 haddockDistPref
187 (\d flags -> flags{haddockDistPref = d})
188 showOrParseArgs
189 , option
191 ["keep-temp-files"]
192 "Keep temporary files"
193 haddockKeepTempFiles
194 (\b flags -> flags{haddockKeepTempFiles = b})
195 trueArg
196 , option
198 ["hoogle"]
199 "Generate a hoogle database"
200 haddockHoogle
201 (\v flags -> flags{haddockHoogle = v})
202 trueArg
203 , option
205 ["html"]
206 "Generate HTML documentation (the default)"
207 haddockHtml
208 (\v flags -> flags{haddockHtml = v})
209 trueArg
210 , option
212 ["html-location"]
213 "Location of HTML documentation for pre-requisite packages"
214 haddockHtmlLocation
215 (\v flags -> flags{haddockHtmlLocation = v})
216 (reqArgFlag "URL")
217 , option
219 ["for-hackage"]
220 "Collection of flags to generate documentation suitable for upload to hackage"
221 haddockForHackage
222 (\v flags -> flags{haddockForHackage = v})
223 (noArg (Flag ForHackage))
224 , option
226 ["executables"]
227 "Run haddock for Executables targets"
228 haddockExecutables
229 (\v flags -> flags{haddockExecutables = v})
230 trueArg
231 , option
233 ["tests"]
234 "Run haddock for Test Suite targets"
235 haddockTestSuites
236 (\v flags -> flags{haddockTestSuites = v})
237 trueArg
238 , option
240 ["benchmarks"]
241 "Run haddock for Benchmark targets"
242 haddockBenchmarks
243 (\v flags -> flags{haddockBenchmarks = v})
244 trueArg
245 , option
247 ["foreign-libraries"]
248 "Run haddock for Foreign Library targets"
249 haddockForeignLibs
250 (\v flags -> flags{haddockForeignLibs = v})
251 trueArg
252 , option
254 ["all"]
255 "Run haddock for all targets"
256 ( \f ->
257 allFlags
258 [ haddockExecutables f
259 , haddockTestSuites f
260 , haddockBenchmarks f
261 , haddockForeignLibs f
264 ( \v flags ->
265 flags
266 { haddockExecutables = v
267 , haddockTestSuites = v
268 , haddockBenchmarks = v
269 , haddockForeignLibs = v
272 trueArg
273 , option
275 ["internal"]
276 "Run haddock for internal modules and include all symbols"
277 haddockInternal
278 (\v flags -> flags{haddockInternal = v})
279 trueArg
280 , option
282 ["css"]
283 "Use PATH as the haddock stylesheet"
284 haddockCss
285 (\v flags -> flags{haddockCss = v})
286 (reqArgFlag "PATH")
287 , option
289 ["hyperlink-source", "hyperlink-sources", "hyperlinked-source"]
290 "Hyperlink the documentation to the source code"
291 haddockLinkedSource
292 (\v flags -> flags{haddockLinkedSource = v})
293 trueArg
294 , option
296 ["quickjump"]
297 "Generate an index for interactive documentation navigation"
298 haddockQuickJump
299 (\v flags -> flags{haddockQuickJump = v})
300 trueArg
301 , option
303 ["hscolour-css"]
304 "Use PATH as the HsColour stylesheet"
305 haddockHscolourCss
306 (\v flags -> flags{haddockHscolourCss = v})
307 (reqArgFlag "PATH")
308 , option
310 ["contents-location"]
311 "Bake URL in as the location for the contents page"
312 haddockContents
313 (\v flags -> flags{haddockContents = v})
314 ( reqArg'
315 "URL"
316 (toFlag . toPathTemplate)
317 (flagToList . fmap fromPathTemplate)
319 , option
321 ["index-location"]
322 "Use a separately-generated HTML index"
323 haddockIndex
324 (\v flags -> flags{haddockIndex = v})
325 ( reqArg'
326 "URL"
327 (toFlag . toPathTemplate)
328 (flagToList . fmap fromPathTemplate)
330 , option
332 ["base-url"]
333 "Base URL for static files."
334 haddockBaseUrl
335 (\v flags -> flags{haddockBaseUrl = v})
336 (reqArgFlag "URL")
337 , option
339 ["lib"]
340 "location of Haddocks static / auxiliary files"
341 haddockLib
342 (\v flags -> flags{haddockLib = v})
343 (reqArgFlag "DIR")
344 , option
346 ["output-dir"]
347 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
348 haddockOutputDir
349 (\v flags -> flags{haddockOutputDir = v})
350 (reqArgFlag "DIR")
353 emptyHaddockFlags :: HaddockFlags
354 emptyHaddockFlags = mempty
356 instance Monoid HaddockFlags where
357 mempty = gmempty
358 mappend = (<>)
360 instance Semigroup HaddockFlags where
361 (<>) = gmappend
363 -- ------------------------------------------------------------
365 -- * HaddocksFlags flags
367 -- ------------------------------------------------------------
369 -- | Governs whether modules from a given interface should be visible or
370 -- hidden in the Haddock generated content page. We don't expose this
371 -- functionality to the user, but simply use 'Visible' for only local packages.
372 -- Visibility of modules is available since @haddock-2.26.1@.
373 data Visibility = Visible | Hidden
374 deriving (Eq, Show)
376 data HaddockProjectFlags = HaddockProjectFlags
377 { haddockProjectHackage :: Flag Bool
378 -- ^ a shortcut option which builds documentation linked to hackage. It implies:
379 -- * `--html-location='https://hackage.haskell.org/package/$prg-$version/docs'
380 -- * `--quickjump`
381 -- * `--gen-index`
382 -- * `--gen-contents`
383 -- * `--hyperlinked-source`
384 , -- options passed to @haddock@ via 'createHaddockIndex'
385 haddockProjectDir :: Flag String
386 -- ^ output directory of combined haddocks, the default is './haddocks'
387 , haddockProjectPrologue :: Flag String
388 , haddockProjectInterfaces :: Flag [(FilePath, Maybe FilePath, Maybe FilePath, Visibility)]
389 -- ^ 'haddocksInterfaces' is inferred by the 'haddocksAction'; currently not
390 -- exposed to the user.
391 , -- options passed to @haddock@ via 'HaddockFlags' when building
392 -- documentation
394 haddockProjectProgramPaths :: [(String, FilePath)]
395 , haddockProjectProgramArgs :: [(String, [String])]
396 , haddockProjectHoogle :: Flag Bool
397 , -- haddockHtml is not supported
398 haddockProjectHtmlLocation :: Flag String
399 , -- haddockForHackage is not supported
400 haddockProjectExecutables :: Flag Bool
401 , haddockProjectTestSuites :: Flag Bool
402 , haddockProjectBenchmarks :: Flag Bool
403 , haddockProjectForeignLibs :: Flag Bool
404 , haddockProjectInternal :: Flag Bool
405 , haddockProjectCss :: Flag FilePath
406 , haddockProjectHscolourCss :: Flag FilePath
407 , -- haddockContent is not supported, a fixed value is provided
408 -- haddockIndex is not supported, a fixed value is provided
409 -- haddockDistPerf is not supported, note: it changes location of the haddocks
410 haddockProjectKeepTempFiles :: Flag Bool
411 , haddockProjectVerbosity :: Flag Verbosity
412 , -- haddockBaseUrl is not supported, a fixed value is provided
413 haddockProjectLib :: Flag String
414 , haddockProjectOutputDir :: Flag FilePath
416 deriving (Show, Generic, Typeable)
418 defaultHaddockProjectFlags :: HaddockProjectFlags
419 defaultHaddockProjectFlags =
420 HaddockProjectFlags
421 { haddockProjectHackage = Flag False
422 , haddockProjectDir = Flag "./haddocks"
423 , haddockProjectPrologue = NoFlag
424 , haddockProjectTestSuites = Flag False
425 , haddockProjectProgramPaths = mempty
426 , haddockProjectProgramArgs = mempty
427 , haddockProjectHoogle = Flag False
428 , haddockProjectHtmlLocation = NoFlag
429 , haddockProjectExecutables = Flag False
430 , haddockProjectBenchmarks = Flag False
431 , haddockProjectForeignLibs = Flag False
432 , haddockProjectInternal = Flag False
433 , haddockProjectCss = NoFlag
434 , haddockProjectHscolourCss = NoFlag
435 , haddockProjectKeepTempFiles = Flag False
436 , haddockProjectVerbosity = Flag normal
437 , haddockProjectLib = NoFlag
438 , haddockProjectOutputDir = NoFlag
439 , haddockProjectInterfaces = NoFlag
442 haddockProjectCommand :: CommandUI HaddockProjectFlags
443 haddockProjectCommand =
444 CommandUI
445 { commandName = "v2-haddock-project"
446 , commandSynopsis = "Generate Haddocks HTML documentation for the cabal project."
447 , commandDescription = Just $ \_ ->
448 "Require the programm haddock, version 2.26.\n"
449 , commandNotes = Nothing
450 , commandUsage =
451 usageAlternatives "haddocks" $
452 [ "[FLAGS]"
453 , "COMPONENTS [FLAGS]"
455 , commandDefaultFlags = defaultHaddockProjectFlags
456 , commandOptions = \showOrParseArgs ->
457 haddockProjectOptions showOrParseArgs
458 ++ programDbPaths
459 progDb
460 ParseArgs
461 haddockProjectProgramPaths
462 (\v flags -> flags{haddockProjectProgramPaths = v})
463 ++ programDbOption
464 progDb
465 showOrParseArgs
466 haddockProjectProgramArgs
467 (\v fs -> fs{haddockProjectProgramArgs = v})
468 ++ programDbOptions
469 progDb
470 ParseArgs
471 haddockProjectProgramArgs
472 (\v flags -> flags{haddockProjectProgramArgs = v})
474 where
475 progDb =
476 addKnownProgram haddockProgram $
477 addKnownProgram ghcProgram $
478 emptyProgramDb
480 haddockProjectOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
481 haddockProjectOptions _showOrParseArgs =
482 [ option
484 ["hackage"]
485 ( concat
486 [ "A short-cut option to build documentation linked to hackage."
489 haddockProjectHackage
490 (\v flags -> flags{haddockProjectHackage = v})
491 trueArg
492 , option
494 ["output"]
495 "Output directory"
496 haddockProjectDir
497 (\v flags -> flags{haddockProjectDir = v})
498 (optArg' "DIRECTORY" maybeToFlag (fmap Just . flagToList))
499 , option
501 ["prologue"]
502 "File path to a prologue file in haddock format"
503 haddockProjectPrologue
504 (\v flags -> flags{haddockProjectPrologue = v})
505 (optArg' "PATH" maybeToFlag (fmap Just . flagToList))
506 , option
508 ["hoogle"]
509 "Generate a hoogle database"
510 haddockProjectHoogle
511 (\v flags -> flags{haddockProjectHoogle = v})
512 trueArg
513 , option
515 ["html-location"]
516 "Location of HTML documentation for pre-requisite packages"
517 haddockProjectHtmlLocation
518 (\v flags -> flags{haddockProjectHtmlLocation = v})
519 (reqArgFlag "URL")
520 , option
522 ["executables"]
523 "Run haddock for Executables targets"
524 haddockProjectExecutables
525 (\v flags -> flags{haddockProjectExecutables = v})
526 trueArg
527 , option
529 ["tests"]
530 "Run haddock for Test Suite targets"
531 haddockProjectTestSuites
532 (\v flags -> flags{haddockProjectTestSuites = v})
533 trueArg
534 , option
536 ["benchmarks"]
537 "Run haddock for Benchmark targets"
538 haddockProjectBenchmarks
539 (\v flags -> flags{haddockProjectBenchmarks = v})
540 trueArg
541 , option
543 ["foreign-libraries"]
544 "Run haddock for Foreign Library targets"
545 haddockProjectForeignLibs
546 (\v flags -> flags{haddockProjectForeignLibs = v})
547 trueArg
548 , option
550 ["internal"]
551 "Run haddock for internal modules and include all symbols"
552 haddockProjectInternal
553 (\v flags -> flags{haddockProjectInternal = v})
554 trueArg
555 , option
557 ["css"]
558 "Use PATH as the haddock stylesheet"
559 haddockProjectCss
560 (\v flags -> flags{haddockProjectCss = v})
561 (reqArgFlag "PATH")
562 , option
564 ["hscolour-css"]
565 "Use PATH as the HsColour stylesheet"
566 haddockProjectHscolourCss
567 (\v flags -> flags{haddockProjectHscolourCss = v})
568 (reqArgFlag "PATH")
569 , option
571 ["keep-temp-files"]
572 "Keep temporary files"
573 haddockProjectKeepTempFiles
574 (\b flags -> flags{haddockProjectKeepTempFiles = b})
575 trueArg
576 , optionVerbosity
577 haddockProjectVerbosity
578 (\v flags -> flags{haddockProjectVerbosity = v})
579 , option
581 ["lib"]
582 "location of Haddocks static / auxiliary files"
583 haddockProjectLib
584 (\v flags -> flags{haddockProjectLib = v})
585 (reqArgFlag "DIR")
586 , option
588 ["output-dir"]
589 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
590 haddockProjectOutputDir
591 (\v flags -> flags{haddockProjectOutputDir = v})
592 (reqArgFlag "DIR")
595 emptyHaddockProjectFlags :: HaddockProjectFlags
596 emptyHaddockProjectFlags = mempty
598 instance Monoid HaddockProjectFlags where
599 mempty = gmempty
600 mappend = (<>)
602 instance Semigroup HaddockProjectFlags where
603 (<>) = gmappend