Skip to content
Snippets Groups Projects
Commit 260e1e1b authored by Alec Theriault's avatar Alec Theriault
Browse files

Remove Haddock's dependency on `Cabal`

At this point, Haddock depended on Cabal-the-library solely for a
verbosity parser (which misleadingly accepts all sorts of verbosity
options that Haddock never uses). Now, the only dependency on Cabal
is for `haddock-test` (which uses Cabal to locate the Haddock interface
files of a couple boot libraries).
parent 384577e8
Branches
Tags
No related merge requests found
......@@ -43,7 +43,6 @@ library
-- this package typically supports only single major versions
build-depends: base ^>= 4.12.0
, Cabal ^>= 2.4.0
, ghc ^>= 8.8
, ghc-paths ^>= 0.1.0.9
, haddock-library ^>= 1.8.0
......@@ -166,8 +165,7 @@ test-suite spec
Haddock.Backends.Hyperlinker.Parser
Haddock.Backends.Hyperlinker.Types
build-depends: Cabal ^>= 2.4
, ghc ^>= 8.8
build-depends: ghc ^>= 8.8
, ghc-paths ^>= 0.1.0.9
, haddock-library ^>= 1.8.0
, xhtml ^>= 3000.2.2
......
......@@ -47,7 +47,6 @@ import Control.Exception (evaluate)
import Data.List
import qualified Data.Map as Map
import qualified Data.Set as Set
import Distribution.Verbosity
import Text.Printf
import Module (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet)
......
......@@ -43,7 +43,6 @@ module Haddock.Options (
import qualified Data.Char as Char
import Data.Version
import Control.Applicative
import Distribution.Verbosity
import FastString
import GHC ( DynFlags, Module, moduleUnitId )
import Haddock.Types
......@@ -332,7 +331,7 @@ sinceQualification flags =
verbosity :: [Flag] -> Verbosity
verbosity flags =
case [ str | Flag_Verbosity str <- flags ] of
[] -> normal
[] -> Normal
x:_ -> case parseVerbosity x of
Left e -> throwE e
Right v -> v
......
......@@ -49,7 +49,7 @@ module Haddock.Utils (
MonadIO(..),
-- * Logging
parseVerbosity,
parseVerbosity, Verbosity(..), silent, normal, verbose, deafening,
out,
-- * System tools
......@@ -81,8 +81,6 @@ import System.Directory ( createDirectory, removeDirectoryRecursive )
import System.IO ( hPutStr, hSetEncoding, IOMode(..), stderr, utf8, withFile )
import System.IO.Unsafe ( unsafePerformIO )
import qualified System.FilePath.Posix as HtmlPath
import Distribution.Verbosity
import Distribution.ReadE
#ifndef mingw32_HOST_OS
import qualified System.Posix.Internals
......@@ -95,10 +93,27 @@ import MonadUtils ( MonadIO(..) )
-- * Logging
--------------------------------------------------------------------------------
data Verbosity = Silent | Normal | Verbose | Deafening
deriving (Eq, Ord, Enum, Bounded, Show)
parseVerbosity :: String -> Either String Verbosity
parseVerbosity = runReadE flagToVerbosity
silent, normal, verbose, deafening :: Verbosity
silent = Silent
normal = Normal
verbose = Verbose
deafening = Deafening
-- | Parse out a verbosity level. Inspired from Cabal's verbosity parsing.
parseVerbosity :: String -> Either String Verbosity
parseVerbosity "0" = Right Silent
parseVerbosity "1" = Right Normal
parseVerbosity "2" = Right Silent
parseVerbosity "3" = Right Deafening
parseVerbosity "silent" = return Silent
parseVerbosity "normal" = return Normal
parseVerbosity "verbose" = return Verbose
parseVerbosity "debug" = return Deafening
parseVerbosity "deafening" = return Deafening
parseVerbosity other = Left ("Can't parse verbosity " ++ other)
-- | Print a message to stdout, if it is not too verbose
out :: MonadIO m
......
......@@ -77,7 +77,6 @@ executable haddock
deepseq,
array,
xhtml >= 3000.2 && < 3000.3,
Cabal >= 1.10,
ghc-boot,
ghc == 8.8.*,
bytestring,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment