Skip to content
Snippets Groups Projects
Unverified Commit 55b4ed9f authored by Kobayashi's avatar Kobayashi Committed by GitHub
Browse files

Pass some haddock flags to dependencies (#8414)

* pass some haddock flags to dependencies

* add tests

* add changelog

* fix whitespace

* fix test on MacOS
parent d45f3d8b
No related branches found
No related tags found
No related merge requests found
Showing
with 208 additions and 2 deletions
......@@ -346,7 +346,15 @@ commandLineFlagsToProjectConfig globalFlags NixStyleFlags {..} clientInstallFlag
splitConfig pc = (pc
, mempty { packageConfigProgramPaths = packageConfigProgramPaths pc
, packageConfigProgramPathExtra = packageConfigProgramPathExtra pc
, packageConfigDocumentation = packageConfigDocumentation pc })
-- Some flags to haddock should be passed to dependencies
, packageConfigDocumentation = packageConfigDocumentation pc
, packageConfigHaddockHoogle = packageConfigHaddockHoogle pc
, packageConfigHaddockHtml = packageConfigHaddockHtml pc
, packageConfigHaddockInternal = packageConfigHaddockInternal pc
, packageConfigHaddockQuickJump = packageConfigHaddockQuickJump pc
, packageConfigHaddockLinkedSource = packageConfigHaddockLinkedSource pc
})
-- | Convert from the types currently used for the user-wide @~/.cabal/config@
-- file into the 'ProjectConfig' type.
......
packages: .
\ No newline at end of file
name: example
version: 1.0
build-type: Simple
cabal-version: >= 1.10
library
hs-source-dirs: src
exposed-modules: Lib
build-depends: base, indef
default-language: Haskell2010
# cabal v2-update
Downloading the latest package list from test-local-repo
# cabal v2-build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- sigs-0.1.0.0 (lib) (requires build)
- indef-0.1.0.0 (lib) (requires build)
- example-1.0 (lib) (first run)
Configuring library for sigs-0.1.0.0..
Preprocessing library for sigs-0.1.0.0..
Building library instantiated with Data.Map = <Data.Map>
for sigs-0.1.0.0..
Preprocessing library for sigs-0.1.0.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for sigs-0.1.0.0..
Documentation created: dist/doc/html/sigs/sigs.txt
Installing library in <PATH>
Configuring library for indef-0.1.0.0..
Preprocessing library for indef-0.1.0.0..
Building library instantiated with Data.Map = <Data.Map>
for indef-0.1.0.0..
Preprocessing library for indef-0.1.0.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for indef-0.1.0.0..
Documentation created: dist/doc/html/indef/indef.txt
Installing library in <PATH>
Configuring library for example-1.0..
Preprocessing library for example-1.0..
Building library instantiated with Data.Map = <Data.Map>
for example-1.0..
Preprocessing library for example-1.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for example-1.0..
Documentation created: <ROOT>/hoogle.dist/work/dist/build/<ARCH>/ghc-<GHCVER>/example-1.0/doc/html/example/example.txt
import Test.Cabal.Prelude
main = withShorterPathForNewBuildStore $ \storeDir -> cabalTest $ withRepo "repo" $ do
-- Checks if hoogle txt files are generated.
-- Logs contain something like "Documentation created: dist/doc/html/indef/indef.txt", so we don't need
-- to do extra check
cabalG ["--store-dir=" ++ storeDir] "v2-build"
[ "example"
, "--enable-documentation"
, "--haddock-hoogle"
]
# cabal v2-update
Downloading the latest package list from test-local-repo
# cabal v2-build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- sigs-0.1.0.0 (lib) (requires build)
- indef-0.1.0.0 (lib) (requires build)
- example-1.0 (lib) (first run)
Configuring library for sigs-0.1.0.0..
Preprocessing library for sigs-0.1.0.0..
Building library instantiated with Data.Map = <Data.Map>
for sigs-0.1.0.0..
Preprocessing library for sigs-0.1.0.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for sigs-0.1.0.0..
Documentation created: dist/doc/html/sigs/index.html
Installing library in <PATH>
Configuring library for indef-0.1.0.0..
Preprocessing library for indef-0.1.0.0..
Building library instantiated with Data.Map = <Data.Map>
for indef-0.1.0.0..
Preprocessing library for indef-0.1.0.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for indef-0.1.0.0..
Documentation created: dist/doc/html/indef/index.html
Installing library in <PATH>
Configuring library for example-1.0..
Preprocessing library for example-1.0..
Building library instantiated with Data.Map = <Data.Map>
for example-1.0..
Preprocessing library for example-1.0..
Running Haddock on library instantiated with Data.Map = <Data.Map>
for example-1.0..
Documentation created: <ROOT>/quickjump.dist/work/dist/build/<ARCH>/ghc-<GHCVER>/example-1.0/doc/html/example/index.html
\ No newline at end of file
import Test.Cabal.Prelude
import System.Directory
import System.FilePath
main = withShorterPathForNewBuildStore $ \storeDir -> cabalTest $ withRepo "repo" $ do
cabalG ["--store-dir=" ++ storeDir] "v2-build"
[ "example"
, "--enable-documentation"
, "--haddock-quickjump"
]
liftIO $ do
libDir <- findDependencyInStore storeDir "indef"
assertFileDoesContain (libDir </> "cabal-hash.txt") "haddock-quickjump: True"
docIndexJsonExists <- doesFileExist (libDir </> "share" </> "doc" </> "html" </> "doc-index.json")
assertBool "doc-index.json doesn't exist, --quickjump is probably not passed to haddock" docIndexJsonExists
import qualified Data.Map as Map
import Data.Map (Map)
import Foo
main = print $ f (+1) (Map.fromList [(0,1),(2,3)] :: Map Int Int)
name: exe
version: 0.1.0.0
license: BSD3
author: Edward Z. Yang
maintainer: ezyang@cs.stanford.edu
build-type: Simple
cabal-version: 2.0
executable exe
build-depends: base, containers, indef
main-is: Main.hs
default-language: Haskell2010
module Foo where
import Data.Map
-- | A dummy function using 'Map'
f :: (a -> b) -> Map k a -> Map k b
f = fmap
name: indef
version: 0.1.0.0
license: BSD3
author: Edward Z. Yang
maintainer: ezyang@cs.stanford.edu
build-type: Simple
cabal-version: 2.0
library
build-depends: base, sigs
exposed-modules: Foo
default-language: Haskell2010
{-# LANGUAGE RoleAnnotations #-}
signature Data.Map where
type role Map nominal representational
data Map k a
instance Functor (Map k)
name: sigs
version: 0.1.0.0
license: BSD3
author: Edward Z. Yang
maintainer: ezyang@cs.stanford.edu
build-type: Simple
cabal-version: 2.0
library
build-depends: base
signatures: Data.Map
default-language: Haskell2010
module Lib where
import Foo
-- | See 'f'
main :: IO ()
main = putStrLn "Hello, Haskell!"
......@@ -62,7 +62,7 @@ import System.Exit (ExitCode (..))
import System.FilePath ((</>), takeExtensions, takeDrive, takeDirectory, normalise, splitPath, joinPath, splitFileName, (<.>), dropTrailingPathSeparator)
import Control.Concurrent (threadDelay)
import qualified Data.Char as Char
import System.Directory (getTemporaryDirectory, getCurrentDirectory, canonicalizePath, copyFile, copyFile, doesDirectoryExist, doesFileExist, createDirectoryIfMissing, getDirectoryContents)
import System.Directory (getTemporaryDirectory, getCurrentDirectory, canonicalizePath, copyFile, copyFile, doesDirectoryExist, doesFileExist, createDirectoryIfMissing, getDirectoryContents, listDirectory)
import Control.Retry (exponentialBackoff, limitRetriesByCumulativeDelay)
import Network.Wait (waitTcpVerbose)
......@@ -1131,3 +1131,21 @@ withShorterPathForNewBuildStore test = do
then takeDrive `fmap` getCurrentDirectory
else getTemporaryDirectory
withTempDirectory normal tempDir "cabal-test-store" test
-- | Find where a package locates in the store dir. This works only if there is exactly one 1 ghc version
-- and exactly 1 directory for the given package in the store dir.
findDependencyInStore :: FilePath -- ^store dir
-> String -- ^package name prefix
-> IO FilePath -- ^package dir
findDependencyInStore storeDir pkgName = do
storeDirForGhcVersion <- head <$> listDirectory storeDir
packageDirs <- listDirectory (storeDir </> storeDirForGhcVersion)
-- Ideally, we should call 'hashedInstalledPackageId' from 'Distribution.Client.PackageHash'.
-- But 'PackageHashInputs', especially 'PackageHashConfigInputs', is too hard to construct.
let pkgName' =
if buildOS == OSX
then filter (not . flip elem "aeiou") pkgName
-- simulates the way 'hashedInstalledPackageId' uses to compress package name
else pkgName
let libDir = head $ filter (pkgName' `isPrefixOf`) packageDirs
pure (storeDir </> storeDirForGhcVersion </> libDir)
synopsis: Pass some haddock flags to dependencies
packages: cabal-install
prs: #8414
issues: #8104 #395
description: {
- Pass "--haddock-hoogle", "--haddock-html", "--haddock-internal", "--haddock-quickjump", "--haddock-hyperlinked-source"
to all the dependencies if they are specified as command line args
}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment