2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
10 -- Module : Distribution.Simple.Setup.Haddock
11 -- Copyright : Isaac Jones 2003-2004
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
27 , HaddockProjectFlags
(..)
28 , emptyHaddockProjectFlags
29 , defaultHaddockProjectFlags
30 , haddockProjectCommand
32 , haddockProjectOptions
35 import Distribution
.Compat
.Prelude
hiding (get
)
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 -- ------------------------------------------------------------
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
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 instance Binary HaddockFlags
113 instance Structured HaddockFlags
115 defaultHaddockFlags
:: HaddockFlags
116 defaultHaddockFlags
=
118 { haddockProgramPaths
= mempty
119 , haddockProgramArgs
= []
120 , haddockHoogle
= Flag
False
121 , haddockHtml
= Flag
False
122 , haddockHtmlLocation
= NoFlag
123 , haddockForHackage
= NoFlag
124 , haddockExecutables
= Flag
False
125 , haddockTestSuites
= Flag
False
126 , haddockBenchmarks
= Flag
False
127 , haddockForeignLibs
= Flag
False
128 , haddockInternal
= Flag
False
129 , haddockCss
= NoFlag
130 , haddockLinkedSource
= Flag
False
131 , haddockQuickJump
= Flag
False
132 , haddockHscolourCss
= NoFlag
133 , haddockContents
= NoFlag
134 , haddockDistPref
= NoFlag
135 , haddockKeepTempFiles
= Flag
False
136 , haddockVerbosity
= Flag normal
137 , haddockCabalFilePath
= mempty
138 , haddockIndex
= NoFlag
139 , haddockBaseUrl
= NoFlag
140 , haddockLib
= NoFlag
141 , haddockOutputDir
= NoFlag
142 , haddockArgs
= mempty
145 haddockCommand
:: CommandUI HaddockFlags
148 { commandName
= "haddock"
149 , commandSynopsis
= "Generate Haddock HTML documentation."
150 , commandDescription
= Just
$ \_
->
151 "Requires the program haddock, version 2.x.\n"
152 , commandNotes
= Nothing
154 usageAlternatives
"haddock" $
156 , "COMPONENTS [FLAGS]"
158 , commandDefaultFlags
= defaultHaddockFlags
159 , commandOptions
= \showOrParseArgs
->
160 haddockOptions showOrParseArgs
165 (\v flags
-> flags
{haddockProgramPaths
= v
})
170 (\v fs
-> fs
{haddockProgramArgs
= v
})
175 (\v flags
-> flags
{haddockProgramArgs
= v
})
179 addKnownProgram haddockProgram
$
180 addKnownProgram ghcProgram
$
183 haddockOptions
:: ShowOrParseArgs
-> [OptionField HaddockFlags
]
184 haddockOptions showOrParseArgs
=
187 (\v flags
-> flags
{haddockVerbosity
= v
})
190 (\d flags
-> flags
{haddockDistPref
= d
})
195 "Keep temporary files"
197 (\b flags
-> flags
{haddockKeepTempFiles
= b
})
202 "Generate a hoogle database"
204 (\v flags
-> flags
{haddockHoogle
= v
})
209 "Generate HTML documentation (the default)"
211 (\v flags
-> flags
{haddockHtml
= v
})
216 "Location of HTML documentation for pre-requisite packages"
218 (\v flags
-> flags
{haddockHtmlLocation
= v
})
223 "Collection of flags to generate documentation suitable for upload to hackage"
225 (\v flags
-> flags
{haddockForHackage
= v
})
226 (noArg
(Flag ForHackage
))
230 "Run haddock for Executables targets"
232 (\v flags
-> flags
{haddockExecutables
= v
})
237 "Run haddock for Test Suite targets"
239 (\v flags
-> flags
{haddockTestSuites
= v
})
244 "Run haddock for Benchmark targets"
246 (\v flags
-> flags
{haddockBenchmarks
= v
})
250 ["foreign-libraries"]
251 "Run haddock for Foreign Library targets"
253 (\v flags
-> flags
{haddockForeignLibs
= v
})
258 "Run haddock for all targets"
261 [ haddockExecutables f
262 , haddockTestSuites f
263 , haddockBenchmarks f
264 , haddockForeignLibs f
269 { haddockExecutables
= v
270 , haddockTestSuites
= v
271 , haddockBenchmarks
= v
272 , haddockForeignLibs
= v
279 "Run haddock for internal modules and include all symbols"
281 (\v flags
-> flags
{haddockInternal
= v
})
286 "Use PATH as the haddock stylesheet"
288 (\v flags
-> flags
{haddockCss
= v
})
292 ["hyperlink-source", "hyperlink-sources", "hyperlinked-source"]
293 "Hyperlink the documentation to the source code"
295 (\v flags
-> flags
{haddockLinkedSource
= v
})
300 "Generate an index for interactive documentation navigation"
302 (\v flags
-> flags
{haddockQuickJump
= v
})
307 "Use PATH as the HsColour stylesheet"
309 (\v flags
-> flags
{haddockHscolourCss
= v
})
313 ["contents-location"]
314 "Bake URL in as the location for the contents page"
316 (\v flags
-> flags
{haddockContents
= v
})
319 (toFlag
. toPathTemplate
)
320 (flagToList
. fmap fromPathTemplate
)
325 "Use a separately-generated HTML index"
327 (\v flags
-> flags
{haddockIndex
= v
})
330 (toFlag
. toPathTemplate
)
331 (flagToList
. fmap fromPathTemplate
)
336 "Base URL for static files."
338 (\v flags
-> flags
{haddockBaseUrl
= v
})
343 "location of Haddocks static / auxiliary files"
345 (\v flags
-> flags
{haddockLib
= v
})
350 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
352 (\v flags
-> flags
{haddockOutputDir
= v
})
356 emptyHaddockFlags
:: HaddockFlags
357 emptyHaddockFlags
= mempty
359 instance Monoid HaddockFlags
where
363 instance Semigroup HaddockFlags
where
366 -- ------------------------------------------------------------
368 -- * HaddocksFlags flags
370 -- ------------------------------------------------------------
372 -- | Governs whether modules from a given interface should be visible or
373 -- hidden in the Haddock generated content page. We don't expose this
374 -- functionality to the user, but simply use 'Visible' for only local packages.
375 -- Visibility of modules is available since @haddock-2.26.1@.
376 data Visibility
= Visible | Hidden
379 data HaddockProjectFlags
= HaddockProjectFlags
380 { haddockProjectHackage
:: Flag
Bool
381 -- ^ a shortcut option which builds documentation linked to hackage. It implies:
382 -- * `--html-location='https://hackage.haskell.org/package/$prg-$version/docs'
385 -- * `--gen-contents`
386 -- * `--hyperlinked-source`
387 , -- options passed to @haddock@ via 'createHaddockIndex'
388 haddockProjectDir
:: Flag
String
389 -- ^ output directory of combined haddocks, the default is './haddocks'
390 , haddockProjectPrologue
:: Flag
String
391 , haddockProjectInterfaces
:: Flag
[(FilePath, Maybe FilePath, Maybe FilePath, Visibility
)]
392 -- ^ 'haddocksInterfaces' is inferred by the 'haddocksAction'; currently not
393 -- exposed to the user.
394 , -- options passed to @haddock@ via 'HaddockFlags' when building
397 haddockProjectProgramPaths
:: [(String, FilePath)]
398 , haddockProjectProgramArgs
:: [(String, [String])]
399 , haddockProjectHoogle
:: Flag
Bool
400 , -- haddockHtml is not supported
401 haddockProjectHtmlLocation
:: Flag
String
402 , -- haddockForHackage is not supported
403 haddockProjectExecutables
:: Flag
Bool
404 , haddockProjectTestSuites
:: Flag
Bool
405 , haddockProjectBenchmarks
:: Flag
Bool
406 , haddockProjectForeignLibs
:: Flag
Bool
407 , haddockProjectInternal
:: Flag
Bool
408 , haddockProjectCss
:: Flag
FilePath
409 , haddockProjectHscolourCss
:: Flag
FilePath
410 , -- haddockContent is not supported, a fixed value is provided
411 -- haddockIndex is not supported, a fixed value is provided
412 -- haddockDistPerf is not supported, note: it changes location of the haddocks
413 haddockProjectKeepTempFiles
:: Flag
Bool
414 , haddockProjectVerbosity
:: Flag Verbosity
415 , -- haddockBaseUrl is not supported, a fixed value is provided
416 haddockProjectLib
:: Flag
String
417 , haddockProjectOutputDir
:: Flag
FilePath
419 deriving (Show, Generic
, Typeable
)
421 defaultHaddockProjectFlags
:: HaddockProjectFlags
422 defaultHaddockProjectFlags
=
424 { haddockProjectHackage
= Flag
False
425 , haddockProjectDir
= Flag
"./haddocks"
426 , haddockProjectPrologue
= NoFlag
427 , haddockProjectTestSuites
= Flag
False
428 , haddockProjectProgramPaths
= mempty
429 , haddockProjectProgramArgs
= mempty
430 , haddockProjectHoogle
= Flag
False
431 , haddockProjectHtmlLocation
= NoFlag
432 , haddockProjectExecutables
= Flag
False
433 , haddockProjectBenchmarks
= Flag
False
434 , haddockProjectForeignLibs
= Flag
False
435 , haddockProjectInternal
= Flag
False
436 , haddockProjectCss
= NoFlag
437 , haddockProjectHscolourCss
= NoFlag
438 , haddockProjectKeepTempFiles
= Flag
False
439 , haddockProjectVerbosity
= Flag normal
440 , haddockProjectLib
= NoFlag
441 , haddockProjectOutputDir
= NoFlag
442 , haddockProjectInterfaces
= NoFlag
445 haddockProjectCommand
:: CommandUI HaddockProjectFlags
446 haddockProjectCommand
=
448 { commandName
= "v2-haddock-project"
449 , commandSynopsis
= "Generate Haddocks HTML documentation for the cabal project."
450 , commandDescription
= Just
$ \_
->
451 "Require the programm haddock, version 2.26.\n"
452 , commandNotes
= Nothing
454 usageAlternatives
"haddocks" $
456 , "COMPONENTS [FLAGS]"
458 , commandDefaultFlags
= defaultHaddockProjectFlags
459 , commandOptions
= \showOrParseArgs
->
460 haddockProjectOptions showOrParseArgs
464 haddockProjectProgramPaths
465 (\v flags
-> flags
{haddockProjectProgramPaths
= v
})
469 haddockProjectProgramArgs
470 (\v fs
-> fs
{haddockProjectProgramArgs
= v
})
474 haddockProjectProgramArgs
475 (\v flags
-> flags
{haddockProjectProgramArgs
= v
})
479 addKnownProgram haddockProgram
$
480 addKnownProgram ghcProgram
$
483 haddockProjectOptions
:: ShowOrParseArgs
-> [OptionField HaddockProjectFlags
]
484 haddockProjectOptions _showOrParseArgs
=
489 [ "A short-cut option to build documentation linked to hackage."
492 haddockProjectHackage
493 (\v flags
-> flags
{haddockProjectHackage
= v
})
500 (\v flags
-> flags
{haddockProjectDir
= v
})
501 (optArg
' "DIRECTORY" maybeToFlag
(fmap Just
. flagToList
))
505 "File path to a prologue file in haddock format"
506 haddockProjectPrologue
507 (\v flags
-> flags
{haddockProjectPrologue
= v
})
508 (optArg
' "PATH" maybeToFlag
(fmap Just
. flagToList
))
512 "Generate a hoogle database"
514 (\v flags
-> flags
{haddockProjectHoogle
= v
})
519 "Location of HTML documentation for pre-requisite packages"
520 haddockProjectHtmlLocation
521 (\v flags
-> flags
{haddockProjectHtmlLocation
= v
})
526 "Run haddock for Executables targets"
527 haddockProjectExecutables
528 (\v flags
-> flags
{haddockProjectExecutables
= v
})
533 "Run haddock for Test Suite targets"
534 haddockProjectTestSuites
535 (\v flags
-> flags
{haddockProjectTestSuites
= v
})
540 "Run haddock for Benchmark targets"
541 haddockProjectBenchmarks
542 (\v flags
-> flags
{haddockProjectBenchmarks
= v
})
546 ["foreign-libraries"]
547 "Run haddock for Foreign Library targets"
548 haddockProjectForeignLibs
549 (\v flags
-> flags
{haddockProjectForeignLibs
= v
})
554 "Run haddock for internal modules and include all symbols"
555 haddockProjectInternal
556 (\v flags
-> flags
{haddockProjectInternal
= v
})
561 "Use PATH as the haddock stylesheet"
563 (\v flags
-> flags
{haddockProjectCss
= v
})
568 "Use PATH as the HsColour stylesheet"
569 haddockProjectHscolourCss
570 (\v flags
-> flags
{haddockProjectHscolourCss
= v
})
575 "Keep temporary files"
576 haddockProjectKeepTempFiles
577 (\b flags
-> flags
{haddockProjectKeepTempFiles
= b
})
580 haddockProjectVerbosity
581 (\v flags
-> flags
{haddockProjectVerbosity
= v
})
585 "location of Haddocks static / auxiliary files"
587 (\v flags
-> flags
{haddockProjectLib
= v
})
592 "Generate haddock documentation into this directory. This flag is provided as a technology preview and is subject to change in the next releases."
593 haddockProjectOutputDir
594 (\v flags
-> flags
{haddockProjectOutputDir
= v
})
598 emptyHaddockProjectFlags
:: HaddockProjectFlags
599 emptyHaddockProjectFlags
= mempty
601 instance Monoid HaddockProjectFlags
where
605 instance Semigroup HaddockProjectFlags
where