cabal init -i should sanitize suggested package name (fix #8404) (#8561)
[cabal.git] / cabal-install / src / Distribution / Client / CmdHaddock.hs
blobbfd2e8baf2be06479c711a4fe94acd827b92c730
1 {-# LANGUAGE RecordWildCards #-}
3 -- | cabal-install CLI command: haddock
4 --
5 module Distribution.Client.CmdHaddock (
6 -- * The @haddock@ CLI and action
7 haddockCommand,
8 haddockAction,
10 ClientHaddockFlags(..),
12 -- * Internals exposed for testing
13 selectPackageTargets,
14 selectComponentTarget
15 ) where
17 import Distribution.Client.Compat.Prelude
18 import Prelude ()
20 import Distribution.Client.ProjectOrchestration
21 import Distribution.Client.ProjectPlanning
22 ( ElaboratedSharedConfig(..) )
23 import Distribution.Client.CmdErrorMessages
24 import Distribution.Client.TargetProblem
25 ( TargetProblem (..), TargetProblem' )
26 import Distribution.Client.NixStyleOptions
27 ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
28 import Distribution.Client.Setup
29 ( GlobalFlags, ConfigFlags(..), InstallFlags (..))
30 import Distribution.Simple.Setup
31 ( HaddockFlags(..), fromFlagOrDefault, trueArg )
32 import Distribution.Simple.Command
33 ( CommandUI(..), usageAlternatives, ShowOrParseArgs, OptionField, option )
34 import Distribution.Simple.Program.Builtin
35 ( haddockProgram )
36 import Distribution.Simple.Program.Db
37 ( addKnownProgram, reconfigurePrograms )
38 import Distribution.Verbosity
39 ( normal )
40 import Distribution.Simple.Utils
41 ( wrapText, die', notice )
42 import Distribution.Simple.Flag (Flag(..))
44 import qualified System.Exit (exitSuccess)
46 newtype ClientHaddockFlags = ClientHaddockFlags { openInBrowser :: Flag Bool }
48 haddockCommand :: CommandUI (NixStyleFlags ClientHaddockFlags)
49 haddockCommand = CommandUI {
50 commandName = "v2-haddock",
51 commandSynopsis = "Build Haddock documentation.",
52 commandUsage = usageAlternatives "v2-haddock" [ "[FLAGS] TARGET" ],
53 commandDescription = Just $ \_ -> wrapText $
54 "Build Haddock documentation for the specified packages within the "
55 ++ "project.\n\n"
57 ++ "Any package in the project can be specified. If no package is "
58 ++ "specified, the default is to build the documentation for the package "
59 ++ "in the current directory. The default behaviour is to build "
60 ++ "documentation for the exposed modules of the library component (if "
61 ++ "any). This can be changed with the '--internal', '--executables', "
62 ++ "'--tests', '--benchmarks' or '--all' flags.\n\n"
64 ++ "Currently, documentation for dependencies is NOT built. This "
65 ++ "behavior may change in future.\n\n"
67 ++ "Additional configuration flags can be specified on the command line "
68 ++ "and these extend the project configuration from the 'cabal.project', "
69 ++ "'cabal.project.local' and other files.",
70 commandNotes = Just $ \pname ->
71 "Examples:\n"
72 ++ " " ++ pname ++ " v2-haddock pkgname"
73 ++ " Build documentation for the package named pkgname\n"
74 , commandOptions = nixStyleOptions haddockOptions
75 , commandDefaultFlags = defaultNixStyleFlags (ClientHaddockFlags (Flag False))
77 --TODO: [nice to have] support haddock on specific components, not just
78 -- whole packages and the silly --executables etc modifiers.
80 haddockOptions :: ShowOrParseArgs -> [OptionField ClientHaddockFlags]
81 haddockOptions _ =
82 [ option [] ["open"] "Open generated documentation in the browser"
83 openInBrowser (\v f -> f { openInBrowser = v}) trueArg
86 -- | The @haddock@ command is TODO.
88 -- For more details on how this works, see the module
89 -- "Distribution.Client.ProjectOrchestration"
91 haddockAction :: NixStyleFlags ClientHaddockFlags -> [String] -> GlobalFlags -> IO ()
92 haddockAction flags@NixStyleFlags {..} targetStrings globalFlags = do
93 projCtx <- establishProjectBaseContext verbosity cliConfig HaddockCommand
95 let baseCtx
96 | fromFlagOrDefault False (openInBrowser extraFlags)
97 = projCtx { buildSettings = (buildSettings projCtx) { buildSettingHaddockOpen = True } }
98 | otherwise
99 = projCtx
101 targetSelectors <- either (reportTargetSelectorProblems verbosity) return
102 =<< readTargetSelectors (localPackages baseCtx) Nothing targetStrings
104 buildCtx <-
105 runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do
107 when (buildSettingOnlyDeps (buildSettings baseCtx)) $
108 die' verbosity
109 "The haddock command does not support '--only-dependencies'."
111 -- When we interpret the targets on the command line, interpret them as
112 -- haddock targets
113 targets <- either (reportBuildDocumentationTargetProblems verbosity) return
114 $ resolveTargets
115 (selectPackageTargets haddockFlags)
116 selectComponentTarget
117 elaboratedPlan
118 Nothing
119 targetSelectors
121 let elaboratedPlan' = pruneInstallPlanToTargets
122 TargetActionHaddock
123 targets
124 elaboratedPlan
125 return (elaboratedPlan', targets)
127 printPlan verbosity baseCtx buildCtx
129 progs <- reconfigurePrograms verbosity
130 (haddockProgramPaths haddockFlags)
131 (haddockProgramArgs haddockFlags)
132 -- we need to insert 'haddockProgram' before we reconfigure it,
133 -- otherwise 'set
134 . addKnownProgram haddockProgram
135 . pkgConfigCompilerProgs
136 . elaboratedShared
137 $ buildCtx
138 let buildCtx' = buildCtx { elaboratedShared =
139 (elaboratedShared buildCtx)
140 { pkgConfigCompilerProgs = progs } }
142 buildOutcomes <- runProjectBuildPhase verbosity baseCtx buildCtx'
143 runProjectPostBuildPhase verbosity baseCtx buildCtx' buildOutcomes
144 where
145 verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
146 installDoc = fromFlagOrDefault True (installDocumentation installFlags)
147 flags' = flags { installFlags = installFlags { installDocumentation = Flag installDoc } }
148 cliConfig = commandLineFlagsToProjectConfig globalFlags flags' mempty -- ClientInstallFlags, not needed here
150 -- | This defines what a 'TargetSelector' means for the @haddock@ command.
151 -- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
152 -- or otherwise classifies the problem.
154 -- For the @haddock@ command we select all buildable libraries. Additionally,
155 -- depending on the @--executables@ flag we also select all the buildable exes.
156 -- We do similarly for test-suites, benchmarks and foreign libs.
158 selectPackageTargets :: HaddockFlags -> TargetSelector
159 -> [AvailableTarget k] -> Either TargetProblem' [k]
160 selectPackageTargets haddockFlags targetSelector targets
162 -- If there are any buildable targets then we select those
163 | not (null targetsBuildable)
164 = Right targetsBuildable
166 -- If there are targets but none are buildable then we report those
167 | not (null targets)
168 = Left (TargetProblemNoneEnabled targetSelector targets')
170 -- If there are no targets at all then we report that
171 | otherwise
172 = Left (TargetProblemNoTargets targetSelector)
173 where
174 targets' = forgetTargetsDetail (map disableNotRequested targets)
175 targetsBuildable = selectBuildableTargets (map disableNotRequested targets)
177 -- When there's a target filter like "pkg:exes" then we do select exes,
178 -- but if it's just a target like "pkg" then we don't build docs for exes
179 -- unless they are requested by default (i.e. by using --executables)
180 disableNotRequested t@(AvailableTarget _ cname (TargetBuildable _ _) _)
181 | not (isRequested targetSelector (componentKind cname))
182 = t { availableTargetStatus = TargetDisabledByUser }
183 disableNotRequested t = t
185 isRequested (TargetPackage _ _ (Just _)) _ = True
186 isRequested (TargetAllPackages (Just _)) _ = True
187 isRequested _ LibKind = True
188 -- isRequested _ SubLibKind = True --TODO: what about sublibs?
190 -- TODO/HACK, we encode some defaults here as v2-haddock's logic;
191 -- make sure this matches the defaults applied in
192 -- "Distribution.Client.ProjectPlanning"; this may need more work
193 -- to be done properly
195 -- See also https://github.com/haskell/cabal/pull/4886
196 isRequested _ FLibKind = fromFlagOrDefault False (haddockForeignLibs haddockFlags)
197 isRequested _ ExeKind = fromFlagOrDefault False (haddockExecutables haddockFlags)
198 isRequested _ TestKind = fromFlagOrDefault False (haddockTestSuites haddockFlags)
199 isRequested _ BenchKind = fromFlagOrDefault False (haddockBenchmarks haddockFlags)
202 -- | For a 'TargetComponent' 'TargetSelector', check if the component can be
203 -- selected.
205 -- For the @haddock@ command we just need the basic checks on being buildable
206 -- etc.
208 selectComponentTarget :: SubComponentTarget
209 -> AvailableTarget k -> Either TargetProblem' k
210 selectComponentTarget = selectComponentTargetBasic
212 reportBuildDocumentationTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
213 reportBuildDocumentationTargetProblems verbosity problems =
214 case problems of
215 [TargetProblemNoneEnabled _ _] -> do
216 notice verbosity $ unwords
217 [ "No documentation was generated as this package does not contain a library."
218 , "Perhaps you want to use the --haddock-all flag, or one or more of the"
219 , "--haddock-executables, --haddock-tests, --haddock-benchmarks or"
220 , "--haddock-internal flags."
222 System.Exit.exitSuccess
223 _ -> reportTargetProblems verbosity "build documentation for" problems