2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE DeriveDataTypeable #-}
4 {-# LANGUAGE DeriveGeneric #-}
5 {-# LANGUAGE FlexibleContexts #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE RankNTypes #-}
8 {-# LANGUAGE ViewPatterns #-}
10 -----------------------------------------------------------------------------
13 -- Module : Distribution.Simple.Setup.Haddock
14 -- Copyright : Isaac Jones 2003-2004
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
29 , haddockCabalFilePath
38 , HaddockProjectFlags
(..)
39 , emptyHaddockProjectFlags
40 , defaultHaddockProjectFlags
41 , haddockProjectCommand
43 , haddockProjectOptions
46 import Distribution
.Compat
.Prelude
hiding (get
)
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 -- ------------------------------------------------------------
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
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
123 -> Flag
(SymbolicPath Pkg
(Dir Dist
))
124 -> Flag
(SymbolicPath CWD
(Dir Pkg
))
125 -> Flag
(SymbolicPath Pkg File
)
128 pattern HaddockCommonFlags
132 , haddockCabalFilePath
135 ( haddockCommonFlags
->
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
=
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
178 { commandName
= "haddock"
179 , commandSynopsis
= "Generate Haddock HTML documentation."
180 , commandDescription
= Just
$ \_
->
181 "Requires the program haddock, version 2.x.\n"
182 , commandNotes
= Nothing
184 usageAlternatives
"haddock" $
186 , "COMPONENTS [FLAGS]"
188 , commandDefaultFlags
= defaultHaddockFlags
189 , commandOptions
= \showOrParseArgs
->
190 haddockOptions showOrParseArgs
195 (\v flags
-> flags
{haddockProgramPaths
= v
})
200 (\v fs
-> fs
{haddockProgramArgs
= v
})
205 (\v flags
-> flags
{haddockProgramArgs
= v
})
209 addKnownProgram haddockProgram
$
210 addKnownProgram ghcProgram
$
213 haddockOptions
:: ShowOrParseArgs
-> [OptionField HaddockFlags
]
214 haddockOptions showOrParseArgs
=
215 withCommonSetupOptions
217 (\c f
-> f
{haddockCommonFlags
= c
})
222 "Generate a hoogle database"
224 (\v flags
-> flags
{haddockHoogle
= v
})
229 "Generate HTML documentation (the default)"
231 (\v flags
-> flags
{haddockHtml
= v
})
236 "Location of HTML documentation for pre-requisite packages"
238 (\v flags
-> flags
{haddockHtmlLocation
= v
})
243 "Collection of flags to generate documentation suitable for upload to hackage"
245 (\v flags
-> flags
{haddockForHackage
= v
})
246 (noArg
(Flag ForHackage
))
250 "Run haddock for Executables targets"
252 (\v flags
-> flags
{haddockExecutables
= v
})
257 "Run haddock for Test Suite targets"
259 (\v flags
-> flags
{haddockTestSuites
= v
})
264 "Run haddock for Benchmark targets"
266 (\v flags
-> flags
{haddockBenchmarks
= v
})
270 ["foreign-libraries"]
271 "Run haddock for Foreign Library targets"
273 (\v flags
-> flags
{haddockForeignLibs
= v
})
278 "Run haddock for all targets"
281 [ haddockExecutables f
282 , haddockTestSuites f
283 , haddockBenchmarks f
284 , haddockForeignLibs f
289 { haddockExecutables
= v
290 , haddockTestSuites
= v
291 , haddockBenchmarks
= v
292 , haddockForeignLibs
= v
299 "Run haddock for internal modules and include all symbols"
301 (\v flags
-> flags
{haddockInternal
= v
})
306 "Use PATH as the haddock stylesheet"
308 (\v flags
-> flags
{haddockCss
= v
})
312 ["hyperlink-source", "hyperlink-sources", "hyperlinked-source"]
313 "Hyperlink the documentation to the source code"
315 (\v flags
-> flags
{haddockLinkedSource
= v
})
320 "Generate an index for interactive documentation navigation"
322 (\v flags
-> flags
{haddockQuickJump
= v
})
327 "Use PATH as the HsColour stylesheet"
329 (\v flags
-> flags
{haddockHscolourCss
= v
})
333 ["contents-location"]
334 "Bake URL in as the location for the contents page"
336 (\v flags
-> flags
{haddockContents
= v
})
339 (toFlag
. toPathTemplate
)
340 (flagToList
. fmap fromPathTemplate
)
345 "Use a separately-generated HTML index"
347 (\v flags
-> flags
{haddockIndex
= v
})
350 (toFlag
. toPathTemplate
)
351 (flagToList
. fmap fromPathTemplate
)
356 "Base URL for static files."
358 (\v flags
-> flags
{haddockBaseUrl
= v
})
363 "location of Haddocks static / auxiliary files"
365 (\v flags
-> flags
{haddockResourcesDir
= v
})
370 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
372 (\v flags
-> flags
{haddockOutputDir
= v
})
377 "Pass --use-unicode option to haddock"
379 (\v flags
-> flags
{haddockUseUnicode
= v
})
383 emptyHaddockFlags
:: HaddockFlags
384 emptyHaddockFlags
= mempty
386 instance Monoid HaddockFlags
where
390 instance Semigroup HaddockFlags
where
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
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'
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
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
=
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
=
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
479 usageAlternatives
"haddock-project" $
481 , "COMPONENTS [FLAGS]"
483 , commandDefaultFlags
= defaultHaddockProjectFlags
484 , commandOptions
= \showOrParseArgs
->
485 haddockProjectOptions showOrParseArgs
489 haddockProjectProgramPaths
490 (\v flags
-> flags
{haddockProjectProgramPaths
= v
})
494 haddockProjectProgramArgs
495 (\v fs
-> fs
{haddockProjectProgramArgs
= v
})
499 haddockProjectProgramArgs
500 (\v flags
-> flags
{haddockProjectProgramArgs
= v
})
504 addKnownProgram haddockProgram
$
505 addKnownProgram ghcProgram
$
508 haddockProjectOptions
:: ShowOrParseArgs
-> [OptionField HaddockProjectFlags
]
509 haddockProjectOptions showOrParseArgs
=
510 withCommonSetupOptions
511 haddockProjectCommonFlags
512 (\c f
-> f
{haddockProjectCommonFlags
= c
})
518 [ "A short-cut option to build documentation linked to hackage."
521 haddockProjectHackage
522 (\v flags
-> flags
{haddockProjectHackage
= v
})
529 (\v flags
-> flags
{haddockProjectDir
= v
})
530 (optArg
' "DIRECTORY" maybeToFlag
(fmap Just
. flagToList
))
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
))
541 "Generate a hoogle database"
543 (\v flags
-> flags
{haddockProjectHoogle
= v
})
548 "Location of HTML documentation for pre-requisite packages"
549 haddockProjectHtmlLocation
550 (\v flags
-> flags
{haddockProjectHtmlLocation
= v
})
555 "Run haddock for Executables targets"
556 haddockProjectExecutables
557 (\v flags
-> flags
{haddockProjectExecutables
= v
})
562 "Run haddock for Test Suite targets"
563 haddockProjectTestSuites
564 (\v flags
-> flags
{haddockProjectTestSuites
= v
})
569 "Run haddock for Benchmark targets"
570 haddockProjectBenchmarks
571 (\v flags
-> flags
{haddockProjectBenchmarks
= v
})
575 ["foreign-libraries"]
576 "Run haddock for Foreign Library targets"
577 haddockProjectForeignLibs
578 (\v flags
-> flags
{haddockProjectForeignLibs
= v
})
582 ["all", "haddock-all"]
583 "Run haddock for all targets"
586 [ haddockProjectExecutables f
587 , haddockProjectTestSuites f
588 , haddockProjectBenchmarks f
589 , haddockProjectForeignLibs f
594 { haddockProjectExecutables
= v
595 , haddockProjectTestSuites
= v
596 , haddockProjectBenchmarks
= v
597 , haddockProjectForeignLibs
= v
604 "Run haddock for internal modules and include all symbols"
605 haddockProjectInternal
606 (\v flags
-> flags
{haddockProjectInternal
= v
})
611 "Use PATH as the haddock stylesheet"
613 (\v flags
-> flags
{haddockProjectCss
= v
})
618 "Use PATH as the HsColour stylesheet"
619 haddockProjectHscolourCss
620 (\v flags
-> flags
{haddockProjectHscolourCss
= v
})
625 "location of Haddocks static / auxiliary files"
626 haddockProjectResourcesDir
627 (\v flags
-> flags
{haddockProjectResourcesDir
= v
})
632 "Pass --use-unicode option to haddock"
633 haddockProjectUseUnicode
634 (\v flags
-> flags
{haddockProjectUseUnicode
= v
})
638 emptyHaddockProjectFlags
:: HaddockProjectFlags
639 emptyHaddockProjectFlags
= mempty
641 instance Monoid HaddockProjectFlags
where
645 instance Semigroup HaddockProjectFlags
where