Merge pull request #10625 from cabalism/fix/project-config-path-haddock
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Haddock.hs
blob6f0459b73110abad4c425317cb756606a6ee7d7a
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.Haddock
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 haddock command-line options.
22 -- See: @Distribution.Simple.Setup@
23 module Distribution.Simple.Setup.Haddock
24 ( HaddockTarget (..)
25 , HaddockFlags
26 ( HaddockCommonFlags
27 , haddockVerbosity
28 , haddockDistPref
29 , haddockCabalFilePath
30 , haddockWorkingDir
31 , haddockTargets
32 , ..
34 , emptyHaddockFlags
35 , defaultHaddockFlags
36 , haddockCommand
37 , Visibility (..)
38 , HaddockProjectFlags (..)
39 , emptyHaddockProjectFlags
40 , defaultHaddockProjectFlags
41 , haddockProjectCommand
42 , haddockOptions
43 , haddockProjectOptions
44 ) where
46 import Distribution.Compat.Prelude hiding (get)
47 import Prelude ()
49 import qualified Distribution.Compat.CharParsing as P
50 import Distribution.Parsec
51 import Distribution.Pretty
52 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
53 import Distribution.Simple.Flag
54 import Distribution.Simple.InstallDirs
55 import Distribution.Simple.Program
56 import Distribution.Simple.Setup.Common
57 import Distribution.Utils.Path
58 import Distribution.Verbosity
60 import qualified Text.PrettyPrint as Disp
62 -- ------------------------------------------------------------
64 -- * Haddock flags
66 -- ------------------------------------------------------------
68 -- | When we build haddock documentation, there are two cases:
70 -- 1. We build haddocks only for the current development version,
71 -- intended for local use and not for distribution. In this case,
72 -- we store the generated documentation in @<dist>/doc/html/<package name>@.
74 -- 2. We build haddocks for intended for uploading them to hackage.
75 -- In this case, we need to follow the layout that hackage expects
76 -- from documentation tarballs, and we might also want to use different
77 -- flags than for development builds, so in this case we store the generated
78 -- documentation in @<dist>/doc/html/<package id>-docs@.
79 data HaddockTarget = ForHackage | ForDevelopment deriving (Eq, Show, Generic, Typeable)
81 instance Binary HaddockTarget
82 instance Structured HaddockTarget
84 instance Pretty HaddockTarget where
85 pretty ForHackage = Disp.text "for-hackage"
86 pretty ForDevelopment = Disp.text "for-development"
88 instance Parsec HaddockTarget where
89 parsec =
90 P.choice
91 [ P.try $ P.string "for-hackage" >> return ForHackage
92 , P.string "for-development" >> return ForDevelopment
95 data HaddockFlags = HaddockFlags
96 { haddockCommonFlags :: !CommonSetupFlags
97 , haddockProgramPaths :: [(String, FilePath)]
98 , haddockProgramArgs :: [(String, [String])]
99 , haddockHoogle :: Flag Bool
100 , haddockHtml :: Flag Bool
101 , haddockHtmlLocation :: Flag String
102 , haddockForHackage :: Flag HaddockTarget
103 , haddockExecutables :: Flag Bool
104 , haddockTestSuites :: Flag Bool
105 , haddockBenchmarks :: Flag Bool
106 , haddockForeignLibs :: Flag Bool
107 , haddockInternal :: Flag Bool
108 , haddockCss :: Flag FilePath
109 , haddockLinkedSource :: Flag Bool
110 , haddockQuickJump :: Flag Bool
111 , haddockHscolourCss :: Flag FilePath
112 , haddockContents :: Flag PathTemplate
113 , haddockIndex :: Flag PathTemplate
114 , haddockBaseUrl :: Flag String
115 , haddockResourcesDir :: Flag String
116 , haddockOutputDir :: Flag FilePath
117 , haddockUseUnicode :: Flag Bool
119 deriving (Show, Generic, Typeable)
121 pattern HaddockCommonFlags
122 :: Flag Verbosity
123 -> Flag (SymbolicPath Pkg (Dir Dist))
124 -> Flag (SymbolicPath CWD (Dir Pkg))
125 -> Flag (SymbolicPath Pkg File)
126 -> [String]
127 -> HaddockFlags
128 pattern HaddockCommonFlags
129 { haddockVerbosity
130 , haddockDistPref
131 , haddockWorkingDir
132 , haddockCabalFilePath
133 , haddockTargets
134 } <-
135 ( haddockCommonFlags ->
136 CommonSetupFlags
137 { setupVerbosity = haddockVerbosity
138 , setupDistPref = haddockDistPref
139 , setupWorkingDir = haddockWorkingDir
140 , setupCabalFilePath = haddockCabalFilePath
141 , setupTargets = haddockTargets
145 instance Binary HaddockFlags
146 instance Structured HaddockFlags
148 defaultHaddockFlags :: HaddockFlags
149 defaultHaddockFlags =
150 HaddockFlags
151 { haddockCommonFlags = defaultCommonSetupFlags
152 , haddockProgramPaths = mempty
153 , haddockProgramArgs = []
154 , haddockHoogle = Flag False
155 , haddockHtml = Flag False
156 , haddockHtmlLocation = NoFlag
157 , haddockForHackage = NoFlag
158 , haddockExecutables = Flag False
159 , haddockTestSuites = Flag False
160 , haddockBenchmarks = Flag False
161 , haddockForeignLibs = Flag False
162 , haddockInternal = Flag False
163 , haddockCss = NoFlag
164 , haddockLinkedSource = Flag False
165 , haddockQuickJump = Flag False
166 , haddockHscolourCss = NoFlag
167 , haddockContents = NoFlag
168 , haddockIndex = NoFlag
169 , haddockBaseUrl = NoFlag
170 , haddockResourcesDir = NoFlag
171 , haddockOutputDir = NoFlag
172 , haddockUseUnicode = Flag False
175 haddockCommand :: CommandUI HaddockFlags
176 haddockCommand =
177 CommandUI
178 { commandName = "haddock"
179 , commandSynopsis = "Generate Haddock HTML documentation."
180 , commandDescription = Just $ \_ ->
181 "Requires the program haddock, version 2.x.\n"
182 , commandNotes = Nothing
183 , commandUsage =
184 usageAlternatives "haddock" $
185 [ "[FLAGS]"
186 , "COMPONENTS [FLAGS]"
188 , commandDefaultFlags = defaultHaddockFlags
189 , commandOptions = \showOrParseArgs ->
190 haddockOptions showOrParseArgs
191 ++ programDbPaths
192 progDb
193 ParseArgs
194 haddockProgramPaths
195 (\v flags -> flags{haddockProgramPaths = v})
196 ++ programDbOption
197 progDb
198 showOrParseArgs
199 haddockProgramArgs
200 (\v fs -> fs{haddockProgramArgs = v})
201 ++ programDbOptions
202 progDb
203 ParseArgs
204 haddockProgramArgs
205 (\v flags -> flags{haddockProgramArgs = v})
207 where
208 progDb =
209 addKnownProgram haddockProgram $
210 addKnownProgram ghcProgram $
211 emptyProgramDb
213 haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
214 haddockOptions showOrParseArgs =
215 withCommonSetupOptions
216 haddockCommonFlags
217 (\c f -> f{haddockCommonFlags = c})
218 showOrParseArgs
219 [ option
221 ["hoogle"]
222 "Generate a hoogle database"
223 haddockHoogle
224 (\v flags -> flags{haddockHoogle = v})
225 trueArg
226 , option
228 ["html"]
229 "Generate HTML documentation (the default)"
230 haddockHtml
231 (\v flags -> flags{haddockHtml = v})
232 trueArg
233 , option
235 ["html-location"]
236 "Location of HTML documentation for pre-requisite packages"
237 haddockHtmlLocation
238 (\v flags -> flags{haddockHtmlLocation = v})
239 (reqArgFlag "URL")
240 , option
242 ["for-hackage"]
243 "Collection of flags to generate documentation suitable for upload to hackage"
244 haddockForHackage
245 (\v flags -> flags{haddockForHackage = v})
246 (noArg (Flag ForHackage))
247 , option
249 ["executables"]
250 "Run haddock for Executables targets"
251 haddockExecutables
252 (\v flags -> flags{haddockExecutables = v})
253 trueArg
254 , option
256 ["tests"]
257 "Run haddock for Test Suite targets"
258 haddockTestSuites
259 (\v flags -> flags{haddockTestSuites = v})
260 trueArg
261 , option
263 ["benchmarks"]
264 "Run haddock for Benchmark targets"
265 haddockBenchmarks
266 (\v flags -> flags{haddockBenchmarks = v})
267 trueArg
268 , option
270 ["foreign-libraries"]
271 "Run haddock for Foreign Library targets"
272 haddockForeignLibs
273 (\v flags -> flags{haddockForeignLibs = v})
274 trueArg
275 , option
277 ["all"]
278 "Run haddock for all targets"
279 ( \f ->
280 allFlags
281 [ haddockExecutables f
282 , haddockTestSuites f
283 , haddockBenchmarks f
284 , haddockForeignLibs f
287 ( \v flags ->
288 flags
289 { haddockExecutables = v
290 , haddockTestSuites = v
291 , haddockBenchmarks = v
292 , haddockForeignLibs = v
295 trueArg
296 , option
298 ["internal"]
299 "Run haddock for internal modules and include all symbols"
300 haddockInternal
301 (\v flags -> flags{haddockInternal = v})
302 trueArg
303 , option
305 ["css"]
306 "Use PATH as the haddock stylesheet"
307 haddockCss
308 (\v flags -> flags{haddockCss = v})
309 (reqArgFlag "PATH")
310 , option
312 ["hyperlink-source", "hyperlink-sources", "hyperlinked-source"]
313 "Hyperlink the documentation to the source code"
314 haddockLinkedSource
315 (\v flags -> flags{haddockLinkedSource = v})
316 trueArg
317 , option
319 ["quickjump"]
320 "Generate an index for interactive documentation navigation"
321 haddockQuickJump
322 (\v flags -> flags{haddockQuickJump = v})
323 trueArg
324 , option
326 ["hscolour-css"]
327 "Use PATH as the HsColour stylesheet"
328 haddockHscolourCss
329 (\v flags -> flags{haddockHscolourCss = v})
330 (reqArgFlag "PATH")
331 , option
333 ["contents-location"]
334 "Bake URL in as the location for the contents page"
335 haddockContents
336 (\v flags -> flags{haddockContents = v})
337 ( reqArg'
338 "URL"
339 (toFlag . toPathTemplate)
340 (flagToList . fmap fromPathTemplate)
342 , option
344 ["index-location"]
345 "Use a separately-generated HTML index"
346 haddockIndex
347 (\v flags -> flags{haddockIndex = v})
348 ( reqArg'
349 "URL"
350 (toFlag . toPathTemplate)
351 (flagToList . fmap fromPathTemplate)
353 , option
355 ["base-url"]
356 "Base URL for static files."
357 haddockBaseUrl
358 (\v flags -> flags{haddockBaseUrl = v})
359 (reqArgFlag "URL")
360 , option
362 ["resources-dir"]
363 "location of Haddocks static / auxiliary files"
364 haddockResourcesDir
365 (\v flags -> flags{haddockResourcesDir = v})
366 (reqArgFlag "DIR")
367 , option
369 ["output-dir"]
370 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
371 haddockOutputDir
372 (\v flags -> flags{haddockOutputDir = v})
373 (reqArgFlag "DIR")
374 , option
376 ["use-unicode"]
377 "Pass --use-unicode option to haddock"
378 haddockUseUnicode
379 (\v flags -> flags{haddockUseUnicode = v})
380 trueArg
383 emptyHaddockFlags :: HaddockFlags
384 emptyHaddockFlags = mempty
386 instance Monoid HaddockFlags where
387 mempty = gmempty
388 mappend = (<>)
390 instance Semigroup HaddockFlags where
391 (<>) = gmappend
393 -- ------------------------------------------------------------
395 -- * HaddocksFlags flags
397 -- ------------------------------------------------------------
399 -- | Governs whether modules from a given interface should be visible or
400 -- hidden in the Haddock generated content page. We don't expose this
401 -- functionality to the user, but simply use 'Visible' for only local packages.
402 -- Visibility of modules is available since @haddock-2.26.1@.
403 data Visibility = Visible | Hidden
404 deriving (Eq, Show)
406 data HaddockProjectFlags = HaddockProjectFlags
407 { haddockProjectCommonFlags :: !CommonSetupFlags
408 , haddockProjectHackage :: Flag Bool
409 -- ^ a shortcut option which builds documentation linked to hackage. It implies:
410 -- * `--html-location='https://hackage.haskell.org/package/$prg-$version/docs'
411 -- * `--quickjump`
412 -- * `--gen-index`
413 -- * `--gen-contents`
414 -- * `--hyperlinked-source`
415 , -- options passed to @haddock@ via 'createHaddockIndex'
416 haddockProjectDir :: Flag String
417 -- ^ output directory of combined haddocks, the default is './haddocks'
418 , haddockProjectPrologue :: Flag String
419 , haddockProjectInterfaces :: Flag [(FilePath, Maybe FilePath, Maybe FilePath, Visibility)]
420 -- ^ 'haddocksInterfaces' is inferred by the 'haddocksAction'; currently not
421 -- exposed to the user.
422 , -- options passed to @haddock@ via 'HaddockFlags' when building
423 -- documentation
425 haddockProjectProgramPaths :: [(String, FilePath)]
426 , haddockProjectProgramArgs :: [(String, [String])]
427 , haddockProjectHoogle :: Flag Bool
428 , -- haddockHtml is not supported
429 haddockProjectHtmlLocation :: Flag String
430 , -- haddockForHackage is not supported
431 haddockProjectExecutables :: Flag Bool
432 , haddockProjectTestSuites :: Flag Bool
433 , haddockProjectBenchmarks :: Flag Bool
434 , haddockProjectForeignLibs :: Flag Bool
435 , haddockProjectInternal :: Flag Bool
436 , haddockProjectCss :: Flag FilePath
437 , haddockProjectHscolourCss :: Flag FilePath
438 , -- haddockContent is not supported, a fixed value is provided
439 -- haddockIndex is not supported, a fixed value is provided
440 -- haddockDistPerf is not supported, note: it changes location of the haddocks
441 -- haddockBaseUrl is not supported, a fixed value is provided
442 haddockProjectResourcesDir :: Flag String
443 , haddockProjectUseUnicode :: Flag Bool
445 deriving (Show, Generic, Typeable)
447 defaultHaddockProjectFlags :: HaddockProjectFlags
448 defaultHaddockProjectFlags =
449 HaddockProjectFlags
450 { haddockProjectCommonFlags = defaultCommonSetupFlags
451 , haddockProjectHackage = Flag False
452 , haddockProjectDir = Flag "./haddocks"
453 , haddockProjectPrologue = NoFlag
454 , haddockProjectTestSuites = Flag False
455 , haddockProjectProgramPaths = mempty
456 , haddockProjectProgramArgs = mempty
457 , haddockProjectHoogle = Flag False
458 , haddockProjectHtmlLocation = NoFlag
459 , haddockProjectExecutables = Flag False
460 , haddockProjectBenchmarks = Flag False
461 , haddockProjectForeignLibs = Flag False
462 , haddockProjectInternal = Flag False
463 , haddockProjectCss = NoFlag
464 , haddockProjectHscolourCss = NoFlag
465 , haddockProjectResourcesDir = NoFlag
466 , haddockProjectInterfaces = NoFlag
467 , haddockProjectUseUnicode = NoFlag
470 haddockProjectCommand :: CommandUI HaddockProjectFlags
471 haddockProjectCommand =
472 CommandUI
473 { commandName = "v2-haddock-project"
474 , commandSynopsis = "Generate Haddocks HTML documentation for the cabal project."
475 , commandDescription = Just $ \_ ->
476 "Requires the program haddock, version 2.26.\n"
477 , commandNotes = Nothing
478 , commandUsage =
479 usageAlternatives "haddock-project" $
480 [ "[FLAGS]"
481 , "COMPONENTS [FLAGS]"
483 , commandDefaultFlags = defaultHaddockProjectFlags
484 , commandOptions = \showOrParseArgs ->
485 haddockProjectOptions showOrParseArgs
486 ++ programDbPaths
487 progDb
488 ParseArgs
489 haddockProjectProgramPaths
490 (\v flags -> flags{haddockProjectProgramPaths = v})
491 ++ programDbOption
492 progDb
493 showOrParseArgs
494 haddockProjectProgramArgs
495 (\v fs -> fs{haddockProjectProgramArgs = v})
496 ++ programDbOptions
497 progDb
498 ParseArgs
499 haddockProjectProgramArgs
500 (\v flags -> flags{haddockProjectProgramArgs = v})
502 where
503 progDb =
504 addKnownProgram haddockProgram $
505 addKnownProgram ghcProgram $
506 emptyProgramDb
508 haddockProjectOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
509 haddockProjectOptions showOrParseArgs =
510 withCommonSetupOptions
511 haddockProjectCommonFlags
512 (\c f -> f{haddockProjectCommonFlags = c})
513 showOrParseArgs
514 [ option
516 ["hackage"]
517 ( concat
518 [ "A short-cut option to build documentation linked to hackage."
521 haddockProjectHackage
522 (\v flags -> flags{haddockProjectHackage = v})
523 trueArg
524 , option
526 ["output"]
527 "Output directory"
528 haddockProjectDir
529 (\v flags -> flags{haddockProjectDir = v})
530 (optArg' "DIRECTORY" maybeToFlag (fmap Just . flagToList))
531 , option
533 ["prologue"]
534 "File path to a prologue file in haddock format"
535 haddockProjectPrologue
536 (\v flags -> flags{haddockProjectPrologue = v})
537 (optArg' "PATH" maybeToFlag (fmap Just . flagToList))
538 , option
540 ["hoogle"]
541 "Generate a hoogle database"
542 haddockProjectHoogle
543 (\v flags -> flags{haddockProjectHoogle = v})
544 trueArg
545 , option
547 ["html-location"]
548 "Location of HTML documentation for pre-requisite packages"
549 haddockProjectHtmlLocation
550 (\v flags -> flags{haddockProjectHtmlLocation = v})
551 (reqArgFlag "URL")
552 , option
554 ["executables"]
555 "Run haddock for Executables targets"
556 haddockProjectExecutables
557 (\v flags -> flags{haddockProjectExecutables = v})
558 trueArg
559 , option
561 ["tests"]
562 "Run haddock for Test Suite targets"
563 haddockProjectTestSuites
564 (\v flags -> flags{haddockProjectTestSuites = v})
565 trueArg
566 , option
568 ["benchmarks"]
569 "Run haddock for Benchmark targets"
570 haddockProjectBenchmarks
571 (\v flags -> flags{haddockProjectBenchmarks = v})
572 trueArg
573 , option
575 ["foreign-libraries"]
576 "Run haddock for Foreign Library targets"
577 haddockProjectForeignLibs
578 (\v flags -> flags{haddockProjectForeignLibs = v})
579 trueArg
580 , option
582 ["all", "haddock-all"]
583 "Run haddock for all targets"
584 ( \f ->
585 allFlags
586 [ haddockProjectExecutables f
587 , haddockProjectTestSuites f
588 , haddockProjectBenchmarks f
589 , haddockProjectForeignLibs f
592 ( \v flags ->
593 flags
594 { haddockProjectExecutables = v
595 , haddockProjectTestSuites = v
596 , haddockProjectBenchmarks = v
597 , haddockProjectForeignLibs = v
600 trueArg
601 , option
603 ["internal"]
604 "Run haddock for internal modules and include all symbols"
605 haddockProjectInternal
606 (\v flags -> flags{haddockProjectInternal = v})
607 trueArg
608 , option
610 ["css"]
611 "Use PATH as the haddock stylesheet"
612 haddockProjectCss
613 (\v flags -> flags{haddockProjectCss = v})
614 (reqArgFlag "PATH")
615 , option
617 ["hscolour-css"]
618 "Use PATH as the HsColour stylesheet"
619 haddockProjectHscolourCss
620 (\v flags -> flags{haddockProjectHscolourCss = v})
621 (reqArgFlag "PATH")
622 , option
624 ["resources-dir"]
625 "location of Haddocks static / auxiliary files"
626 haddockProjectResourcesDir
627 (\v flags -> flags{haddockProjectResourcesDir = v})
628 (reqArgFlag "DIR")
629 , option
631 ["use-unicode"]
632 "Pass --use-unicode option to haddock"
633 haddockProjectUseUnicode
634 (\v flags -> flags{haddockProjectUseUnicode = v})
635 trueArg
638 emptyHaddockProjectFlags :: HaddockProjectFlags
639 emptyHaddockProjectFlags = mempty
641 instance Monoid HaddockProjectFlags where
642 mempty = gmempty
643 mappend = (<>)
645 instance Semigroup HaddockProjectFlags where
646 (<>) = gmappend