{-# LANGUAGE RecordWildCards #-}

-- | cabal-install CLI command: haddock
--
module Distribution.Client.CmdHaddock (
    -- * The @haddock@ CLI and action
    haddockCommand,
    haddockAction,

    ClientHaddockFlags(..),

    -- * Internals exposed for testing
    selectPackageTargets,
    selectComponentTarget
  ) where

import Distribution.Client.Compat.Prelude
import Prelude ()

import Distribution.Client.ProjectOrchestration
import Distribution.Client.ProjectPlanning
         ( ElaboratedSharedConfig(..) )
import Distribution.Client.CmdErrorMessages
import Distribution.Client.TargetProblem
         ( TargetProblem (..), TargetProblem' )
import Distribution.Client.NixStyleOptions
         ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
import Distribution.Client.Setup
         ( GlobalFlags, ConfigFlags(..), InstallFlags (..))
import Distribution.Simple.Setup
         ( HaddockFlags(..), fromFlagOrDefault, trueArg )
import Distribution.Simple.Command
         ( CommandUI(..), usageAlternatives, ShowOrParseArgs, OptionField, option )
import Distribution.Simple.Program.Builtin
         ( haddockProgram )
import Distribution.Simple.Program.Db
         ( addKnownProgram, reconfigurePrograms )
import Distribution.Verbosity
         ( normal )
import Distribution.Simple.Utils
         ( wrapText, die', notice )
import Distribution.Simple.Flag (Flag(..))

import qualified System.Exit (exitSuccess)

newtype ClientHaddockFlags = ClientHaddockFlags { ClientHaddockFlags -> Flag Bool
openInBrowser :: Flag Bool }

haddockCommand :: CommandUI (NixStyleFlags ClientHaddockFlags)
haddockCommand :: CommandUI (NixStyleFlags ClientHaddockFlags)
haddockCommand = CommandUI {
  commandName :: String
commandName         = String
"v2-haddock",
  commandSynopsis :: String
commandSynopsis     = String
"Build Haddock documentation.",
  commandUsage :: String -> String
commandUsage        = String -> [String] -> String -> String
usageAlternatives String
"v2-haddock" [ String
"[FLAGS] TARGET" ],
  commandDescription :: Maybe (String -> String)
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
_ -> String -> String
wrapText forall a b. (a -> b) -> a -> b
$
        String
"Build Haddock documentation for the specified packages within the "
     forall a. [a] -> [a] -> [a]
++ String
"project.\n\n"

     forall a. [a] -> [a] -> [a]
++ String
"Any package in the project can be specified. If no package is "
     forall a. [a] -> [a] -> [a]
++ String
"specified, the default is to build the documentation for the package "
     forall a. [a] -> [a] -> [a]
++ String
"in the current directory. The default behaviour is to build "
     forall a. [a] -> [a] -> [a]
++ String
"documentation for the exposed modules of the library component (if "
     forall a. [a] -> [a] -> [a]
++ String
"any). This can be changed with the '--internal', '--executables', "
     forall a. [a] -> [a] -> [a]
++ String
"'--tests', '--benchmarks' or '--all' flags.\n\n"

     forall a. [a] -> [a] -> [a]
++ String
"Currently, documentation for dependencies is NOT built. This "
     forall a. [a] -> [a] -> [a]
++ String
"behavior may change in future.\n\n"

     forall a. [a] -> [a] -> [a]
++ String
"Additional configuration flags can be specified on the command line "
     forall a. [a] -> [a] -> [a]
++ String
"and these extend the project configuration from the 'cabal.project', "
     forall a. [a] -> [a] -> [a]
++ String
"'cabal.project.local' and other files.",
  commandNotes :: Maybe (String -> String)
commandNotes        = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
pname ->
        String
"Examples:\n"
     forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" v2-haddock pkgname"
     forall a. [a] -> [a] -> [a]
++ String
"    Build documentation for the package named pkgname\n"
  , commandOptions :: ShowOrParseArgs -> [OptionField (NixStyleFlags ClientHaddockFlags)]
commandOptions      = forall a.
(ShowOrParseArgs -> [OptionField a])
-> ShowOrParseArgs -> [OptionField (NixStyleFlags a)]
nixStyleOptions ShowOrParseArgs -> [OptionField ClientHaddockFlags]
haddockOptions
  , commandDefaultFlags :: NixStyleFlags ClientHaddockFlags
commandDefaultFlags = forall a. a -> NixStyleFlags a
defaultNixStyleFlags (Flag Bool -> ClientHaddockFlags
ClientHaddockFlags (forall a. a -> Flag a
Flag Bool
False))
  }
   --TODO: [nice to have] support haddock on specific components, not just
   -- whole packages and the silly --executables etc modifiers.

haddockOptions :: ShowOrParseArgs -> [OptionField ClientHaddockFlags]
haddockOptions :: ShowOrParseArgs -> [OptionField ClientHaddockFlags]
haddockOptions ShowOrParseArgs
_ =
  [ forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [String
"open"] String
"Open generated documentation in the browser"
    ClientHaddockFlags -> Flag Bool
openInBrowser (\Flag Bool
v ClientHaddockFlags
f -> ClientHaddockFlags
f { openInBrowser :: Flag Bool
openInBrowser = Flag Bool
v}) forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
  ]

-- | The @haddock@ command is TODO.
--
-- For more details on how this works, see the module
-- "Distribution.Client.ProjectOrchestration"
--
haddockAction :: NixStyleFlags ClientHaddockFlags -> [String] -> GlobalFlags -> IO ()
haddockAction :: NixStyleFlags ClientHaddockFlags
-> [String] -> GlobalFlags -> IO ()
haddockAction flags :: NixStyleFlags ClientHaddockFlags
flags@NixStyleFlags {ConfigFlags
HaddockFlags
TestFlags
BenchmarkFlags
ProjectFlags
InstallFlags
ConfigExFlags
ClientHaddockFlags
extraFlags :: forall a. NixStyleFlags a -> a
projectFlags :: forall a. NixStyleFlags a -> ProjectFlags
benchmarkFlags :: forall a. NixStyleFlags a -> BenchmarkFlags
testFlags :: forall a. NixStyleFlags a -> TestFlags
haddockFlags :: forall a. NixStyleFlags a -> HaddockFlags
installFlags :: forall a. NixStyleFlags a -> InstallFlags
configExFlags :: forall a. NixStyleFlags a -> ConfigExFlags
configFlags :: forall a. NixStyleFlags a -> ConfigFlags
extraFlags :: ClientHaddockFlags
projectFlags :: ProjectFlags
benchmarkFlags :: BenchmarkFlags
testFlags :: TestFlags
haddockFlags :: HaddockFlags
installFlags :: InstallFlags
configExFlags :: ConfigExFlags
configFlags :: ConfigFlags
..} [String]
targetStrings GlobalFlags
globalFlags = do
    ProjectBaseContext
projCtx <- Verbosity
-> ProjectConfig -> CurrentCommand -> IO ProjectBaseContext
establishProjectBaseContext Verbosity
verbosity ProjectConfig
cliConfig CurrentCommand
HaddockCommand

    let baseCtx :: ProjectBaseContext
baseCtx
          | forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (ClientHaddockFlags -> Flag Bool
openInBrowser ClientHaddockFlags
extraFlags)
            = ProjectBaseContext
projCtx { buildSettings :: BuildTimeSettings
buildSettings = (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
projCtx) { buildSettingHaddockOpen :: Bool
buildSettingHaddockOpen = Bool
True } }
          | Bool
otherwise
            = ProjectBaseContext
projCtx

    [TargetSelector]
targetSelectors <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Verbosity -> [TargetSelectorProblem] -> IO a
reportTargetSelectorProblems Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                   forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a.
[PackageSpecifier (SourcePackage (PackageLocation a))]
-> Maybe ComponentKindFilter
-> [String]
-> IO (Either [TargetSelectorProblem] [TargetSelector])
readTargetSelectors (ProjectBaseContext -> [PackageSpecifier UnresolvedSourcePackage]
localPackages ProjectBaseContext
baseCtx) forall a. Maybe a
Nothing [String]
targetStrings

    ProjectBuildContext
buildCtx <-
      Verbosity
-> ProjectBaseContext
-> (ElaboratedInstallPlan
    -> IO (ElaboratedInstallPlan, TargetsMap))
-> IO ProjectBuildContext
runProjectPreBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx forall a b. (a -> b) -> a -> b
$ \ElaboratedInstallPlan
elaboratedPlan -> do

            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BuildTimeSettings -> Bool
buildSettingOnlyDeps (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
baseCtx)) forall a b. (a -> b) -> a -> b
$
              forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity
                String
"The haddock command does not support '--only-dependencies'."

              -- When we interpret the targets on the command line, interpret them as
              -- haddock targets
            TargetsMap
targets <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Verbosity -> [TargetProblem'] -> IO a
reportBuildDocumentationTargetProblems Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                     forall a b. (a -> b) -> a -> b
$ forall err.
(forall k.
 TargetSelector
 -> [AvailableTarget k] -> Either (TargetProblem err) [k])
-> (forall k.
    SubComponentTarget
    -> AvailableTarget k -> Either (TargetProblem err) k)
-> ElaboratedInstallPlan
-> Maybe SourcePackageDb
-> [TargetSelector]
-> Either [TargetProblem err] TargetsMap
resolveTargets
                         (forall k.
HaddockFlags
-> TargetSelector
-> [AvailableTarget k]
-> Either TargetProblem' [k]
selectPackageTargets HaddockFlags
haddockFlags)
                         forall k.
SubComponentTarget -> AvailableTarget k -> Either TargetProblem' k
selectComponentTarget
                         ElaboratedInstallPlan
elaboratedPlan
                         forall a. Maybe a
Nothing
                         [TargetSelector]
targetSelectors

            let elaboratedPlan' :: ElaboratedInstallPlan
elaboratedPlan' = TargetAction
-> TargetsMap -> ElaboratedInstallPlan -> ElaboratedInstallPlan
pruneInstallPlanToTargets
                                    TargetAction
TargetActionHaddock
                                    TargetsMap
targets
                                    ElaboratedInstallPlan
elaboratedPlan
            forall (m :: * -> *) a. Monad m => a -> m a
return (ElaboratedInstallPlan
elaboratedPlan', TargetsMap
targets)

    Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO ()
printPlan Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx

    ProgramDb
progs <- Verbosity
-> [(String, String)]
-> [(String, [String])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms Verbosity
verbosity
               (HaddockFlags -> [(String, String)]
haddockProgramPaths HaddockFlags
haddockFlags)
               (HaddockFlags -> [(String, [String])]
haddockProgramArgs HaddockFlags
haddockFlags)
             -- we need to insert 'haddockProgram' before we reconfigure it,
             -- otherwise 'set
           forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> ProgramDb -> ProgramDb
addKnownProgram Program
haddockProgram
           forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs
           forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared
           forall a b. (a -> b) -> a -> b
$ ProjectBuildContext
buildCtx
    let buildCtx' :: ProjectBuildContext
buildCtx' = ProjectBuildContext
buildCtx { elaboratedShared :: ElaboratedSharedConfig
elaboratedShared =
                               (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx)
                               { pkgConfigCompilerProgs :: ProgramDb
pkgConfigCompilerProgs = ProgramDb
progs } }

    BuildOutcomes
buildOutcomes <- Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO BuildOutcomes
runProjectBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx'
    Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> BuildOutcomes
-> IO ()
runProjectPostBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx' BuildOutcomes
buildOutcomes
  where
    verbosity :: Verbosity
verbosity = forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
configFlags)
    installDoc :: Bool
installDoc = forall a. a -> Flag a -> a
fromFlagOrDefault Bool
True (InstallFlags -> Flag Bool
installDocumentation InstallFlags
installFlags)
    flags' :: NixStyleFlags ClientHaddockFlags
flags' = NixStyleFlags ClientHaddockFlags
flags { installFlags :: InstallFlags
installFlags = InstallFlags
installFlags { installDocumentation :: Flag Bool
installDocumentation = forall a. a -> Flag a
Flag Bool
installDoc } }
    cliConfig :: ProjectConfig
cliConfig = forall a.
GlobalFlags
-> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig
commandLineFlagsToProjectConfig GlobalFlags
globalFlags NixStyleFlags ClientHaddockFlags
flags' forall a. Monoid a => a
mempty -- ClientInstallFlags, not needed here

-- | This defines what a 'TargetSelector' means for the @haddock@ command.
-- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
-- or otherwise classifies the problem.
--
-- For the @haddock@ command we select all buildable libraries. Additionally,
-- depending on the @--executables@ flag we also select all the buildable exes.
-- We do similarly for test-suites, benchmarks and foreign libs.
--
selectPackageTargets  :: HaddockFlags -> TargetSelector
                      -> [AvailableTarget k] -> Either TargetProblem' [k]
selectPackageTargets :: forall k.
HaddockFlags
-> TargetSelector
-> [AvailableTarget k]
-> Either TargetProblem' [k]
selectPackageTargets HaddockFlags
haddockFlags TargetSelector
targetSelector [AvailableTarget k]
targets

    -- If there are any buildable targets then we select those
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [k]
targetsBuildable)
  = forall a b. b -> Either a b
Right [k]
targetsBuildable

    -- If there are targets but none are buildable then we report those
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AvailableTarget k]
targets)
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> [AvailableTarget ()] -> TargetProblem a
TargetProblemNoneEnabled TargetSelector
targetSelector [AvailableTarget ()]
targets')

    -- If there are no targets at all then we report that
  | Bool
otherwise
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> TargetProblem a
TargetProblemNoTargets TargetSelector
targetSelector)
  where
    targets' :: [AvailableTarget ()]
targets'         = forall k. [AvailableTarget k] -> [AvailableTarget ()]
forgetTargetsDetail    (forall a b. (a -> b) -> [a] -> [b]
map forall {k}. AvailableTarget k -> AvailableTarget k
disableNotRequested [AvailableTarget k]
targets)
    targetsBuildable :: [k]
targetsBuildable = forall k. [AvailableTarget k] -> [k]
selectBuildableTargets (forall a b. (a -> b) -> [a] -> [b]
map forall {k}. AvailableTarget k -> AvailableTarget k
disableNotRequested [AvailableTarget k]
targets)

    -- When there's a target filter like "pkg:exes" then we do select exes,
    -- but if it's just a target like "pkg" then we don't build docs for exes
    -- unless they are requested by default (i.e. by using --executables)
    disableNotRequested :: AvailableTarget k -> AvailableTarget k
disableNotRequested t :: AvailableTarget k
t@(AvailableTarget PackageId
_ ComponentName
cname (TargetBuildable k
_ TargetRequested
_) Bool
_)
      | Bool -> Bool
not (TargetSelector -> ComponentKindFilter -> Bool
isRequested TargetSelector
targetSelector (ComponentName -> ComponentKindFilter
componentKind ComponentName
cname))
      = AvailableTarget k
