From a6504507cb7f575dad63aa9f992cfc8d4f70c582 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Mon, 7 Jan 2019 13:55:22 -0800
Subject: Print kinded tyvars in constructors for Hoogle (#993)
Fixes #992
---
haddock-api/src/Haddock/Backends/Hoogle.hs | 10 ++++++++--
1 file changed, 8 insertions(+), 2 deletions(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 5f77c38c..7e2ce2f2 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -266,8 +266,14 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
-- docs for con_names on why it is a list to begin with.
name = commaSeparate dflags . map unL $ getConNames con
- resType = apps $ map (reL . HsTyVar NoExt NotPromoted . reL) $
- (tcdName dat) : [hsTyVarName v | L _ v@(UserTyVar _ _) <- hsQTvExplicit $ tyClDeclTyVars dat]
+ resType = let c = HsTyVar NoExt NotPromoted (noLoc (tcdName dat))
+ as = map (tyVarBndr2Type . unLoc) (hsQTvExplicit $ tyClDeclTyVars dat)
+ in apps (map noLoc (c : as))
+
+ tyVarBndr2Type :: HsTyVarBndr GhcRn -> HsType GhcRn
+ tyVarBndr2Type (UserTyVar _ n) = HsTyVar NoExt NotPromoted n
+ tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig NoExt (noLoc (HsTyVar NoExt NotPromoted n)) k
+ tyVarBndr2Type (XTyVarBndr _) = panic "haddock:ppCtor"
ppCtor dflags _dat subdocs con@(ConDeclGADT { })
= concatMap (lookupCon dflags subdocs) (getConNames con) ++ f
--
cgit v1.2.3
From a5199600c39d25d7b71dcb2328000c1c49ad95a2 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Wed, 6 Feb 2019 01:01:41 -0800
Subject: Better identifier parsing
* '(<|>)' and '`elem`' now get parsed and rendered properly as links
* 'DbModule'/'DbUnitId' now properly get split apart into two links
* tuple names now get parsed properly
* some more small niceties...
The identifier parsing code is more precise and more efficient (although to be
fair: it is also longer and in its own module). On the rendering side, we need
to pipe through information about backticks/parens/neither all the way through
from renaming to the backends.
In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc
lib docs change. The only "regression" is things like '\0'. These should be
changed to @\\0@ (the path by which this previously worked seems accidental).
---
doc/markup.rst | 9 +-
haddock-api/src/Haddock.hs | 2 +-
haddock-api/src/Haddock/Backends/Hoogle.hs | 2 +-
haddock-api/src/Haddock/Backends/LaTeX.hs | 19 +-
.../src/Haddock/Backends/Xhtml/DocMarkup.hs | 16 +-
haddock-api/src/Haddock/Backends/Xhtml/Names.hs | 28 +-
haddock-api/src/Haddock/Interface/Json.hs | 5 +-
haddock-api/src/Haddock/Interface/LexParseRn.hs | 58 +++--
haddock-api/src/Haddock/Interface/Rename.hs | 4 +-
haddock-api/src/Haddock/InterfaceFile.hs | 27 +-
haddock-api/src/Haddock/Parser.hs | 19 +-
haddock-api/src/Haddock/Types.hs | 28 +-
haddock-library/haddock-library.cabal | 2 +
.../src/Documentation/Haddock/Parser.hs | 63 +----
.../src/Documentation/Haddock/Parser/Identifier.hs | 186 ++++++++++++++
.../src/Documentation/Haddock/Parser/Monad.hs | 13 +-
.../test/Documentation/Haddock/ParserSpec.hs | 9 +-
haddock.cabal | 1 +
html-test/ref/Identifiers.html | 286 +++++++++++++++++++++
html-test/ref/Test.html | 2 +-
html-test/src/Identifiers.hs | 35 +++
21 files changed, 679 insertions(+), 135 deletions(-)
create mode 100644 haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
create mode 100644 html-test/ref/Identifiers.html
create mode 100644 html-test/src/Identifiers.hs
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/doc/markup.rst b/doc/markup.rst
index 48a6f4ad..56238855 100644
--- a/doc/markup.rst
+++ b/doc/markup.rst
@@ -932,14 +932,9 @@ necessary to escape the single quote when used as an apostrophe: ::
Nothing special is needed to hyperlink identifiers which contain
apostrophes themselves: to hyperlink ``foo'`` one would simply type
-``'foo''``. Hyperlinking operators works in exactly the same way.
+``'foo''``. Hyperlinking operators works in exactly the same way. ::
-Note that it is not possible to directly hyperlink an identifier in infix
-form or an operator in prefix form. The next best thing to do is to wrap
-the whole identifier in monospaced text and put the parentheses/backticks
-outside of the identifier, but inside the link: ::
-
- -- | A prefix operator @('++')@ and an infix identifier @\``elem`\`@.
+ -- | A prefix operator @'(++)'@ and an infix identifier @'`elem`'@.
Emphasis, Bold and Monospaced Text
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index 1378c173..3e0332b5 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -663,7 +663,7 @@ getPrologue dflags flags =
h <- openFile filename ReadMode
hSetEncoding h utf8
str <- hGetContents h -- semi-closes the handle
- return . Just $! second rdrName $ parseParas dflags Nothing str
+ return . Just $! second (fmap rdrName) $ parseParas dflags Nothing str
_ -> throwE "multiple -p/--prologue options"
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 9e3186e5..f581c01a 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -334,7 +334,7 @@ markupTag dflags = Markup {
markupString = str,
markupAppend = (++),
markupIdentifier = box (TagInline "a") . str . out dflags,
- markupIdentifierUnchecked = box (TagInline "a") . str . out dflags . snd,
+ markupIdentifierUnchecked = box (TagInline "a") . str . showWrapped (out dflags . snd),
markupModule = box (TagInline "a") . str,
markupWarning = box (TagInline "i"),
markupEmphasis = box (TagInline "i"),
diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs
index d0752506..85769b13 100644
--- a/haddock-api/src/Haddock/Backends/LaTeX.hs
+++ b/haddock-api/src/Haddock/Backends/LaTeX.hs
@@ -1106,8 +1106,8 @@ ppSymName name
| otherwise = ppName name
-ppVerbOccName :: OccName -> LaTeX
-ppVerbOccName = text . latexFilter . occNameString
+ppVerbOccName :: Wrap OccName -> LaTeX
+ppVerbOccName = text . latexFilter . showWrapped occNameString
ppIPName :: HsIPName -> LaTeX
ppIPName = text . ('?':) . unpackFS . hsIPNameFS
@@ -1115,13 +1115,12 @@ ppIPName = text . ('?':) . unpackFS . hsIPNameFS
ppOccName :: OccName -> LaTeX
ppOccName = text . occNameString
+ppVerbDocName :: Wrap DocName -> LaTeX
+ppVerbDocName = text . latexFilter . showWrapped (occNameString . nameOccName . getName)
-ppVerbDocName :: DocName -> LaTeX
-ppVerbDocName = ppVerbOccName . nameOccName . getName
-
-ppVerbRdrName :: RdrName -> LaTeX
-ppVerbRdrName = ppVerbOccName . rdrNameOcc
+ppVerbRdrName :: Wrap RdrName -> LaTeX
+ppVerbRdrName = text . latexFilter . showWrapped (occNameString . rdrNameOcc)
ppDocName :: DocName -> LaTeX
@@ -1182,7 +1181,7 @@ parLatexMarkup ppId = Markup {
markupString = \s v -> text (fixString v s),
markupAppend = \l r v -> l v <> r v,
markupIdentifier = markupId ppId,
- markupIdentifierUnchecked = markupId (ppVerbOccName . snd),
+ markupIdentifierUnchecked = markupId (ppVerbOccName . fmap snd),
markupModule = \m _ -> let (mdl,_ref) = break (=='#') m in tt (text mdl),
markupWarning = \p v -> emph (p v),
markupEmphasis = \p v -> emph (p v),
@@ -1239,11 +1238,11 @@ parLatexMarkup ppId = Markup {
where theid = ppId_ id
-latexMarkup :: DocMarkup DocName (StringContext -> LaTeX)
+latexMarkup :: DocMarkup (Wrap DocName) (StringContext -> LaTeX)
latexMarkup = parLatexMarkup ppVerbDocName
-rdrLatexMarkup :: DocMarkup RdrName (StringContext -> LaTeX)
+rdrLatexMarkup :: DocMarkup (Wrap RdrName) (StringContext -> LaTeX)
rdrLatexMarkup = parLatexMarkup ppVerbRdrName
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
index 09aabc0c..1901cf05 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
@@ -171,12 +171,12 @@ flatten x = [x]
-- extract/append the underlying 'Doc' and convert it to 'Html'. For
-- 'CollapsingHeader', we attach extra info to the generated 'Html'
-- that allows us to expand/collapse the content.
-hackMarkup :: DocMarkup id Html -> Maybe Package -> Hack (ModuleName, OccName) id -> Html
+hackMarkup :: DocMarkup id Html -> Maybe Package -> Hack (Wrap (ModuleName, OccName)) id -> Html
hackMarkup fmt' currPkg h' =
let (html, ms) = hackMarkup' fmt' h'
in html +++ renderMeta fmt' currPkg (metaConcat ms)
where
- hackMarkup' :: DocMarkup id Html -> Hack (ModuleName, OccName) id
+ hackMarkup' :: DocMarkup id Html -> Hack (Wrap (ModuleName, OccName)) id
-> (Html, [Meta])
hackMarkup' fmt h = case h of
UntouchedDoc d -> (markup fmt $ _doc d, [_meta d])
@@ -206,7 +206,7 @@ renderMeta _ _ _ = noHtml
-- | Goes through 'hackMarkup' to generate the 'Html' rather than
-- skipping straight to 'markup': this allows us to employ XHtml
-- specific hacks to the tree first.
-markupHacked :: DocMarkup id Html
+markupHacked :: DocMarkup (Wrap id) Html
-> Maybe Package -- this package
-> Maybe String
-> MDoc id
@@ -220,7 +220,7 @@ docToHtml :: Maybe String -- ^ Name of the thing this doc is for. See
-> Maybe Package -- ^ Current package
-> Qualification -> MDoc DocName -> Html
docToHtml n pkg qual = markupHacked fmt pkg n . cleanup
- where fmt = parHtmlMarkup qual True (ppDocName qual Raw)
+ where fmt = parHtmlMarkup qual True (ppWrappedDocName qual Raw)
-- | Same as 'docToHtml' but it doesn't insert the 'anchor' element
-- in links. This is used to generate the Contents box elements.
@@ -228,16 +228,16 @@ docToHtmlNoAnchors :: Maybe String -- ^ See 'toHack'
-> Maybe Package -- ^ Current package
-> Qualification -> MDoc DocName -> Html
docToHtmlNoAnchors n pkg qual = markupHacked fmt pkg n . cleanup
- where fmt = parHtmlMarkup qual False (ppDocName qual Raw)
+ where fmt = parHtmlMarkup qual False (ppWrappedDocName qual Raw)
origDocToHtml :: Maybe Package -> Qualification -> MDoc Name -> Html
origDocToHtml pkg qual = markupHacked fmt pkg Nothing . cleanup
- where fmt = parHtmlMarkup qual True (const $ ppName Raw)
+ where fmt = parHtmlMarkup qual True (const (ppWrappedName Raw))
rdrDocToHtml :: Maybe Package -> Qualification -> MDoc RdrName -> Html
rdrDocToHtml pkg qual = markupHacked fmt pkg Nothing . cleanup
- where fmt = parHtmlMarkup qual True (const ppRdrName)
+ where fmt = parHtmlMarkup qual True (const (ppRdrName . unwrap))
docElement :: (Html -> Html) -> Html -> Html
@@ -273,7 +273,7 @@ cleanup = overDoc (markup fmtUnParagraphLists)
unParagraph (DocParagraph d) = d
unParagraph doc = doc
- fmtUnParagraphLists :: DocMarkup a (Doc a)
+ fmtUnParagraphLists :: DocMarkup (Wrap a) (Doc a)
fmtUnParagraphLists = idMarkup {
markupUnorderedList = DocUnorderedList . map unParagraph,
markupOrderedList = DocOrderedList . map unParagraph
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
index 574045e0..6a047747 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
@@ -13,7 +13,8 @@
module Haddock.Backends.Xhtml.Names (
ppName, ppDocName, ppLDocName, ppRdrName, ppUncheckedLink,
ppBinder, ppBinderInfix, ppBinder',
- ppModule, ppModuleRef, ppIPName, linkId, Notation(..)
+ ppModule, ppModuleRef, ppIPName, linkId, Notation(..),
+ ppWrappedDocName, ppWrappedName,
) where
@@ -24,7 +25,7 @@ import Haddock.Utils
import Text.XHtml hiding ( name, p, quote )
import qualified Data.Map as M
-import qualified Data.List as List
+import Data.List ( stripPrefix )
import GHC hiding (LexicalFixity(..))
import Name
@@ -49,9 +50,11 @@ ppIPName :: HsIPName -> Html
ppIPName = toHtml . ('?':) . unpackFS . hsIPNameFS
-ppUncheckedLink :: Qualification -> (ModuleName, OccName) -> Html
-ppUncheckedLink _ (mdl, occ) = linkIdOcc' mdl (Just occ) << ppOccName occ -- TODO: apply ppQualifyName
-
+ppUncheckedLink :: Qualification -> Wrap (ModuleName, OccName) -> Html
+ppUncheckedLink _ x = linkIdOcc' mdl (Just occ) << occHtml
+ where
+ (mdl, occ) = unwrap x
+ occHtml = toHtml (showWrapped (occNameString . snd) x) -- TODO: apply ppQualifyName
-- The Bool indicates if it is to be rendered in infix notation
ppLDocName :: Qualification -> Notation -> Located DocName -> Html
@@ -68,6 +71,19 @@ ppDocName qual notation insertAnchors docName =
ppQualifyName qual notation name (nameModule name)
| otherwise -> ppName notation name
+
+ppWrappedDocName :: Qualification -> Notation -> Bool -> Wrap DocName -> Html
+ppWrappedDocName qual notation insertAnchors docName = case docName of
+ Unadorned n -> ppDocName qual notation insertAnchors n
+ Parenthesized n -> ppDocName qual Prefix insertAnchors n
+ Backticked n -> ppDocName qual Infix insertAnchors n
+
+ppWrappedName :: Notation -> Wrap Name -> Html
+ppWrappedName notation docName = case docName of
+ Unadorned n -> ppName notation n
+ Parenthesized n -> ppName Prefix n
+ Backticked n -> ppName Infix n
+
-- | Render a name depending on the selected qualification mode
ppQualifyName :: Qualification -> Notation -> Name -> Module -> Html
ppQualifyName qual notation name mdl =
@@ -79,7 +95,7 @@ ppQualifyName qual notation name mdl =
then ppName notation name
else ppFullQualName notation mdl name
RelativeQual localmdl ->
- case List.stripPrefix (moduleString localmdl) (moduleString mdl) of
+ case stripPrefix (moduleString localmdl) (moduleString mdl) of
-- local, A.x -> x
Just [] -> ppName notation name
-- sub-module, A.B.x -> B.x
diff --git a/haddock-api/src/Haddock/Interface/Json.hs b/haddock-api/src/Haddock/Interface/Json.hs
index 636d3e19..a9834fa0 100644
--- a/haddock-api/src/Haddock/Interface/Json.hs
+++ b/haddock-api/src/Haddock/Interface/Json.hs
@@ -62,7 +62,10 @@ jsonMDoc MetaDoc{..} =
]
jsonDoc :: Doc Name -> JsonDoc
-jsonDoc doc = jsonString (show (bimap (moduleNameString . fst) nameStableString doc))
+jsonDoc doc = jsonString (show (bimap showModName showName doc))
+ where
+ showModName = showWrapped (moduleNameString . fst)
+ showName = showWrapped nameStableString
jsonModule :: Module -> JsonDoc
jsonModule = JSString . moduleStableString
diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs
index 66083cf5..faf23728 100644
--- a/haddock-api/src/Haddock/Interface/LexParseRn.hs
+++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs
@@ -22,6 +22,7 @@ module Haddock.Interface.LexParseRn
import Avail
import Control.Arrow
import Control.Monad
+import Data.Functor (($>))
import Data.List
import Data.Ord
import Documentation.Haddock.Doc (metaDocConcat)
@@ -95,8 +96,9 @@ rename dflags gre = rn
rn d = case d of
DocAppend a b -> DocAppend <$> rn a <*> rn b
DocParagraph doc -> DocParagraph <$> rn doc
- DocIdentifier (NsRdrName ns x) -> do
- let occ = rdrNameOcc x
+ DocIdentifier i -> do
+ let NsRdrName ns x = unwrap i
+ occ = rdrNameOcc x
isValueName = isDataOcc occ || isVarOcc occ
let valueNsChoices | isValueName = [x]
@@ -119,7 +121,7 @@ rename dflags gre = rn
case choices of
-- The only way this can happen is if a value namespace was
-- specified on something that cannot be a value.
- [] -> invalidValue dflags x
+ [] -> invalidValue dflags i
-- There was nothing in the environment so we need to
-- pick some default from what's available to us. We
@@ -129,14 +131,14 @@ rename dflags gre = rn
-- type constructor names (such as in #253). So now we
-- only get type constructor links if they are actually
-- in scope.
- a:_ -> outOfScope dflags ns a
+ a:_ -> outOfScope dflags ns (i $> a)
-- There is only one name in the environment that matches so
-- use it.
- [a] -> pure (DocIdentifier (gre_name a))
+ [a] -> pure (DocIdentifier (i $> gre_name a))
-- There are multiple names available.
- gres -> ambiguous dflags x gres
+ gres -> ambiguous dflags i gres
DocWarning doc -> DocWarning <$> rn doc
DocEmphasis doc -> DocEmphasis <$> rn doc
@@ -168,13 +170,13 @@ rename dflags gre = rn
-- users shouldn't rely on this doing the right thing. See tickets
-- #253 and #375 on the confusion this causes depending on which
-- default we pick in 'rename'.
-outOfScope :: DynFlags -> Namespace -> RdrName -> ErrMsgM (Doc a)
+outOfScope :: DynFlags -> Namespace -> Wrap RdrName -> ErrMsgM (Doc a)
outOfScope dflags ns x =
- case x of
- Unqual occ -> warnAndMonospace occ
- Qual mdl occ -> pure (DocIdentifierUnchecked (mdl, occ))
- Orig _ occ -> warnAndMonospace occ
- Exact name -> warnAndMonospace name -- Shouldn't happen since x is out of scope
+ case unwrap x of
+ Unqual occ -> warnAndMonospace (x $> occ)
+ Qual mdl occ -> pure (DocIdentifierUnchecked (x $> (mdl, occ)))
+ Orig _ occ -> warnAndMonospace (x $> occ)
+ Exact name -> warnAndMonospace (x $> name) -- Shouldn't happen since x is out of scope
where
prefix = case ns of
Value -> "the value "
@@ -182,11 +184,11 @@ outOfScope dflags ns x =
None -> ""
warnAndMonospace a = do
- tell ["Warning: " ++ prefix ++ "'" ++ showPpr dflags a ++ "' is out of scope.\n" ++
- " If you qualify the identifier, haddock can try to link it\n" ++
- " it anyway."]
- pure (monospaced a)
- monospaced a = DocMonospaced (DocString (showPpr dflags a))
+ let a' = showWrapped (showPpr dflags) a
+ tell ["Warning: " ++ prefix ++ "'" ++ a' ++ "' is out of scope.\n" ++
+ " If you qualify the identifier, haddock can try to link it anyway."]
+ pure (monospaced a')
+ monospaced = DocMonospaced . DocString
-- | Handle ambiguous identifiers.
--
@@ -194,36 +196,42 @@ outOfScope dflags ns x =
--
-- Emits a warning if the 'GlobalRdrElts's don't belong to the same type or class.
ambiguous :: DynFlags
- -> RdrName
+ -> Wrap NsRdrName
-> [GlobalRdrElt] -- ^ More than one @gre@s sharing the same `RdrName` above.
-> ErrMsgM (Doc Name)
ambiguous dflags x gres = do
let noChildren = map availName (gresToAvailInfo gres)
dflt = maximumBy (comparing (isLocalName &&& isTyConName)) noChildren
- msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++
+ msg = "Warning: " ++ showNsRdrName dflags x ++ " is ambiguous. It is defined\n" ++
concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map gre_name gres) ++
" You may be able to disambiguate the identifier by qualifying it or\n" ++
" by specifying the type/value namespace explicitly.\n" ++
- " Defaulting to " ++ x_str ++ " defined " ++ defnLoc dflt
+ " Defaulting to the one defined " ++ defnLoc dflt
-- TODO: Once we have a syntax for namespace qualification (#667) we may also
-- want to emit a warning when an identifier is a data constructor for a type
-- of the same name, but not the only constructor.
-- For example, for @data D = C | D@, someone may want to reference the @D@
-- constructor.
when (length noChildren > 1) $ tell [msg]
- pure (DocIdentifier dflt)
+ pure (DocIdentifier (x $> dflt))
where
isLocalName (nameSrcLoc -> RealSrcLoc {}) = True
isLocalName _ = False
- x_str = '\'' : showPpr dflags x ++ "'"
defnLoc = showSDoc dflags . pprNameDefnLoc
-- | Handle value-namespaced names that cannot be for values.
--
-- Emits a warning that the value-namespace is invalid on a non-value identifier.
-invalidValue :: DynFlags -> RdrName -> ErrMsgM (Doc a)
+invalidValue :: DynFlags -> Wrap NsRdrName -> ErrMsgM (Doc a)
invalidValue dflags x = do
- tell ["Warning: '" ++ showPpr dflags x ++ "' cannot be value, yet it is\n" ++
+ tell ["Warning: " ++ showNsRdrName dflags x ++ " cannot be value, yet it is\n" ++
" namespaced as such. Did you mean to specify a type namespace\n" ++
" instead?"]
- pure (DocMonospaced (DocString (showPpr dflags x)))
+ pure (DocMonospaced (DocString (showNsRdrName dflags x)))
+
+-- | Printable representation of a wrapped and namespaced name
+showNsRdrName :: DynFlags -> Wrap NsRdrName -> String
+showNsRdrName dflags = (\p i -> p ++ "'" ++ i ++ "'") <$> prefix <*> ident
+ where
+ ident = showWrapped (showPpr dflags . rdrName)
+ prefix = renderNs . namespace . unwrap
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 57e6d699..88238f04 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -173,8 +173,8 @@ renameLDocHsSyn :: LHsDocString -> RnM LHsDocString
renameLDocHsSyn = return
-renameDoc :: Traversable t => t Name -> RnM (t DocName)
-renameDoc = traverse rename
+renameDoc :: Traversable t => t (Wrap Name) -> RnM (t (Wrap DocName))
+renameDoc = traverse (traverse rename)
renameFnArgsDoc :: FnArgsDoc Name -> RnM (FnArgsDoc DocName)
renameFnArgsDoc = mapM renameDoc
diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs
index e1d8dbe1..7645b1bb 100644
--- a/haddock-api/src/Haddock/InterfaceFile.hs
+++ b/haddock-api/src/Haddock/InterfaceFile.hs
@@ -83,7 +83,7 @@ binaryInterfaceMagic = 0xD0Cface
--
binaryInterfaceVersion :: Word16
#if (__GLASGOW_HASKELL__ >= 807) && (__GLASGOW_HASKELL__ < 809)
-binaryInterfaceVersion = 34
+binaryInterfaceVersion = 35
binaryInterfaceVersionCompatibility :: [Word16]
binaryInterfaceVersionCompatibility = [binaryInterfaceVersion]
@@ -701,3 +701,28 @@ instance Binary DocName where
name <- get bh
return (Undocumented name)
_ -> error "get DocName: Bad h"
+
+instance Binary n => Binary (Wrap n) where
+ put_ bh (Unadorned n) = do
+ putByte bh 0
+ put_ bh n
+ put_ bh (Parenthesized n) = do
+ putByte bh 1
+ put_ bh n
+ put_ bh (Backticked n) = do
+ putByte bh 2
+ put_ bh n
+
+ get bh = do
+ h <- getByte bh
+ case h of
+ 0 -> do
+ name <- get bh
+ return (Unadorned name)
+ 1 -> do
+ name <- get bh
+ return (Parenthesized name)
+ 2 -> do
+ name <- get bh
+ return (Backticked name)
+ _ -> error "get Wrap: Bad h"
diff --git a/haddock-api/src/Haddock/Parser.hs b/haddock-api/src/Haddock/Parser.hs
index 8b7dda7c..6d5dc103 100644
--- a/haddock-api/src/Haddock/Parser.hs
+++ b/haddock-api/src/Haddock/Parser.hs
@@ -15,27 +15,32 @@ module Haddock.Parser ( parseParas
import qualified Documentation.Haddock.Parser as P
import Documentation.Haddock.Types
-import Haddock.Types (NsRdrName(..))
+import Haddock.Types
import DynFlags ( DynFlags )
import FastString ( fsLit )
import Lexer ( mkPState, unP, ParseResult(POk) )
import Parser ( parseIdentifier )
-import RdrName ( RdrName )
import SrcLoc ( mkRealSrcLoc, GenLocated(..) )
import StringBuffer ( stringToStringBuffer )
-parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod NsRdrName
+
+parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod (Wrap NsRdrName)
parseParas d p = overDoc (P.overIdentifier (parseIdent d)) . P.parseParas p
-parseString :: DynFlags -> String -> DocH mod NsRdrName
+parseString :: DynFlags -> String -> DocH mod (Wrap NsRdrName)
parseString d = P.overIdentifier (parseIdent d) . P.parseString
-parseIdent :: DynFlags -> Namespace -> String -> Maybe NsRdrName
+parseIdent :: DynFlags -> Namespace -> String -> Maybe (Wrap NsRdrName)
parseIdent dflags ns str0 =
- let buffer = stringToStringBuffer str0
+ let buffer = stringToStringBuffer str1
realSrcLc = mkRealSrcLoc (fsLit "") 0 0
pstate = mkPState dflags buffer realSrcLc
+ (wrap,str1) = case str0 of
+ '(' : s@(c : _) | c /= ',', c /= ')' -- rule out tuple names
+ -> (Parenthesized, init s)
+ '`' : s@(_ : _) -> (Backticked, init s)
+ _ -> (Unadorned, str0)
in case unP parseIdentifier pstate of
- POk _ (L _ name) -> Just (NsRdrName ns name)
+ POk _ (L _ name) -> Just (wrap (NsRdrName ns name))
_ -> Nothing
diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs
index e8da4120..cd4ac1a1 100644
--- a/haddock-api/src/Haddock/Types.hs
+++ b/haddock-api/src/Haddock/Types.hs
@@ -42,7 +42,7 @@ import GHC
import DynFlags (Language)
import qualified GHC.LanguageExtensions as LangExt
import OccName
-import Outputable
+import Outputable hiding ((<>))
-----------------------------------------------------------------------------
-- * Convenient synonyms
@@ -334,6 +334,26 @@ instance SetName DocName where
setName name' (Documented _ mdl) = Documented name' mdl
setName name' (Undocumented _) = Undocumented name'
+-- | Adds extra "wrapper" information to a name.
+--
+-- This is to work around the fact that most name types in GHC ('Name', 'RdrName',
+-- 'OccName', ...) don't include backticks or parens.
+data Wrap n
+ = Unadorned { unwrap :: n } -- ^ don't do anything to the name
+ | Parenthesized { unwrap :: n } -- ^ add parentheses around the name
+ | Backticked { unwrap :: n } -- ^ add backticks around the name
+ deriving (Show, Functor, Foldable, Traversable)
+
+-- | Useful for debugging
+instance Outputable n => Outputable (Wrap n) where
+ ppr (Unadorned n) = ppr n
+ ppr (Parenthesized n) = hcat [ char '(', ppr n, char ')' ]
+ ppr (Backticked n) = hcat [ char '`', ppr n, char '`' ]
+
+showWrapped :: (a -> String) -> Wrap a -> String
+showWrapped f (Unadorned n) = f n
+showWrapped f (Parenthesized n) = "(" ++ f n ++ ")"
+showWrapped f (Backticked n) = "`" ++ f n ++ "`"
-----------------------------------------------------------------------------
@@ -429,10 +449,10 @@ instance NamedThing name => NamedThing (InstOrigin name) where
type LDoc id = Located (Doc id)
-type Doc id = DocH (ModuleName, OccName) id
-type MDoc id = MetaDoc (ModuleName, OccName) id
+type Doc id = DocH (Wrap (ModuleName, OccName)) (Wrap id)
+type MDoc id = MetaDoc (Wrap (ModuleName, OccName)) (Wrap id)
-type DocMarkup id a = DocMarkupH (ModuleName, OccName) id a
+type DocMarkup id a = DocMarkupH (Wrap (ModuleName, OccName)) id a
instance (NFData a, NFData mod)
=> NFData (DocH mod a) where
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index b24db5d4..5475d61b 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -49,6 +49,7 @@ library
other-modules:
Documentation.Haddock.Parser.Util
Documentation.Haddock.Parser.Monad
+ Documentation.Haddock.Parser.Identifier
test-suite spec
import: lib-defaults
@@ -70,6 +71,7 @@ test-suite spec
Documentation.Haddock.Parser.UtilSpec
Documentation.Haddock.ParserSpec
Documentation.Haddock.Types
+ Documentation.Haddock.Parser.Identifier
build-depends:
, base-compat ^>= 0.9.3 || ^>= 0.10.0
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index e9b1c496..36c8bb5b 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -27,8 +27,7 @@ module Documentation.Haddock.Parser (
import Control.Applicative
import Control.Arrow (first)
import Control.Monad
-import Data.Char (chr, isUpper, isAlpha, isAlphaNum, isSpace)
-import Data.Foldable (asum)
+import Data.Char (chr, isUpper, isAlpha, isSpace)
import Data.List (intercalate, unfoldr, elemIndex)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Monoid
@@ -37,6 +36,7 @@ import Documentation.Haddock.Doc
import Documentation.Haddock.Markup ( markup, plainMarkup )
import Documentation.Haddock.Parser.Monad
import Documentation.Haddock.Parser.Util
+import Documentation.Haddock.Parser.Identifier
import Documentation.Haddock.Types
import Prelude hiding (takeWhile)
import qualified Prelude as P
@@ -47,37 +47,10 @@ import Text.Parsec (try)
import qualified Data.Text as T
import Data.Text (Text)
-#if MIN_VERSION_base(4,9,0)
-import Text.Read.Lex (isSymbolChar)
-#else
-import Data.Char (GeneralCategory (..),
- generalCategory)
-#endif
-- $setup
-- >>> :set -XOverloadedStrings
-#if !MIN_VERSION_base(4,9,0)
--- inlined from base-4.10.0.0
-isSymbolChar :: Char -> Bool
-isSymbolChar c = not (isPuncChar c) && case generalCategory c of
- MathSymbol -> True
- CurrencySymbol -> True
- ModifierSymbol -> True
- OtherSymbol -> True
- DashPunctuation -> True
- OtherPunctuation -> c `notElem` ("'\"" :: String)
- ConnectorPunctuation -> c /= '_'
- _ -> False
- where
- -- | The @special@ character class as defined in the Haskell Report.
- isPuncChar :: Char -> Bool
- isPuncChar = (`elem` (",;()[]{}`" :: String))
-#endif
-
--- | Identifier string surrounded with opening and closing quotes/backticks.
-data Identifier = Identifier !Namespace !Char String !Char
-
-- | Drops the quotes/backticks around all identifiers, as if they
-- were valid but still 'String's.
toRegular :: DocH mod Identifier -> DocH mod String
@@ -838,34 +811,6 @@ autoUrl = mkLink <$> url
mkHyperlink lnk = Hyperlink (T.unpack lnk) Nothing
-
--- | Parses strings between identifier delimiters. Consumes all input that it
--- deems to be valid in an identifier. Note that it simply blindly consumes
--- characters and does no actual validation itself.
-parseValid :: Parser String
-parseValid = p some
- where
- idChar = Parsec.satisfy (\c -> isAlphaNum c || isSymbolChar c || c == '_')
-
- p p' = do
- vs <- p' idChar
- c <- peekChar'
- case c of
- '`' -> return vs
- '\'' -> choice' [ (\x -> vs ++ "'" ++ x) <$> ("'" *> p many), return vs ]
- _ -> fail "outofvalid"
-
--- | Parses identifiers with help of 'parseValid'. Asks GHC for
--- 'String' from the string it deems valid.
+-- | Parses identifiers with help of 'parseValid'.
identifier :: Parser (DocH mod Identifier)
-identifier = do
- ns <- asum [ Value <$ Parsec.char 'v'
- , Type <$ Parsec.char 't'
- , pure None
- ]
- o <- idDelim
- vid <- parseValid
- e <- idDelim
- return $ DocIdentifier (Identifier ns o vid e)
- where
- idDelim = Parsec.oneOf "'`"
+identifier = DocIdentifier <$> parseValid
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
new file mode 100644
index 00000000..7bc98b62
--- /dev/null
+++ b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
@@ -0,0 +1,186 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE ViewPatterns #-}
+-- |
+-- Module : Documentation.Haddock.Parser.Identifier
+-- Copyright : (c) Alec Theriault 2019,
+-- License : BSD-like
+--
+-- Maintainer : haddock@projects.haskell.org
+-- Stability : experimental
+-- Portability : portable
+--
+-- Functionality for parsing identifiers and operators
+
+module Documentation.Haddock.Parser.Identifier (
+ Identifier(..),
+ parseValid,
+) where
+
+import Documentation.Haddock.Types ( Namespace(..) )
+import Documentation.Haddock.Parser.Monad
+import qualified Text.Parsec as Parsec
+import Text.Parsec.Pos ( updatePosChar )
+import Text.Parsec ( State(..)
+ , getParserState, setParserState )
+
+import Data.Text (Text)
+import qualified Data.Text as T
+
+import Data.Char (isAlpha, isAlphaNum)
+import Control.Monad (guard)
+import Data.Functor (($>))
+#if MIN_VERSION_base(4,9,0)
+import Text.Read.Lex (isSymbolChar)
+#else
+import Data.Char (GeneralCategory (..),
+ generalCategory)
+#endif
+
+import Data.Maybe
+
+-- | Identifier string surrounded with namespace, opening, and closing quotes/backticks.
+data Identifier = Identifier !Namespace !Char String !Char
+ deriving (Show, Eq)
+
+parseValid :: Parser Identifier
+parseValid = do
+ s@State{ stateInput = inp, statePos = pos } <- getParserState
+
+ case takeIdentifier inp of
+ Nothing -> Parsec.parserFail "parseValid: Failed to match a valid identifier"
+ Just (ns, op, ident, cl, inp') ->
+ let posOp = updatePosChar pos op
+ posIdent = T.foldl updatePosChar posOp ident
+ posCl = updatePosChar posIdent cl
+ s' = s{ stateInput = inp', statePos = posCl }
+ in setParserState s' $> Identifier ns op (T.unpack ident) cl
+
+
+#if !MIN_VERSION_base(4,9,0)
+-- inlined from base-4.10.0.0
+isSymbolChar :: Char -> Bool
+isSymbolChar c = not (isPuncChar c) && case generalCategory c of
+ MathSymbol -> True
+ CurrencySymbol -> True
+ ModifierSymbol -> True
+ OtherSymbol -> True
+ DashPunctuation -> True
+ OtherPunctuation -> c `notElem` "'\""
+ ConnectorPunctuation -> c /= '_'
+ _ -> False
+ where
+ -- | The @special@ character class as defined in the Haskell Report.
+ isPuncChar :: Char -> Bool
+ isPuncChar = (`elem` (",;()[]{}`" :: String))
+#endif
+
+-- | Try to parse a delimited identifier off the front of the given input.
+--
+-- This tries to match as many valid Haskell identifiers/operators as possible,
+-- to the point of sometimes accepting invalid things (ex: keywords). Some
+-- considerations:
+--
+-- - operators and identifiers can have module qualifications
+-- - operators can be wrapped in parens (for prefix)
+-- - identifiers can be wrapped in backticks (for infix)
+-- - delimiters are backticks or regular ticks
+-- - since regular ticks are also valid in identifiers, we opt for the
+-- longest successful parse
+--
+-- This function should make /O(1)/ allocations
+takeIdentifier :: Text -> Maybe (Namespace, Char, Text, Char, Text)
+takeIdentifier input = listToMaybe $ do
+
+ -- Optional namespace
+ let (ns, input') = case T.uncons input of
+ Just ('v', i) -> (Value, i)
+ Just ('t', i) -> (Type, i)
+ _ -> (None, input)
+
+ -- Opening tick
+ (op, input'') <- maybeToList (T.uncons input')
+ guard (op == '\'' || op == '`')
+
+ -- Identifier/operator
+ (ident, input''') <- wrapped input''
+
+ -- Closing tick
+ (cl, input'''') <- maybeToList (T.uncons input''')
+ guard (cl == '\'' || cl == '`')
+
+ pure (ns, op, ident, cl, input'''')
+
+ where
+
+ -- | Parse out a wrapped, possibly qualified, operator or identifier
+ wrapped t = do
+ (c, t' ) <- maybeToList (T.uncons t)
+ -- Tuples
+ case c of
+ '(' | Just (c', _) <- T.uncons t'
+ , c' == ',' || c' == ')'
+ -> do let (commas, t'') = T.span (== ',') t'
+ (')', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (T.length commas + 2) t, t''')
+
+ -- Parenthesized
+ '(' -> do (n, t'' ) <- general False 0 [] t'
+ (')', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (n + 2) t, t''')
+
+ -- Backticked
+ '`' -> do (n, t'' ) <- general False 0 [] t'
+ ('`', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (n + 2) t, t''')
+
+ -- Unadorned
+ _ -> do (n, t'' ) <- general False 0 [] t
+ pure (T.take n t, t'')
+
+ -- | Parse out a possibly qualified operator or identifier
+ general :: Bool -- ^ refuse inputs starting with operators
+ -> Int -- ^ total characters \"consumed\" so far
+ -> [(Int, Text)] -- ^ accumulated results
+ -> Text -- ^ current input
+ -> [(Int, Text)] -- ^ total characters parsed & what remains
+ general !identOnly !i acc t
+ -- Starts with an identifier (either just an identifier, or a module qual)
+ | Just (n, rest) <- identLike t
+ = if T.null rest
+ then acc
+ else case T.head rest of
+ '`' -> (n + i, rest) : acc
+ ')' -> (n + i, rest) : acc
+ '.' -> general False (n + i + 1) acc (T.tail rest)
+ '\'' -> let (m, rest') = quotes rest
+ in general True (n + m + 1 + i) ((n + m + i, rest') : acc) (T.tail rest')
+ _ -> acc
+
+ -- An operator
+ | Just (n, rest) <- optr t
+ , not identOnly
+ = (n + i, rest) : acc
+
+ -- Anything else
+ | otherwise
+ = acc
+
+ -- | Parse an identifier off the front of the input
+ identLike t
+ | T.null t = Nothing
+ | isAlpha (T.head t) || '_' == T.head t
+ = let !(idt, rest) = T.span (\c -> isAlphaNum c || c == '_') t
+ !(octos, rest') = T.span (== '#') rest
+ in Just (T.length idt + T.length octos, rest')
+ | otherwise = Nothing
+
+ -- | Parse all but the last quote off the front of the input
+ -- PRECONDITION: T.head t == '\''
+ quotes :: Text -> (Int, Text)
+ quotes t = let !n = T.length (T.takeWhile (== '\'') t) - 1
+ in (n, T.drop n t)
+
+ -- | Parse an operator off the front of the input
+ optr t = let !(op, rest) = T.span isSymbolChar t
+ in if T.null op then Nothing else Just (T.length op, rest)
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
index 8f5bd217..fa46f536 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
@@ -4,6 +4,18 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances #-}
+-- |
+-- Module : Documentation.Haddock.Parser.Monad
+-- Copyright : (c) Alec Theriault 2018-2019,
+-- License : BSD-like
+--
+-- Maintainer : haddock@projects.haskell.org
+-- Stability : experimental
+-- Portability : portable
+--
+-- Defines the Parsec monad over which all parsing is done and also provides
+-- more efficient versions of the usual parsec combinator functions (but
+-- specialized to 'Text').
module Documentation.Haddock.Parser.Monad where
@@ -96,7 +108,6 @@ takeWhile f = do
s' = s{ stateInput = inp', statePos = pos' }
setParserState s' $> t
-
-- | Like 'takeWhile', but fails if no characters matched.
--
-- Equivalent to @fmap T.pack . Parsec.many1@, but more efficient.
diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
index e186a5cf..bc40a0a2 100644
--- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs
+++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
@@ -112,7 +112,7 @@ spec = do
"``" `shouldParseTo` "``"
it "can parse an identifier in infix notation enclosed within backticks" $ do
- "``infix``" `shouldParseTo` "`" <> DocIdentifier "infix" <> "`"
+ "``infix``" `shouldParseTo` DocIdentifier "`infix`"
it "can parse identifiers containing a single quote" $ do
"'don't'" `shouldParseTo` DocIdentifier "don't"
@@ -138,6 +138,13 @@ spec = do
it "can parse type-namespaced identifiers" $ do
"t'foo'" `shouldParseTo` DocIdentifier "foo"
+ it "can parse parenthesized operators and backticked identifiers" $ do
+ "'(<|>)'" `shouldParseTo` DocIdentifier "(<|>)"
+ "'`elem`'" `shouldParseTo` DocIdentifier "`elem`"
+
+ it "can properly figure out the end of identifiers" $ do
+ "'DbModule'/'DbUnitId'" `shouldParseTo` DocIdentifier "DbModule" <> "/" <> DocIdentifier "DbUnitId"
+
context "when parsing operators" $ do
it "can parse an operator enclosed within single quotes" $ do
"'.='" `shouldParseTo` DocIdentifier ".="
diff --git a/haddock.cabal b/haddock.cabal
index 2b8ee6ff..91a5ea3d 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -89,6 +89,7 @@ executable haddock
other-modules:
Documentation.Haddock.Parser
Documentation.Haddock.Parser.Monad
+ Documentation.Haddock.Parser.Identifier
Documentation.Haddock.Types
Documentation.Haddock.Doc
Documentation.Haddock.Parser.Util
diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html
new file mode 100644
index 00000000..1a0a18a5
--- /dev/null
+++ b/html-test/ref/Identifiers.html
@@ -0,0 +1,286 @@
+Identifiers
diff --git a/html-test/ref/Test.html b/html-test/ref/Test.html
index b76622e7..aefc4d14 100644
--- a/html-test/ref/Test.html
+++ b/html-test/ref/Test.html
@@ -2364,7 +2364,7 @@ is at the beginning of the line).f'
- but f' doesn't get link'd 'f\''
Date: Sun, 22 Mar 2020 11:46:42 -0400
Subject: Clean up warnings
* unused imports
* imports of `Data.List` without import lists
* missing `CompatPrelude` file in `.cabal`
---
haddock-api/src/Haddock/Backends/Hoogle.hs | 3 +--
haddock-api/src/Haddock/Backends/LaTeX.hs | 9 +-------
haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 1 -
.../src/Haddock/Backends/Xhtml/DocMarkup.hs | 2 +-
haddock-api/src/Haddock/Interface.hs | 2 +-
.../src/Haddock/Interface/AttachInstances.hs | 2 +-
haddock-api/src/Haddock/Interface/Create.hs | 2 +-
haddock-api/src/Haddock/Interface/LexParseRn.hs | 2 +-
haddock-api/src/Haddock/Interface/Rename.hs | 2 --
haddock-api/src/Haddock/InterfaceFile.hs | 2 +-
haddock-api/src/Haddock/Utils.hs | 1 -
haddock-api/src/Haddock/Utils/Json.hs | 2 +-
haddock-library/haddock-library.cabal | 26 ++++++++++------------
haddock.cabal | 1 +
14 files changed, 22 insertions(+), 35 deletions(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 1f98ef9c..b38d4047 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -27,10 +27,9 @@ import Haddock.Utils hiding (out)
import GHC
import Outputable
-import NameSet
import Data.Char
-import Data.List
+import Data.List (isPrefixOf, intercalate)
import Data.Maybe
import Data.Version
diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs
index f2fb1041..63b12a14 100644
--- a/haddock-api/src/Haddock/Backends/LaTeX.hs
+++ b/haddock-api/src/Haddock/Backends/LaTeX.hs
@@ -38,7 +38,7 @@ import System.FilePath
import Data.Char
import Control.Monad
import Data.Maybe
-import Data.List
+import Data.List ( sort )
import Prelude hiding ((<>))
import Haddock.Doc (combineDocumentation)
@@ -517,12 +517,6 @@ ppSubSigLike unicode typ argDocs subdocs leader = do_args 0 leader typ
gadtOpen = char '{'
-ppForAllSeparator :: Bool -> ForallVisFlag -> LaTeX
-ppForAllSeparator unicode fvf =
- case fvf of
- ForallVis -> text "\\ " <> arrow unicode
- ForallInvis -> dot
-
ppTypeSig :: [Name] -> HsType DocNameI -> Bool -> LaTeX
ppTypeSig nms ty unicode =
hsep (punctuate comma $ map ppSymName nms)
@@ -1063,7 +1057,6 @@ ppForAllPart unicode tvs fvf = hsep (forallSymbol unicode : tvs') <> fv
ForallVis -> text "\\ " <> arrow unicode
ForallInvis -> dot
-
ppr_mono_lty :: LHsType DocNameI -> Bool -> LaTeX
ppr_mono_lty ty unicode = ppr_mono_ty (unLoc ty) unicode
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
index c7ae15ca..b450dc94 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
@@ -36,7 +36,6 @@ import Text.XHtml hiding ( name, title, p, quote )
import BasicTypes (PromotionFlag(..), isPromoted)
import GHC hiding (LexicalFixity(..))
-import qualified GHC
import GHC.Exts
import Name
import BooleanFormula
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
index edab4b16..0d7accfc 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
@@ -19,7 +19,7 @@ module Haddock.Backends.Xhtml.DocMarkup (
docElement, docSection, docSection_,
) where
-import Data.List
+import Data.List (intersperse)
import Documentation.Haddock.Markup
import Haddock.Backends.Xhtml.Names
import Haddock.Backends.Xhtml.Utils
diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs
index c2c0d733..24568235 100644
--- a/haddock-api/src/Haddock/Interface.hs
+++ b/haddock-api/src/Haddock/Interface.hs
@@ -44,7 +44,7 @@ import Haddock.Utils
import Control.Monad
import Control.Exception (evaluate)
-import Data.List
+import Data.List (foldl', isPrefixOf, nub)
import qualified Data.Map as Map
import qualified Data.Set as Set
import Text.Printf
diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs
index 35f24ee5..685dca01 100644
--- a/haddock-api/src/Haddock/Interface/AttachInstances.hs
+++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs
@@ -21,7 +21,7 @@ import Haddock.GhcUtils
import Control.Applicative ((<|>))
import Control.Arrow hiding ((<+>))
-import Data.List
+import Data.List (sortBy)
import Data.Ord (comparing)
import Data.Maybe ( maybeToList, mapMaybe, fromMaybe )
import qualified Data.Map as Map
diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index d5cbdaf5..b182a615 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -32,7 +32,7 @@ import Data.Bifunctor
import Data.Bitraversable
import qualified Data.Map as M
import Data.Map (Map)
-import Data.List
+import Data.List (find, foldl', sortBy)
import Data.Maybe
import Data.Ord
import Control.Applicative
diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs
index 0b40ed3c..08a3c0f8 100644
--- a/haddock-api/src/Haddock/Interface/LexParseRn.hs
+++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs
@@ -22,7 +22,7 @@ module Haddock.Interface.LexParseRn
import Control.Arrow
import Control.Monad
import Data.Functor (($>))
-import Data.List
+import Data.List (maximumBy, (\\))
import Data.Ord
import Documentation.Haddock.Doc (metaDocConcat)
import DynFlags (languageExtensions)
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 72d063dc..0b122b07 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -22,14 +22,12 @@ import Haddock.Types
import Bag (emptyBag)
import GHC hiding (NoLink)
import Name
-import Outputable ( panic )
import RdrName (RdrName(Exact))
import TysWiredIn (eqTyCon_RDR)
import Control.Applicative
import Control.Arrow ( first )
import Control.Monad hiding (mapM)
-import Data.List
import qualified Data.Map as Map hiding ( Map )
import Prelude hiding (mapM)
diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs
index b5be311a..3ce2fabb 100644
--- a/haddock-api/src/Haddock/InterfaceFile.hs
+++ b/haddock-api/src/Haddock/InterfaceFile.hs
@@ -26,7 +26,7 @@ import Haddock.Utils hiding (out)
import Control.Monad
import Data.Array
import Data.IORef
-import Data.List
+import Data.List (mapAccumR)
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Word
diff --git a/haddock-api/src/Haddock/Utils.hs b/haddock-api/src/Haddock/Utils.hs
index 79673365..3eb702c9 100644
--- a/haddock-api/src/Haddock/Utils.hs
+++ b/haddock-api/src/Haddock/Utils.hs
@@ -65,7 +65,6 @@ import BasicTypes ( PromotionFlag(..) )
import Exception (ExceptionMonad)
import GHC
import Name
-import Outputable ( panic )
import Control.Monad ( liftM )
import Data.Char ( isAlpha, isAlphaNum, isAscii, ord, chr )
diff --git a/haddock-api/src/Haddock/Utils/Json.hs b/haddock-api/src/Haddock/Utils/Json.hs
index e3c3dddc..2270a547 100644
--- a/haddock-api/src/Haddock/Utils/Json.hs
+++ b/haddock-api/src/Haddock/Utils/Json.hs
@@ -19,7 +19,7 @@ import Data.Char
import Data.Int
import Data.String
import Data.Word
-import Data.List
+import Data.List (intersperse)
import Data.Monoid
import Data.ByteString.Builder (Builder)
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index e58fe2ef..294ef5be 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -59,22 +59,20 @@ test-suite spec
type: exitcode-stdio-1.0
main-is: Spec.hs
hs-source-dirs:
- test
- src
-
- cpp-options:
- -DTEST
+ test
+ src
other-modules:
- Documentation.Haddock.Doc
- Documentation.Haddock.Markup
- Documentation.Haddock.Parser
- Documentation.Haddock.Parser.Monad
- Documentation.Haddock.Parser.Util
- Documentation.Haddock.Parser.UtilSpec
- Documentation.Haddock.ParserSpec
- Documentation.Haddock.Types
- Documentation.Haddock.Parser.Identifier
+ CompatPrelude
+ Documentation.Haddock.Doc
+ Documentation.Haddock.Markup
+ Documentation.Haddock.Parser
+ Documentation.Haddock.Parser.Monad
+ Documentation.Haddock.Parser.Util
+ Documentation.Haddock.Parser.UtilSpec
+ Documentation.Haddock.ParserSpec
+ Documentation.Haddock.Types
+ Documentation.Haddock.Parser.Identifier
build-depends:
, base-compat ^>= 0.9.3 || ^>= 0.11.0
diff --git a/haddock.cabal b/haddock.cabal
index 92fe249e..425ed454 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -87,6 +87,7 @@ executable haddock
transformers
other-modules:
+ CompatPrelude
Documentation.Haddock.Parser
Documentation.Haddock.Parser.Monad
Documentation.Haddock.Parser.Identifier
--
cgit v1.2.3
From 03dbfdd70186e484135ba1ea8d27672264cd9712 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Sun, 22 Mar 2020 20:10:52 -0400
Subject: Tentative 2.24 release
Adjusted changelogs and versions in `.cabal` files in preparation for
the upcoming release bundled with GHC 8.10.
---
CHANGES.md | 7 +++++++
haddock-api/haddock-api.cabal | 6 +++---
haddock-api/src/Haddock/Backends/Hoogle.hs | 2 +-
haddock-api/src/Haddock/InterfaceFile.hs | 2 +-
haddock-library/CHANGES.md | 4 +++-
haddock-library/haddock-library.cabal | 2 +-
haddock.cabal | 4 ++--
7 files changed, 18 insertions(+), 9 deletions(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/CHANGES.md b/CHANGES.md
index 88656da4..b0600381 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -1,3 +1,10 @@
+## Changes in 2.24.0
+
+ * Reify oversaturated data family instances correctly (#1103)
+
+ * Removed the majority of Haddock's possible `panic` routes through
+ the TTG refactor to make extension variants empty
+
## Changes in 2.23.0
* "Linuwial" is the new default theme (#721, #782, #949)
diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal
index 8ad0ae64..0324fcd6 100644
--- a/haddock-api/haddock-api.cabal
+++ b/haddock-api/haddock-api.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.0
name: haddock-api
-version: 2.23.0
+version: 2.24.0
synopsis: A documentation-generation tool for Haskell libraries
description: Haddock is a documentation-generation tool for Haskell
libraries
@@ -45,7 +45,7 @@ library
build-depends: base ^>= 4.14.0
, ghc ^>= 8.10
, ghc-paths ^>= 0.1.0.9
- , haddock-library ^>= 1.8.0
+ , haddock-library ^>= 1.9.0
, xhtml ^>= 3000.2.2
-- Versions for the dependencies below are transitively pinned by
@@ -167,7 +167,7 @@ test-suite spec
build-depends: ghc ^>= 8.10
, ghc-paths ^>= 0.1.0.12
- , haddock-library ^>= 1.8.0
+ , haddock-library ^>= 1.9.0
, xhtml ^>= 3000.2.2
, hspec >= 2.4.4 && < 2.8
, QuickCheck >= 2.11 && < 2.14
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index b38d4047..b4a605f2 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -260,7 +260,7 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
tyVarBndr2Type :: HsTyVarBndr GhcRn -> HsType GhcRn
tyVarBndr2Type (UserTyVar _ n) = HsTyVar noExtField NotPromoted n
tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig noExtField (reL (HsTyVar noExtField NotPromoted n)) k
- tyVarBndr2Type (XTyVarBndr _) = panic "haddock:ppCtor"
+ tyVarBndr2Type (XTyVarBndr nec) = noExtCon nec
ppCtor dflags _dat subdocs con@(ConDeclGADT { })
= concatMap (lookupCon dflags subdocs) (getConNames con) ++ f
diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs
index 3ce2fabb..17be6fa1 100644
--- a/haddock-api/src/Haddock/InterfaceFile.hs
+++ b/haddock-api/src/Haddock/InterfaceFile.hs
@@ -83,7 +83,7 @@ binaryInterfaceMagic = 0xD0Cface
--
binaryInterfaceVersion :: Word16
#if (__GLASGOW_HASKELL__ >= 809) && (__GLASGOW_HASKELL__ < 811)
-binaryInterfaceVersion = 35
+binaryInterfaceVersion = 36
binaryInterfaceVersionCompatibility :: [Word16]
binaryInterfaceVersionCompatibility = [binaryInterfaceVersion]
diff --git a/haddock-library/CHANGES.md b/haddock-library/CHANGES.md
index d112db45..5b400d7c 100644
--- a/haddock-library/CHANGES.md
+++ b/haddock-library/CHANGES.md
@@ -1,7 +1,9 @@
-## Changes in version 1.8.0.1
+## Changes in version 1.9.0
* Fix build-time regression for `base < 4.7` (#1119)
+ * Update parsing to strip whitespace from table cells (#1074)
+
## Changes in version 1.8.0
* Support inline markup in markdown-style links (#875)
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index 294ef5be..57f45887 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.2
name: haddock-library
-version: 1.8.0.1
+version: 1.9.0
synopsis: Library exposing some functionality of Haddock.
description: Haddock is a documentation-generation tool for Haskell
diff --git a/haddock.cabal b/haddock.cabal
index 425ed454..f01fe8fc 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.4
name: haddock
-version: 2.23.0
+version: 2.24.0
synopsis: A documentation-generation tool for Haskell libraries
description:
This is Haddock, a tool for automatically generating documentation
@@ -144,7 +144,7 @@ executable haddock
else
-- in order for haddock's advertised version number to have proper meaning,
-- we pin down to a single haddock-api version.
- build-depends: haddock-api == 2.23.0
+ build-depends: haddock-api == 2.24.0
test-suite html-test
type: exitcode-stdio-1.0
--
cgit v1.2.3
From b33e4bebce0fb98acfc2c1f5efc370e95a061c86 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Sat, 28 Mar 2020 12:28:48 -0400
Subject: Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL`
* `unL` is already defined by GHC as `unLoc`
* `reL` is already defined by GHC as `noLoc` (in a safer way too!)
* Condense `setOutputDir` and add a about exporting from GHC
Fixes #978
---
haddock-api/src/Haddock/Backends/Hoogle.hs | 24 ++++++------
haddock-api/src/Haddock/Backends/LaTeX.hs | 2 +-
haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 4 +-
haddock-api/src/Haddock/GhcUtils.hs | 53 ++++++++++----------------
haddock-api/src/Haddock/Interface/Create.hs | 18 ++++-----
5 files changed, 44 insertions(+), 57 deletions(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index b4a605f2..63acb465 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -82,7 +82,7 @@ dropHsDocTy = f
f (HsOpTy x a b c) = HsOpTy x (g a) b (g c)
f (HsParTy x a) = HsParTy x (g a)
f (HsKindSig x a b) = HsKindSig x (g a) b
- f (HsDocTy _ a _) = f $ unL a
+ f (HsDocTy _ a _) = f $ unLoc a
f x = x
outHsType :: (OutputableBndrId p)
@@ -215,7 +215,7 @@ ppSynonym dflags x = [out dflags x]
ppData :: DynFlags -> TyClDecl GhcRn -> [(Name, DocForDecl Name)] -> [String]
ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs
= showData decl{ tcdDataDefn = defn { dd_cons=[],dd_derivs=noLoc [] }} :
- concatMap (ppCtor dflags decl subdocs . unL) (dd_cons defn)
+ concatMap (ppCtor dflags decl subdocs . unLoc) (dd_cons defn)
where
-- GHC gives out "data Bar =", we want to delete the equals.
@@ -244,22 +244,22 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
[out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]]
| r <- map unLoc recs]
- funs = foldr1 (\x y -> reL $ HsFunTy noExtField x y)
- apps = foldl1 (\x y -> reL $ HsAppTy noExtField x y)
+ funs = foldr1 (\x y -> noLoc $ HsFunTy noExtField x y)
+ apps = foldl1 (\x y -> noLoc $ HsAppTy noExtField x y)
- typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unL $ funs flds)
+ typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unLoc $ funs flds)
-- We print the constructors as comma-separated list. See GHC
-- docs for con_names on why it is a list to begin with.
- name = commaSeparate dflags . map unL $ getConNames con
+ name = commaSeparate dflags . map unLoc $ getConNames con
- resType = let c = HsTyVar noExtField NotPromoted (reL (tcdName dat))
+ resType = let c = HsTyVar noExtField NotPromoted (noLoc (tcdName dat))
as = map (tyVarBndr2Type . unLoc) (hsQTvExplicit $ tyClDeclTyVars dat)
- in apps (map reL (c : as))
+ in apps (map noLoc (c : as))
tyVarBndr2Type :: HsTyVarBndr GhcRn -> HsType GhcRn
tyVarBndr2Type (UserTyVar _ n) = HsTyVar noExtField NotPromoted n
- tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig noExtField (reL (HsTyVar noExtField NotPromoted n)) k
+ tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig noExtField (noLoc (HsTyVar noExtField NotPromoted n)) k
tyVarBndr2Type (XTyVarBndr nec) = noExtCon nec
ppCtor dflags _dat subdocs con@(ConDeclGADT { })
@@ -267,8 +267,8 @@ ppCtor dflags _dat subdocs con@(ConDeclGADT { })
where
f = [typeSig name (getGADTConTypeG con)]
- typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unL ty)
- name = out dflags $ map unL $ getConNames con
+ typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unLoc ty)
+ name = out dflags $ map unLoc $ getConNames con
ppCtor _ _ _ (XConDecl nec) = noExtCon nec
ppFixity :: DynFlags -> (Name, Fixity) -> [String]
@@ -298,7 +298,7 @@ docWith dflags header d
mkSubdoc :: DynFlags -> Located Name -> [(Name, DocForDecl Name)] -> [String] -> [String]
mkSubdoc dflags n subdocs s = concatMap (ppDocumentation dflags) getDoc ++ s
where
- getDoc = maybe [] (return . fst) (lookup (unL n) subdocs)
+ getDoc = maybe [] (return . fst) (lookup (unLoc n) subdocs)
data Tag = TagL Char [Tags] | TagP Tags | TagPre Tags | TagInline String Tags | Str String
deriving Show
diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs
index d52c136f..647812f9 100644
--- a/haddock-api/src/Haddock/Backends/LaTeX.hs
+++ b/haddock-api/src/Haddock/Backends/LaTeX.hs
@@ -624,7 +624,7 @@ ppClassDecl instances doc subdocs
text "\\haddockpremethods{}" <> emph (text "Associated Types") $$
vcat [ ppFamDecl True (fst doc) [] (FamDecl noExtField decl) True
| L _ decl <- ats
- , let name = unL . fdLName $ decl
+ , let name = unLoc . fdLName $ decl
doc = lookupAnySubdoc name subdocs
]
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
index 25669ca7..ef0ba1b6 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
@@ -492,7 +492,7 @@ ppShortClassDecl summary links (ClassDecl { tcdCtxt = lctxt, tcdLName = lname, t
+++ shortSubDecls False
(
[ ppAssocType summary links doc at [] splice unicode pkg qual | at <- ats
- , let doc = lookupAnySubdoc (unL $ fdLName $ unL at) subdocs ] ++
+ , let doc = lookupAnySubdoc (unLoc $ fdLName $ unLoc at) subdocs ] ++
-- ToDo: add associated type defaults
@@ -544,7 +544,7 @@ ppClassDecl summary links instances fixities loc d subdocs
<+>
subDefaults (maybeToList defTys)
| at <- ats
- , let name = unL . fdLName $ unL at
+ , let name = unLoc . fdLName $ unLoc at
doc = lookupAnySubdoc name subdocs
subfixs = filter ((== name) . fst) fixities
defTys = (declElem . ppDefaultAssocTy name) <$> lookupDAT name
diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs
index f600997a..923516b6 100644
--- a/haddock-api/src/Haddock/GhcUtils.hs
+++ b/haddock-api/src/Haddock/GhcUtils.hs
@@ -319,8 +319,8 @@ restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ]
case con_args d of
PrefixCon _ -> Just d
RecCon fields
- | all field_avail (unL fields) -> Just d
- | otherwise -> Just (d { con_args = PrefixCon (field_types (map unL (unL fields))) })
+ | all field_avail (unLoc fields) -> Just d
+ | otherwise -> Just (d { con_args = PrefixCon (field_types (map unLoc (unLoc fields))) })
-- if we have *all* the field names available, then
-- keep the record declaration. Otherwise degrade to
-- a constructor declaration. This isn't quite right, but
@@ -340,7 +340,7 @@ restrictDecls names = mapMaybe (filterLSigNames (`elem` names))
restrictATs :: [Name] -> [LFamilyDecl GhcRn] -> [LFamilyDecl GhcRn]
-restrictATs names ats = [ at | at <- ats , unL (fdLName (unL at)) `elem` names ]
+restrictATs names ats = [ at | at <- ats , unLoc (fdLName (unLoc at)) `elem` names ]
-------------------------------------------------------------------------------
@@ -443,18 +443,6 @@ reparenConDeclField (ConDeclField x n t d) = ConDeclField x n (reparenLType t) d
reparenConDeclField c@XConDeclField{} = c
--------------------------------------------------------------------------------
--- * Located
--------------------------------------------------------------------------------
-
-
-unL :: Located a -> a
-unL (L _ x) = x
-
-
-reL :: a -> Located a
-reL = L undefined
-
-------------------------------------------------------------------------------
-- * NamedThing instances
-------------------------------------------------------------------------------
@@ -475,17 +463,17 @@ class Parent a where
instance Parent (ConDecl GhcRn) where
children con =
case con_args con of
- RecCon fields -> map (extFieldOcc . unL) $
- concatMap (cd_fld_names . unL) (unL fields)
+ RecCon fields -> map (extFieldOcc . unLoc) $
+ concatMap (cd_fld_names . unLoc) (unLoc fields)
_ -> []
instance Parent (TyClDecl GhcRn) where
children d
- | isDataDecl d = map unL $ concatMap (getConNames . unL)
+ | isDataDecl d = map unLoc $ concatMap (getConNames . unLoc)
$ (dd_cons . tcdDataDefn) $ d
| isClassDecl d =
- map (unL . fdLName . unL) (tcdATs d) ++
- [ unL n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns ]
+ map (unLoc . fdLName . unLoc) (tcdATs d) ++
+ [ unLoc n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns ]
| otherwise = []
@@ -495,13 +483,13 @@ family = getName &&& children
familyConDecl :: ConDecl GHC.GhcRn -> [(Name, [Name])]
-familyConDecl d = zip (map unL (getConNames d)) (repeat $ children d)
+familyConDecl d = zip (map unLoc (getConNames d)) (repeat $ children d)
-- | A mapping from the parent (main-binder) to its children and from each
-- child to its grand-children, recursively.
families :: TyClDecl GhcRn -> [(Name, [Name])]
families d
- | isDataDecl d = family d : concatMap (familyConDecl . unL) (dd_cons (tcdDataDefn d))
+ | isDataDecl d = family d : concatMap (familyConDecl . unLoc) (dd_cons (tcdDataDefn d))
| isClassDecl d = [family d]
| otherwise = []
@@ -546,17 +534,16 @@ minimalDef n = do
-- * DynFlags
-------------------------------------------------------------------------------
-
-setObjectDir, setHiDir, setHieDir, setStubDir, setOutputDir :: String -> DynFlags -> DynFlags
-setObjectDir f d = d{ objectDir = Just f}
-setHiDir f d = d{ hiDir = Just f}
-setHieDir f d = d{ hieDir = Just f}
-setStubDir f d = d{ stubDir = Just f
- , includePaths = addGlobalInclude (includePaths d) [f] }
- -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
- -- \#included from the .hc file when compiling with -fvia-C.
-setOutputDir f = setObjectDir f . setHiDir f . setHieDir f . setStubDir f
-
+-- TODO: use `setOutputDir` from GHC
+setOutputDir :: FilePath -> DynFlags -> DynFlags
+setOutputDir dir dynFlags =
+ dynFlags { objectDir = Just dir
+ , hiDir = Just dir
+ , hieDir = Just dir
+ , stubDir = Just dir
+ , includePaths = addGlobalInclude (includePaths dynFlags) [dir]
+ , dumpDir = Just dir
+ }
-------------------------------------------------------------------------------
-- * 'StringBuffer' and 'ByteString'
diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index b182a615..af006d03 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -461,14 +461,14 @@ subordinates instMap decl = case decl of
dataSubs :: HsDataDefn GhcRn -> [(Name, [HsDocString], Map Int HsDocString)]
dataSubs dd = constrs ++ fields ++ derivs
where
- cons = map unL $ (dd_cons dd)
- constrs = [ (unL cname, maybeToList $ fmap unL $ con_doc c, conArgDocs c)
+ cons = map unLoc $ (dd_cons dd)
+ constrs = [ (unLoc cname, maybeToList $ fmap unLoc $ con_doc c, conArgDocs c)
| c <- cons, cname <- getConNames c ]
- fields = [ (extFieldOcc n, maybeToList $ fmap unL doc, M.empty)
+ fields = [ (extFieldOcc n, maybeToList $ fmap unLoc doc, M.empty)
| RecCon flds <- map getConArgs cons
, L _ (ConDeclField _ ns _ doc) <- (unLoc flds)
, L _ n <- ns ]
- derivs = [ (instName, [unL doc], M.empty)
+ derivs = [ (instName, [unLoc doc], M.empty)
| (l, doc) <- mapMaybe (extract_deriv_ty . hsib_body) $
concatMap (unLoc . deriv_clause_tys . unLoc) $
unLoc $ dd_derivs dd
@@ -585,13 +585,13 @@ sortByLoc = sortBy (comparing getLoc)
-- | Filter out declarations that we don't handle in Haddock
filterDecls :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)]
-filterDecls = filter (isHandled . unL . fst)
+filterDecls = filter (isHandled . unLoc . fst)
where
isHandled (ForD _ (ForeignImport {})) = True
isHandled (TyClD {}) = True
isHandled (InstD {}) = True
isHandled (DerivD {}) = True
- isHandled (SigD _ d) = isUserLSig (reL d)
+ isHandled (SigD _ d) = isUserLSig (noLoc d)
isHandled (ValD {}) = True
-- we keep doc declarations to be able to get at named docs
isHandled (DocD {}) = True
@@ -677,7 +677,7 @@ mkExportItems
return [ExportDoc doc]
lookupExport (IEDocNamed _ str, _) = liftErrMsg $
- findNamedDoc str [ unL d | d <- decls ] >>= \case
+ findNamedDoc str [ unLoc d | d <- decls ] >>= \case
Nothing -> return []
Just docStr -> do
doc <- processDocStringParas dflags pkgName gre docStr
@@ -725,13 +725,13 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames
export <- hiValExportItem dflags t l doc (l `elem` splices) $ M.lookup t fixMap
return [export]
(ds, docs_) | decl : _ <- filter (not . isValD . unLoc) ds ->
- let declNames = getMainDeclBinder (unL decl)
+ let declNames = getMainDeclBinder (unLoc decl)
in case () of
_
-- We should not show a subordinate by itself if any of its
-- parents is also exported. See note [1].
| t `notElem` declNames,
- Just p <- find isExported (parents t $ unL decl) ->
+ Just p <- find isExported (parents t $ unLoc decl) ->
do liftErrMsg $ tell [
"Warning: " ++ moduleString thisMod ++ ": " ++
pretty dflags (nameOccName t) ++ " is exported separately but " ++
--
cgit v1.2.3
From 1d657cf377b5f147b08aafb3ab3a5d11be538331 Mon Sep 17 00:00:00 2001
From: Alan Zimmerman
Date: Tue, 6 Oct 2020 18:38:35 +0100
Subject: Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled
(cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1)
---
haddock-api/src/Haddock/Backends/Hoogle.hs | 3 ++-
haddock-api/src/Haddock/Convert.hs | 7 ++++---
haddock-api/src/Haddock/GhcUtils.hs | 7 ++++---
haddock-api/src/Haddock/Interface/Create.hs | 9 ++++-----
haddock-api/src/Haddock/Interface/Rename.hs | 6 +++---
haddock-api/src/Haddock/Interface/Specialize.hs | 5 +++--
6 files changed, 20 insertions(+), 17 deletions(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 75a49036..c5a0f772 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -27,6 +27,7 @@ import Haddock.Utils hiding (out)
import GHC
import GHC.Utils.Outputable as Outputable
+import GHC.Parser.Annotation (IsUnicodeSyntax(..))
import Data.Char
import Data.List
@@ -245,7 +246,7 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
[out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]]
| r <- map unLoc recs]
- funs = foldr1 (\x y -> reL $ HsFunTy noExtField HsUnrestrictedArrow x y)
+ funs = foldr1 (\x y -> reL $ HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) x y)
apps = foldl1 (\x y -> reL $ HsAppTy noExtField x y)
typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unL $ funs flds)
diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 3b73dcd1..d95337b8 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -52,6 +52,7 @@ import GHC.Utils.Outputable ( assertPanic )
import GHC.Types.Var
import GHC.Types.Var.Set
import GHC.Types.SrcLoc
+import GHC.Parser.Annotation (IsUnicodeSyntax(..))
import Haddock.Types
import Haddock.Interface.Specialize
@@ -769,9 +770,9 @@ noKindTyVars _ _ = emptyVarSet
synifyMult :: [TyVar] -> Mult -> HsArrow GhcRn
synifyMult vs t = case t of
- One -> HsLinearArrow
- Many -> HsUnrestrictedArrow
- ty -> HsExplicitMult (synifyType WithinType vs ty)
+ One -> HsLinearArrow NormalSyntax
+ Many -> HsUnrestrictedArrow NormalSyntax
+ ty -> HsExplicitMult NormalSyntax (synifyType WithinType vs ty)
diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs
index 3abb6481..8b4bcc05 100644
--- a/haddock-api/src/Haddock/GhcUtils.hs
+++ b/haddock-api/src/Haddock/GhcUtils.hs
@@ -42,6 +42,7 @@ import GHC.Types.Var.Env ( TyVarEnv, extendVarEnv, elemVarEnv, emptyVarEnv )
import GHC.Core.TyCo.Rep ( Type(..) )
import GHC.Core.Type ( isRuntimeRepVar )
import GHC.Builtin.Types( liftedRepDataConTyCon )
+import GHC.Parser.Annotation (IsUnicodeSyntax(..))
import GHC.Data.StringBuffer ( StringBuffer )
import qualified GHC.Data.StringBuffer as S
@@ -165,13 +166,13 @@ getGADTConType (ConDeclGADT { con_forall = L _ has_forall
| otherwise
= tau_ty
--- tau_ty :: LHsType DocNameI
+-- tau_ty :: LHsType DocNameI
tau_ty = case args of
RecCon flds -> mkFunTy (noLoc (HsRecTy noExtField (unLoc flds))) res_ty
PrefixCon pos_args -> foldr mkFunTy res_ty (map hsScaledThing pos_args)
InfixCon arg1 arg2 -> (hsScaledThing arg1) `mkFunTy` ((hsScaledThing arg2) `mkFunTy` res_ty)
- mkFunTy a b = noLoc (HsFunTy noExtField HsUnrestrictedArrow a b)
+ mkFunTy a b = noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) a b)
getGADTConType (ConDeclH98 {}) = panic "getGADTConType"
-- Should only be called on ConDeclGADT
@@ -227,7 +228,7 @@ getGADTConTypeG (ConDeclGADT { con_forall = L _ has_forall
InfixCon arg1 arg2 -> (hsScaledThing arg1) `mkFunTy` ((hsScaledThing arg2) `mkFunTy` res_ty)
-- mkFunTy :: LHsType DocNameI -> LHsType DocNameI -> LHsType DocNameI
- mkFunTy a b = noLoc (HsFunTy noExtField HsUnrestrictedArrow a b)
+ mkFunTy a b = noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) a b)
getGADTConTypeG (ConDeclH98 {}) = panic "getGADTConTypeG"
-- Should only be called on ConDeclGADT
diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index 7b9674a6..dd9419eb 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -56,8 +56,7 @@ import GHC.Data.FastString ( unpackFS, bytesFS )
import GHC.Types.Basic ( StringLiteral(..), SourceText(..), PromotionFlag(..) )
import qualified GHC.Utils.Outputable as O
import GHC.HsToCore.Docs hiding (mkMaps)
-
-import GHC.Core.Multiplicity
+import GHC.Parser.Annotation (IsUnicodeSyntax(..))
-- | Use a 'TypecheckedModule' to produce an 'Interface'.
@@ -958,8 +957,8 @@ extractPatternSyn nm t tvs cons =
typ'' = noLoc (HsQualTy noExtField (noLoc []) typ')
in PatSynSig noExtField [noLoc nm] (mkEmptyImplicitBndrs typ'')
- longArrow :: (XFunTy name ~ NoExtField) => [LHsType name] -> LHsType name -> LHsType name
- longArrow inputs output = foldr (\x y -> noLoc (HsFunTy noExtField HsUnrestrictedArrow x y)) output inputs
+ longArrow :: [LHsType GhcRn] -> LHsType GhcRn -> LHsType GhcRn
+ longArrow inputs output = foldr (\x y -> noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) x y)) output inputs
data_ty con
| ConDeclGADT{} <- con = con_res_ty con
@@ -976,7 +975,7 @@ extractRecSel _ _ _ [] = error "extractRecSel: selector not found"
extractRecSel nm t tvs (L _ con : rest) =
case getConArgs con of
RecCon (L _ fields) | ((l,L _ (ConDeclField _ _nn ty _)) : _) <- matching_fields fields ->
- L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField HsUnrestrictedArrow data_ty (getBangType ty)))))
+ L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) data_ty (getBangType ty)))))
_ -> extractRecSel nm t tvs rest
where
matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)]
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 27bad4b9..061ef8eb 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -223,9 +223,9 @@ renameMaybeInjectivityAnn :: Maybe (LInjectivityAnn GhcRn)
renameMaybeInjectivityAnn = traverse renameInjectivityAnn
renameArrow :: HsArrow GhcRn -> RnM (HsArrow DocNameI)
-renameArrow HsUnrestrictedArrow = return HsUnrestrictedArrow
-renameArrow HsLinearArrow = return HsLinearArrow
-renameArrow (HsExplicitMult p) = HsExplicitMult <$> renameLType p
+renameArrow (HsUnrestrictedArrow u) = return (HsUnrestrictedArrow u)
+renameArrow (HsLinearArrow u) = return (HsLinearArrow u)
+renameArrow (HsExplicitMult u p) = HsExplicitMult u <$> renameLType p
renameType :: HsType GhcRn -> RnM (HsType DocNameI)
renameType t = case t of
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index 5c933f25..0e9fc851 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -17,6 +17,7 @@ import GHC.Types.Name
import GHC.Data.FastString
import GHC.Builtin.Types.Prim ( funTyConName )
import GHC.Builtin.Types ( listTyConName, unrestrictedFunTyConName )
+import GHC.Parser.Annotation (IsUnicodeSyntax(..))
import Control.Monad
import Control.Monad.Trans.State
@@ -136,7 +137,7 @@ sugarTuples typ =
sugarOperators :: NamedThing (IdP (GhcPass p)) => HsType (GhcPass p) -> HsType (GhcPass p)
sugarOperators (HsAppTy _ (L _ (HsAppTy _ (L _ (HsTyVar _ _ (L l name))) la)) lb)
| isSymOcc $ getOccName name' = mkHsOpTy la (L l name) lb
- | unrestrictedFunTyConName == name' = HsFunTy noExtField HsUnrestrictedArrow la lb
+ | unrestrictedFunTyConName == name' = HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) la lb
where
name' = getName name
sugarOperators typ = typ
@@ -282,7 +283,7 @@ renameType t@(HsTyLit _ _) = pure t
renameType (HsWildCardTy wc) = pure (HsWildCardTy wc)
renameHsArrow :: HsArrow GhcRn -> Rename (IdP GhcRn) (HsArrow GhcRn)
-renameHsArrow (HsExplicitMult p) = HsExplicitMult <$> renameLType p
+renameHsArrow (HsExplicitMult u p) = HsExplicitMult u <$> renameLType p
renameHsArrow mult = pure mult
--
cgit v1.2.3
From 96a60e218b35df611ee56c4bdd8408ec4375e6ca Mon Sep 17 00:00:00 2001
From: tomjaguarpaw
Date: Tue, 8 Dec 2020 17:00:04 +0000
Subject: Enable two warnings (#1245)
because they will be soon be added to -Wall.
See https://gitlab.haskell.org/ghc/ghc/-/issues/15656
---
haddock-api/haddock-api.cabal | 2 ++
haddock-api/src/Haddock/Backends/Hoogle.hs | 1 +
haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 1 +
haddock-api/src/Haddock/GhcUtils.hs | 1 +
haddock-api/src/Haddock/Interface/AttachInstances.hs | 2 ++
haddock-api/src/Haddock/Interface/Rename.hs | 1 +
haddock-api/src/Haddock/Interface/Specialize.hs | 1 +
haddock.cabal | 2 +-
8 files changed, 10 insertions(+), 1 deletion(-)
(limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal
index 4abfd984..5fa51905 100644
--- a/haddock-api/haddock-api.cabal
+++ b/haddock-api/haddock-api.cabal
@@ -70,6 +70,8 @@ library
-Wredundant-constraints
-Wnoncanonical-monad-instances
-Wmissing-home-modules
+ -Wincomplete-uni-patterns
+ -Wincomplete-record-updates
exposed-modules:
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 63acb465..4961edc2 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-----------------------------------------------------------------------------
-- |
-- Module : Haddock.Backends.Hoogle
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
index 0247d567..0974d6da 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module Haddock.Backends.Hyperlinker.Parser (parse) where
import Control.Applicative ( Alternative(..) )
diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs
index 923516b6..0874e7b4 100644
--- a/haddock-api/src/Haddock/GhcUtils.hs
+++ b/haddock-api/src/Haddock/GhcUtils.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
-- |
diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs
index 685dca01..ce987b76 100644
--- a/haddock-api/src/Haddock/Interface/AttachInstances.hs
+++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs
@@ -1,5 +1,7 @@
{-# LANGUAGE MagicHash, BangPatterns #-}
{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
+{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-----------------------------------------------------------------------------
-- |
-- Module : Haddock.Interface.AttachInstances
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index b4ff31e5..78c58581 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
----------------------------------------------------------------------------
-- |
-- Module : Haddock.Interface.Rename
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index 492818bd..6e11a859 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RecordWildCards #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module Haddock.Interface.Specialize
( specializeInstHead
diff --git a/haddock.cabal b/haddock.cabal
index 1d6ad180..0bf99950 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -62,7 +62,7 @@ executable haddock
default-language: Haskell2010
main-is: Main.hs
hs-source-dirs: driver
- ghc-options: -funbox-strict-fields -Wall -O2 -threaded
+ ghc-options: -funbox-strict-fields -Wall -Wincomplete-uni-patterns -Wincomplete-record-updates -O2 -threaded
-- haddock typically only supports a single GHC major version
build-depends:
--
cgit v1.2.3