t { availableTargetStatus :: AvailableTargetStatus k
availableTargetStatus = forall k. AvailableTargetStatus k
TargetDisabledByUser }
    disableNotRequested AvailableTarget k
t = AvailableTarget k
t

    isRequested :: TargetSelector -> ComponentKindFilter -> Bool
isRequested (TargetPackage TargetImplicitCwd
_ [PackageId]
_ (Just ComponentKindFilter
_)) ComponentKindFilter
_ = Bool
True
    isRequested (TargetAllPackages (Just ComponentKindFilter
_)) ComponentKindFilter
_ = Bool
True
    isRequested TargetSelector
_ ComponentKindFilter
LibKind    = Bool
True
--  isRequested _ SubLibKind = True --TODO: what about sublibs?

    -- TODO/HACK, we encode some defaults here as v2-haddock's logic;
    -- make sure this matches the defaults applied in
    -- "Distribution.Client.ProjectPlanning"; this may need more work
    -- to be done properly
    --
    -- See also https://github.com/haskell/cabal/pull/4886
    isRequested TargetSelector
_ ComponentKindFilter
FLibKind   = forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (HaddockFlags -> Flag Bool
haddockForeignLibs HaddockFlags
haddockFlags)
    isRequested TargetSelector
_ ComponentKindFilter
ExeKind    = forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (HaddockFlags -> Flag Bool
haddockExecutables HaddockFlags
haddockFlags)
    isRequested TargetSelector
_ ComponentKindFilter
TestKind   = forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (HaddockFlags -> Flag Bool
haddockTestSuites  HaddockFlags
haddockFlags)
    isRequested TargetSelector
_ ComponentKindFilter
BenchKind  = forall a. a -> Flag a -> a
fromFlagOrDefault Bool
False (HaddockFlags -> Flag Bool
haddockBenchmarks  HaddockFlags
haddockFlags)


-- | For a 'TargetComponent' 'TargetSelector', check if the component can be
-- selected.
--
-- For the @haddock@ command we just need the basic checks on being buildable
-- etc.
--
selectComponentTarget :: SubComponentTarget
                      -> AvailableTarget k -> Either TargetProblem' k
selectComponentTarget :: forall k.
SubComponentTarget -> AvailableTarget k -> Either TargetProblem' k
selectComponentTarget = forall k a.
SubComponentTarget
-> AvailableTarget k -> Either (TargetProblem a) k
selectComponentTargetBasic

reportBuildDocumentationTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
reportBuildDocumentationTargetProblems :: forall a. Verbosity -> [TargetProblem'] -> IO a
reportBuildDocumentationTargetProblems Verbosity
verbosity [TargetProblem']
problems =
  case [TargetProblem']
problems of
    [TargetProblemNoneEnabled TargetSelector
_ [AvailableTarget ()]
_] -> do
      Verbosity -> String -> IO ()
notice Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
        [ String
"No documentation was generated as this package does not contain a library."
        , String
"Perhaps you want to use the --haddock-all flag, or one or more of the"
        , String
"--haddock-executables, --haddock-tests, --haddock-benchmarks or"
        , String
"--haddock-internal flags."
        ]
      forall a. IO a
System.Exit.exitSuccess
    [TargetProblem']
_ -> forall a. Verbosity -> String -> [TargetProblem'] -> IO a
reportTargetProblems Verbosity
verbosity String
"build documentation for" [TargetProblem']
problems