From 143094b0badbeb217e33e7da4ad4ba669c4e7bd5 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Mon, 7 May 2018 18:53:15 -0700 Subject: Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 34512de8..277634b9 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -24,8 +24,13 @@ import Haddock.Backends.Hyperlinker.Types as T -- (In reality, this only holds for input not containing '\r', '\t', '\f', '\v', -- characters, since GHC transforms those into ' ' and '\n') parse :: DynFlags -> FilePath -> String -> [T.Token] -parse dflags fp s = ghcToks (processCPP dflags fp s) - +parse dflags fp = ghcToks . processCPP dflags fp . filterCRLF + where + -- Remove CRLFs from source + filterCRLF :: String -> String + filterCRLF ('\r':'\n':cs) = '\n' : filterCRLF cs + filterCRLF (c:cs) = c : filterCRLF cs + filterCRLF [] = [] -- | Parse the source into tokens using the GHC lexer. -- -- cgit v1.2.3 From 2dd12f50b67feb77ae310a3af942ce3b058318e3 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Tue, 8 May 2018 04:00:18 +0200 Subject: Add docs for some DocH constructors (#814) --- haddock-library/src/Documentation/Haddock/Types.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs index 005ec186..b5dea3d4 100644 --- a/haddock-library/src/Documentation/Haddock/Types.hs +++ b/haddock-library/src/Documentation/Haddock/Types.hs @@ -107,8 +107,10 @@ data DocH mod id | DocParagraph (DocH mod id) | DocIdentifier id | DocIdentifierUnchecked mod + -- ^ A qualified identifier that couldn't be resolved. | DocModule String | DocWarning (DocH mod id) + -- ^ This constructor has no counterpart in Haddock markup. | DocEmphasis (DocH mod id) | DocMonospaced (DocH mod id) | DocBold (DocH mod id) @@ -121,6 +123,7 @@ data DocH mod id | DocMathInline String | DocMathDisplay String | DocAName String + -- ^ A (HTML) anchor. | DocProperty String | DocExamples [Example] | DocHeader (Header (DocH mod id)) -- cgit v1.2.3 From 22bfe0a50a63fa2685ed94bd7f3d1ab565f31f6a Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Tue, 8 May 2018 02:15:45 -0700 Subject: Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). --- .../src/Haddock/Backends/Hyperlinker/Renderer.hs | 64 +++++----------------- 1 file changed, 14 insertions(+), 50 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs index 5291220a..d7ea70a6 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs @@ -1,6 +1,5 @@ {-# LANGUAGE RecordWildCards #-} - module Haddock.Backends.Hyperlinker.Renderer (render) where @@ -28,36 +27,10 @@ render :: Maybe FilePath -> Maybe FilePath -> SrcMap -> [RichToken] -> Html render mcss mjs srcs tokens = header mcss mjs <> body srcs tokens - -data TokenGroup - = GrpNormal Token - | GrpRich TokenDetails [Token] - - --- | Group consecutive tokens pointing to the same element. --- --- We want to render qualified identifiers as one entity. For example, --- @Bar.Baz.foo@ consists of 5 tokens (@Bar@, @.@, @Baz@, @.@, @foo@) but for --- better user experience when highlighting and clicking links, these tokens --- should be regarded as one identifier. Therefore, before rendering we must --- group consecutive elements pointing to the same 'GHC.Name' (note that even --- dot token has it if it is part of qualified name). -groupTokens :: [RichToken] -> [TokenGroup] -groupTokens [] = [] -groupTokens ((RichToken tok Nothing):rest) = (GrpNormal tok):(groupTokens rest) -groupTokens ((RichToken tok (Just det)):rest) = - let (grp, rest') = span same rest - in (GrpRich det (tok:(map rtkToken grp))):(groupTokens rest') - where - same (RichToken _ (Just det')) = det == det' - same _ = False - - body :: SrcMap -> [RichToken] -> Html -body srcs tokens = - Html.body . Html.pre $ hypsrc +body srcs tokens = Html.body . Html.pre $ hypsrc where - hypsrc = mconcat . map (tokenGroup srcs) . groupTokens $ tokens + hypsrc = mconcat . map (richToken srcs) $ tokens header :: Maybe FilePath -> Maybe FilePath -> Html @@ -78,29 +51,20 @@ header mcss mjs = , Html.src scriptFile ] - -tokenGroup :: SrcMap -> TokenGroup -> Html -tokenGroup _ (GrpNormal tok@(Token { .. })) +-- | Given information about the source position of definitions, render a token +richToken :: SrcMap -> RichToken -> Html +richToken srcs (RichToken Token{..} details) | tkType == TkSpace = renderSpace (GHC.srcSpanStartLine tkSpan) tkValue - | otherwise = tokenSpan tok ! attrs - where - attrs = [ multiclass . tokenStyle $ tkType ] -tokenGroup srcs (GrpRich det tokens) = - externalAnchor det . internalAnchor det . hyperlink srcs det $ content + | otherwise = linked content where - content = mconcat . map (richToken det) $ tokens - - -richToken :: TokenDetails -> Token -> Html -richToken det tok = - tokenSpan tok ! [ multiclass style ] - where - style = (tokenStyle . tkType) tok ++ richTokenStyle det - - -tokenSpan :: Token -> Html -tokenSpan = Html.thespan . Html.toHtml . tkValue - + content = tokenSpan ! [ multiclass style ] + tokenSpan = Html.thespan (Html.toHtml tkValue) + style = tokenStyle tkType ++ maybe [] richTokenStyle details + + -- If we have name information, we can make links + linked = case details of + Just d -> externalAnchor d . internalAnchor d . hyperlink srcs d + Nothing -> id richTokenStyle :: TokenDetails -> [StyleClass] richTokenStyle (RtkVar _) = ["hs-var"] -- cgit v1.2.3 From a8840a37976209c5a3c4cf929eff502cdca80ecf Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Tue, 8 May 2018 19:48:11 +0200 Subject: Renamer: Warn about out of scope identifiers. (#819) --- haddock-api/src/Haddock/Interface/LexParseRn.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 9a978f9f..cbe55dc4 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -104,7 +104,9 @@ rename dflags gre = rn -- We found no names in the env so we start guessing. [] -> case choices of + -- This shouldn't happen as 'dataTcOccs' always returns at least its input. [] -> pure (DocMonospaced (DocString (showPpr dflags x))) + -- There was nothing in the environment so we need to -- pick some default from what's available to us. We -- diverge here from the old way where we would default @@ -113,7 +115,7 @@ 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:_ -> pure (outOfScope dflags a) + a:_ -> outOfScope dflags a -- There is only one name in the environment that matches so -- use it. @@ -154,12 +156,15 @@ 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 -> RdrName -> Doc a +outOfScope :: DynFlags -> RdrName -> ErrMsgM (Doc a) outOfScope dflags x = case x of - Unqual occ -> monospaced occ - Qual mdl occ -> DocIdentifierUnchecked (mdl, occ) - Orig _ occ -> monospaced occ - Exact name -> monospaced name -- Shouldn't happen since x is out of scope + 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 where + warnAndMonospace a = do + tell ["Warning: '" ++ showPpr dflags a ++ "' is out of scope."] + pure (monospaced a) monospaced a = DocMonospaced (DocString (showPpr dflags a)) -- cgit v1.2.3 From 00ccfecdfedb55d44c84dfa4f0f1de90cfe6fafd Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Thu, 10 May 2018 11:19:47 -0400 Subject: Remove Hoogle backend hack that butchers infix datatype names --- haddock-api/src/Haddock/Backends/Hoogle.hs | 3 +-- hoogle-test/ref/Bug825/test.txt | 9 +++++++++ hoogle-test/src/Bug825/Bug825.hs | 6 ++++++ 3 files changed, 16 insertions(+), 2 deletions(-) create mode 100644 hoogle-test/ref/Bug825/test.txt create mode 100644 hoogle-test/src/Bug825/Bug825.hs diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index e7ce9d30..484841ba 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -225,11 +225,10 @@ ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs -- GHC gives out "data Bar =", we want to delete the equals -- also writes data : a b, when we want data (:) a b - showData d = unwords $ map f $ if last xs == "=" then init xs else xs + showData d = unwords $ if last xs == "=" then init xs else xs where xs = words $ out dflags d nam = out dflags $ tyClDeclLName d - f w = if w == nam then operator nam else w ppData _ _ _ = panic "ppData" -- | for constructors, and named-fields... diff --git a/hoogle-test/ref/Bug825/test.txt b/hoogle-test/ref/Bug825/test.txt new file mode 100644 index 00000000..a88202dc --- /dev/null +++ b/hoogle-test/ref/Bug825/test.txt @@ -0,0 +1,9 @@ +-- Hoogle documentation, generated by Haddock +-- See Hoogle, http://www.haskell.org/hoogle/ + +@package test +@version 0.0.0 + +module Bug825 +data a :~: b +data (:~~:) a b diff --git a/hoogle-test/src/Bug825/Bug825.hs b/hoogle-test/src/Bug825/Bug825.hs new file mode 100644 index 00000000..bfe07139 --- /dev/null +++ b/hoogle-test/src/Bug825/Bug825.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeOperators #-} +module Bug825 where + +data a :~: b +data (:~~:) a b -- cgit v1.2.3 From 72ff1ba81d29613c8336a7a88c3a01ae540d81d0 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Thu, 10 May 2018 11:24:38 -0400 Subject: Wibbles --- haddock-api/src/Haddock/Backends/Hoogle.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 484841ba..59a4f53c 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -223,12 +223,12 @@ ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs concatMap (ppCtor dflags decl subdocs . unL) (dd_cons defn) where - -- GHC gives out "data Bar =", we want to delete the equals - -- also writes data : a b, when we want data (:) a b + -- GHC gives out "data Bar =", we want to delete the equals. + -- There's no need to worry about parenthesizing infix data type names, + -- since this Outputable instance for TyClDecl gets this right already. showData d = unwords $ if last xs == "=" then init xs else xs where xs = words $ out dflags d - nam = out dflags $ tyClDeclLName d ppData _ _ _ = panic "ppData" -- | for constructors, and named-fields... -- cgit v1.2.3 From 4f148a9282491d7c9d6fa87dc01e4be4acdec13f Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Wed, 23 May 2018 02:29:05 -0700 Subject: Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix #834. * Accept html-test output --- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 8 ++-- html-test/ref/Bug26.html | 14 +++---- html-test/ref/Bug613.html | 14 +++---- html-test/ref/Bug647.html | 8 ---- html-test/ref/Bug679.html | 8 ---- html-test/ref/DeprecatedClass.html | 28 +++++-------- html-test/ref/Hash.html | 16 ++++--- html-test/ref/Instances.html | 24 +++++++++++ html-test/ref/Minimal.html | 36 +++++++++++----- html-test/ref/Operators.html | 34 +++++++-------- html-test/ref/OrphanInstancesClass.html | 8 ---- html-test/ref/Test.html | 58 ++++++++++++-------------- html-test/ref/Ticket61.html | 8 ---- 13 files changed, 124 insertions(+), 140 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 815ecee9..1daf9ace 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -475,9 +475,9 @@ ppShortClassDecl summary links (ClassDecl { tcdCtxt = lctxt, tcdLName = lname, t -- ToDo: add associated type defaults - [ ppFunSig summary links loc doc names (hsSigWcType typ) + [ ppFunSig summary links loc doc names (hsSigType typ) [] splice unicode pkg qual - | L _ (TypeSig lnames typ) <- sigs + | L _ (ClassOpSig False lnames typ) <- sigs , let doc = lookupAnySubdoc (head names) subdocs names = map unLoc lnames ] -- FIXME: is taking just the first name ok? Is it possible that @@ -537,12 +537,12 @@ ppClassDecl summary links instances fixities loc d subdocs minimalBit = case [ s | MinimalSig _ (L _ s) <- sigs ] of -- Miminal complete definition = every shown method And xs : _ | sort [getName n | L _ (Var (L _ n)) <- xs] == - sort [getName n | TypeSig ns _ <- sigs, L _ n <- ns] + sort [getName n | ClassOpSig _ ns _ <- sigs, L _ n <- ns] -> noHtml -- Minimal complete definition = the only shown method Var (L _ n) : _ | [getName n] == - [getName n' | L _ (TypeSig ns _) <- lsigs, L _ n' <- ns] + [getName n' | L _ (ClassOpSig _ ns _) <- lsigs, L _ n' <- ns] -> noHtml -- Minimal complete definition = nothing diff --git a/html-test/ref/Bug26.html b/html-test/ref/Bug26.html index e50169ba..a363fef3 100644 --- a/html-test/ref/Bug26.html +++ b/html-test/ref/Bug26.html @@ -71,7 +71,11 @@ > a where
  • c_f :: a
  • Since: 1.0

    Minimal complete definition

    c_f

    Methods

    f where
    • fmap :: (a -> b) -> f a -> f b
    • #

      Minimal complete definition

      fmap

      Methods

      #

      Minimal complete definition

      f

      Methods

      #

      Minimal complete definition

      foo

      Methods

      a where
      • foo :: a -> a
      • a where
        • bar :: a -> a
        • some class

          Minimal complete definition

          foo

          Methods

          Deprecated: SomeOtherClass

          Minimal complete definition

          bar

          Methods

          a where
          • hash :: a -> Int
          • A class of types which can be hashed.

            Minimal complete definition

            hash

            Methods

            #

            Minimal complete definition

            Nothing

            Methods

            #

            Minimal complete definition

            Nothing

            Methods

            #

            Minimal complete definition

            Nothing

            Methods

            #

            Minimal complete definition

            Nothing

            Associated Types

            #

            Minimal complete definition

            (a, b, c | (d | e, (f | g)))

            Methods

            #

            Minimal complete definition

            aaa, bbb

            Methods

            #

            Minimal complete definition

            Nothing

            Methods

            a ><< b
          • (>><), (<<>) :: a -> b -> ()
          • (**>), (**<), (>**), (<**) :: a -> a -> ()
          • Class with fixity, including associated types

          • Minimal complete definition

            (>><), (<<>), (**>), (**<), (>**), (<**)

            Associated Types

            #

            Minimal complete definition

            aClass

            Methods

            a where
            • a :: IO a
            • b :: [a]
            • a where
              • d :: T a b
              • e :: (a, a)
              • a where
                • ff :: a
                • class)

                • Methods

                  This is a class declaration with no separate docs for the methods

                  Minimal complete definition

                  d, e

                  Methods

                  #

                  Minimal complete definition

                  ff

                  Methods

                  #

                  Minimal complete definition

                  f

                  Methods

                  Date: Tue, 5 Jun 2018 19:47:06 +0200 Subject: Bump a few dependency bounds (#845) --- haddock-api/haddock-api.cabal | 6 +++--- haddock-library/haddock-library.cabal | 8 ++++---- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index acb4d9e4..b2d7829c 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -166,12 +166,12 @@ test-suite spec Haddock.Backends.Hyperlinker.Parser Haddock.Backends.Hyperlinker.Types - build-depends: Cabal ^>= 2.0.0 + build-depends: Cabal ^>= 2.2 , ghc ^>= 8.4 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 - , hspec ^>= 2.4.4 + , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 -- Versions for the dependencies below are transitively pinned by @@ -188,7 +188,7 @@ test-suite spec , transformers build-tool-depends: - hspec-discover:hspec-discover ^>= 2.4.4 + hspec-discover:hspec-discover >= 2.4.4 && < 2.6 source-repository head type: git diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 49ec826c..eb961041 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -72,18 +72,18 @@ test-suite spec build-depends: base >= 4.5 && < 4.12 - , base-compat ^>= 0.9.3 + , base-compat >= 0.9.3 && < 0.11 , bytestring >= 0.9.2.1 && < 0.11 , containers >= 0.4.2.1 && < 0.6 , transformers >= 0.3.0 && < 0.6 - , hspec ^>= 2.4.4 + , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 , text >= 1.2.3.0 && < 1.3 , parsec >= 3.1.13.0 && < 3.2 , deepseq >= 1.3 && < 1.5 build-tool-depends: - hspec-discover:hspec-discover ^>= 2.4.4 + hspec-discover:hspec-discover >= 2.4.4 && < 2.6 test-suite fixtures type: exitcode-stdio-1.0 @@ -93,7 +93,7 @@ test-suite fixtures hs-source-dirs: fixtures build-depends: base >= 4.5 && < 4.12 - , base-compat ^>= 0.9.3 + , base-compat >= 0.9.3 && < 0.11 , directory ^>= 1.3.0.2 , filepath ^>= 1.4.1.2 , optparse-applicative ^>= 0.14.0.0 -- cgit v1.2.3 From bea565ec5a029b8c19965aa22f34c23a112c0a7f Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Tue, 5 Jun 2018 10:47:16 -0700 Subject: Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes #837. --- .../src/Haddock/Backends/Hyperlinker/Parser.hs | 32 ++- hypsrc-test/ref/src/CPP.html | 216 +++++++++++++++++++++ hypsrc-test/src/CPP.hs | 26 +++ 3 files changed, 267 insertions(+), 7 deletions(-) create mode 100644 hypsrc-test/ref/src/CPP.html create mode 100644 hypsrc-test/src/CPP.hs diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 277634b9..456050d1 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -3,6 +3,8 @@ module Haddock.Backends.Hyperlinker.Parser (parse) where import Data.Either ( isRight, isLeft ) import Data.List ( foldl', isPrefixOf, isSuffixOf ) import Data.Maybe ( maybeToList ) +import Data.Char ( isSpace ) +import qualified Text.Read as R import GHC ( DynFlags, addSourceToTokens ) import SrcLoc @@ -109,12 +111,9 @@ isCPPline :: String -> Bool isCPPline = isPrefixOf "#" . dropWhile (`elem` " \t") . take 5 --- | Split a "line" off the front of a string, supporting newline escapes. --- --- By "line", we understand: the shortest substring ending in a '\n' that is not --- --- 1. immediately preceded by a '\\' --- 2. not inside some (possibly nested) block comment +-- | Split a "line" off the front of a string, hopefully without cutting tokens +-- in half. I say "hopefully" because knowing what a token is requires lexing, +-- yet lexing depends on this function. -- -- All characters in the input are present in the output: -- @@ -122,17 +121,36 @@ isCPPline = isPrefixOf "#" . dropWhile (`elem` " \t") . take 5 spanToNewline :: Int -- ^ open '{-' -> String -- ^ input -> (String, String) -spanToNewline _ [] = ([], []) + +-- Base case and space characters +spanToNewline _ "" = ("", "") +spanToNewline n ('\n':str) | n <= 0 = ("\n", str) spanToNewline n ('\n':str) | n <= 0 = ("\n", str) spanToNewline n ('\\':'\n':str) = let (str', rest) = spanToNewline n str in ('\\':'\n':str', rest) + +-- Block comments spanToNewline n ('{':'-':str) = let (str', rest) = spanToNewline (n+1) str in ('{':'-':str', rest) spanToNewline n ('-':'}':str) = let (str', rest) = spanToNewline (n-1) str in ('-':'}':str', rest) + +-- When not in a block comment, try to lex a Haskell token +spanToNewline 0 str@(c:_) | ((lexed, str') : _) <- R.lex str, not (isSpace c) = + if all (== '-') lexed && length lexed >= 2 + -- A Haskell line comment + then case span (/= '\n') str' of + (str'', '\n':rest) -> (lexed ++ str'' ++ "\n", rest) + (_, _) -> (str, "") + + -- An actual Haskell token + else let (str'', rest) = spanToNewline 0 str' + in (lexed ++ str'', rest) + +-- In all other cases, advance one character at a time spanToNewline n (c:str) = let (str', rest) = spanToNewline n str in (c:str', rest) diff --git a/hypsrc-test/ref/src/CPP.html b/hypsrc-test/ref/src/CPP.html new file mode 100644 index 00000000..fb85bd2f --- /dev/null +++ b/hypsrc-test/ref/src/CPP.html @@ -0,0 +1,216 @@ +
                  {-# LANGUAGE CPP #-}
                  +module CPP where
                  +
                  +#define SOMETHING1
                  +
                  +foo :: String
                  +foo = {-  " single quotes are fine in block comments
                  +          {- nested block comments are fine -}
                  +       -} "foo"
                  +
                  +#define SOMETHING2
                  +
                  +bar :: String
                  +bar = "block comment in a string is not a comment {- "
                  +
                  +#define SOMETHING3
                  +
                  +-- " single quotes are fine in line comments
                  +-- {- unclosed block comments are fine in line comments
                  +
                  +-- Multiline CPP is also fine
                  +#define FOO\
                  +  1
                  +
                  +baz :: String
                  +baz = "line comment in a string is not a comment --"
                  +
                  \ No newline at end of file diff --git a/hypsrc-test/src/CPP.hs b/hypsrc-test/src/CPP.hs new file mode 100644 index 00000000..f00ce031 --- /dev/null +++ b/hypsrc-test/src/CPP.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE CPP #-} +module CPP where + +#define SOMETHING1 + +foo :: String +foo = {- " single quotes are fine in block comments + {- nested block comments are fine -} + -} "foo" + +#define SOMETHING2 + +bar :: String +bar = "block comment in a string is not a comment {- " + +#define SOMETHING3 + +-- " single quotes are fine in line comments +-- {- unclosed block comments are fine in line comments + +-- Multiline CPP is also fine +#define FOO\ + 1 + +baz :: String +baz = "line comment in a string is not a comment --" -- cgit v1.2.3 From ef16b9f8f73e6a4d639919152925ab83d9b1024f Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Fri, 8 Jun 2018 22:20:30 +0200 Subject: Renamer: Warn about ambiguous identifiers (#831) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes #830. * Deduplicate warnings Fixes #832. --- haddock-api/src/Haddock/Interface.hs | 4 ++-- haddock-api/src/Haddock/Interface/LexParseRn.hs | 20 +++++++++++++++++--- 2 files changed, 19 insertions(+), 5 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 89064a6c..a66745ea 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -184,10 +184,10 @@ processModule verbosity modsum flags modMap instIfaceMap = do if not $ isBootSummary modsum then do out verbosity verbose "Creating interface..." - (interface, msg) <- {-# SCC createIterface #-} + (interface, msgs) <- {-# SCC createIterface #-} withTiming getDynFlags "createInterface" (const ()) $ do runWriterGhc $ createInterface tm flags modMap instIfaceMap - liftIO $ mapM_ putStrLn msg + liftIO $ mapM_ putStrLn (nub msgs) dflags <- getDynFlags let (haddockable, haddocked) = ifaceHaddockCoverage interface percentage = round (fromIntegral haddocked * 100 / fromIntegral haddockable :: Double) :: Int diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index cbe55dc4..5d3cf2a6 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -28,7 +28,7 @@ import Haddock.Interface.ParseModuleHeader import Haddock.Parser import Haddock.Types import Name -import Outputable ( showPpr ) +import Outputable ( showPpr, showSDoc ) import RdrName import EnumSet import RnEnv (dataTcOccs) @@ -120,11 +120,11 @@ rename dflags gre = rn -- There is only one name in the environment that matches so -- use it. [a] -> pure (DocIdentifier a) + -- But when there are multiple names available, default to -- type constructors: somewhat awfully GHC returns the -- values in the list positionally. - a:b:_ | isTyConName a -> pure (DocIdentifier a) - | otherwise -> pure (DocIdentifier b) + a:b:_ -> ambiguous dflags x (if isTyConName a then a else b) names DocWarning doc -> DocWarning <$> rn doc DocEmphasis doc -> DocEmphasis <$> rn doc @@ -168,3 +168,17 @@ outOfScope dflags x = tell ["Warning: '" ++ showPpr dflags a ++ "' is out of scope."] pure (monospaced a) monospaced a = DocMonospaced (DocString (showPpr dflags a)) + +-- | Warn about an ambiguous identifier. +ambiguous :: DynFlags -> RdrName -> Name -> [Name] -> ErrMsgM (Doc Name) +ambiguous dflags x dflt names = do + tell [msg] + pure (DocIdentifier dflt) + where + msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++ + concatMap (\n -> " * " ++ defnLoc n ++ "\n") names ++ + " You may be able to disambiguate the identifier by qualifying it or\n" ++ + " by hiding some imports.\n" ++ + " Defaulting to " ++ x_str ++ " defined " ++ defnLoc dflt + x_str = '\'' : showPpr dflags x ++ "'" + defnLoc = showSDoc dflags . pprNameDefnLoc -- cgit v1.2.3 From fa89b060f01d762b0f7b9def5cca5876f9a302db Mon Sep 17 00:00:00 2001 From: Herbert Valerio Riedel Date: Wed, 20 Jun 2018 23:28:46 +0200 Subject: Update Travis CI job --- .travis.yml | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5f9b731d..290b0e0e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -26,12 +26,9 @@ before_cache: matrix: include: - - compiler: "ghc-8.4.2" + - compiler: "ghc-8.6.1" # env: TEST=--disable-tests BENCH=--disable-benchmarks - addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.4.2], sources: [hvr-ghc]}} - - compiler: "ghc-head" - # env: TEST=--disable-tests BENCH=--disable-benchmarks - addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-head], sources: [hvr-ghc]}} + addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.6.1], sources: [hvr-ghc]}} allow_failures: - compiler: "ghc-head" -- cgit v1.2.3 From 9339517a2bd1c16c1d11e66d9c754f0ef702f99a Mon Sep 17 00:00:00 2001 From: Herbert Valerio Riedel Date: Wed, 20 Jun 2018 23:32:41 +0200 Subject: Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... --- .travis.yml | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 39135739..e3e6cd62 100644 --- a/.travis.yml +++ b/.travis.yml @@ -26,15 +26,9 @@ before_cache: matrix: include: - - compiler: "ghc-8.4.2" + - compiler: "ghc-8.4.3" # env: TEST=--disable-tests BENCH=--disable-benchmarks - addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.4.2], sources: [hvr-ghc]}} - - compiler: "ghc-head" - # env: TEST=--disable-tests BENCH=--disable-benchmarks - addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-head], sources: [hvr-ghc]}} - - allow_failures: - - compiler: "ghc-head" + addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.4.3], sources: [hvr-ghc]}} before_install: - HC=${CC} -- cgit v1.2.3 From 61d6f935da97eb96685f07bf385102c2dbc2a33c Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Sat, 30 Jun 2018 13:41:38 +0200 Subject: README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section --- README.md | 41 ++++++++++++++++++++++++++++++++++++----- 1 file changed, 36 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index bfc2261b..51642aab 100644 --- a/README.md +++ b/README.md @@ -11,6 +11,32 @@ Full documentation can be found in the `doc/` subdirectory, in [reStructedText format](http://www.sphinx-doc.org/en/stable/rest.html) format. + +## Project overview + +This project consists of three packages: + +* haddock +* haddock-api +* haddock-library + +### haddock + +The haddock package provides the `haddock` executable. It is implemented as a +tiny wrapper around haddock-api's `Documentation.Haddock.haddock` function. + +### haddock-api + +haddock-api contains the program logic of the `haddock` tool. [The haddocks for +the `Documentation.Haddock` module](http://hackage.haskell.org/package/haddock-api-2.19.0.1/docs/Documentation-Haddock.html) +offer a good overview of haddock-api's functionality. + +### haddock-library + +haddock-library is concerned with the parsing and processing of the Haddock +markup language. + + ## Contributing Please create issues when you have any problems and pull requests if you have some code. @@ -33,7 +59,7 @@ and then proceed using your favourite build tool. ```bash cabal new-build -w ghc-8.4.1 # build & run the test suite -cabal new-test -w ghc-8.4.1 +cabal new-test -w ghc-8.4.1 all ``` #### Using Cabal sandboxes @@ -65,11 +91,16 @@ stack test ### Git Branches If you're a GHC developer and want to update Haddock to work with your -changes, you should be working on `ghc-head` branch instead of `master`. +changes, you should be working on `ghc-head` branch. See instructions at https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/Git/Submodules for an example workflow. -The `master` branch usually requires a GHC from the latest GHC stable -branch. The required GHC version can be inferred from the version -bounds on `ghc` in the respective `.cabal` files. +### Updating `html-test` + +When accepting any changes in the output of `html-test`, it is important +to use the `--haddock-path` option. For example: + +``` +cabal new-run -- html-test --haddock-path $(find dist-newstyle/ -executable -type f -name haddock) --accept +``` -- cgit v1.2.3 From 88316b972e3d47197b1019111bae0f7f87275fce Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Thu, 5 Jul 2018 10:43:35 -0400 Subject: Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. --- haddock-api/src/Haddock/Backends/Hoogle.hs | 4 ++-- hoogle-test/ref/Bug722/test.txt | 16 ++++++++++++++++ hoogle-test/src/Bug722/Bug722.hs | 13 +++++++++++++ 3 files changed, 31 insertions(+), 2 deletions(-) create mode 100644 hoogle-test/ref/Bug722/test.txt create mode 100644 hoogle-test/src/Bug722/Bug722.hs diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 59a4f53c..df626c4c 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -123,7 +123,7 @@ ppExport dflags ExportDecl { expItemDecl = L _ decl , expItemMbDoc = (dc, _) , expItemSubDocs = subdocs , expItemFixities = fixities - } = ppDocumentation dflags dc ++ f decl + } = ppDocumentation dflags dc ++ f decl ++ ppFixities where f (TyClD d@DataDecl{}) = ppData dflags d subdocs f (TyClD d@SynDecl{}) = ppSynonym dflags d @@ -131,7 +131,7 @@ ppExport dflags ExportDecl { expItemDecl = L _ decl f (TyClD (FamDecl d)) = ppFam dflags d f (ForD (ForeignImport name typ _ _)) = [pp_sig dflags [name] (hsSigType typ)] f (ForD (ForeignExport name typ _ _)) = [pp_sig dflags [name] (hsSigType typ)] - f (SigD sig) = ppSig dflags sig ++ ppFixities + f (SigD sig) = ppSig dflags sig f _ = [] ppFixities = concatMap (ppFixity dflags) fixities diff --git a/hoogle-test/ref/Bug722/test.txt b/hoogle-test/ref/Bug722/test.txt new file mode 100644 index 00000000..96f3747b --- /dev/null +++ b/hoogle-test/ref/Bug722/test.txt @@ -0,0 +1,16 @@ +-- Hoogle documentation, generated by Haddock +-- See Hoogle, http://www.haskell.org/hoogle/ + +@package test +@version 0.0.0 + +module Bug722 +class Foo a +(!@#) :: Foo a => a -> a -> a +infixl 4 !@# +type family &* :: * -> * -> * +infixr 3 &* +data a :-& b +(:^&) :: a -> b -> (:-&) a b +infixl 6 :-& +infixl 6 :^& diff --git a/hoogle-test/src/Bug722/Bug722.hs b/hoogle-test/src/Bug722/Bug722.hs new file mode 100644 index 00000000..a33d5b24 --- /dev/null +++ b/hoogle-test/src/Bug722/Bug722.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TypeOperators, TypeFamilies #-} +module Bug722 where + +class Foo a where + (!@#) :: a -> a -> a +infixl 4 !@# + +type family (&*) :: * -> * -> * +infixr 3 &* + +data a :-& b = a :^& b +infixl 6 :-&, :^& + -- cgit v1.2.3 From 657b1b3d519545f8d4ca048c06210d6cbf0f0da0 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Fri, 6 Jul 2018 10:06:32 -0400 Subject: Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case --- haddock-api/src/Haddock/Backends/Hoogle.hs | 8 +++++--- hoogle-test/ref/Bug806/test.txt | 1 + hoogle-test/src/Bug806/Bug806.hs | 1 + 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index df626c4c..a89ac2c7 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -45,13 +45,15 @@ prefix = ["-- Hoogle documentation, generated by Haddock" ppHoogle :: DynFlags -> String -> Version -> String -> Maybe (Doc RdrName) -> [Interface] -> FilePath -> IO () ppHoogle dflags package version synopsis prologue ifaces odir = do - let filename = package ++ ".txt" + let -- Since Hoogle is line based, we want to avoid breaking long lines. + dflags' = dflags{ pprCols = maxBound } + filename = package ++ ".txt" contents = prefix ++ - docWith dflags (drop 2 $ dropWhile (/= ':') synopsis) prologue ++ + docWith dflags' (drop 2 $ dropWhile (/= ':') synopsis) prologue ++ ["@package " ++ package] ++ ["@version " ++ showVersion version | not (null (versionBranch version)) ] ++ - concat [ppModule dflags i | i <- ifaces, OptHide `notElem` ifaceOptions i] + concat [ppModule dflags' i | i <- ifaces, OptHide `notElem` ifaceOptions i] createDirectoryIfMissing True odir h <- openFile (odir filename) WriteMode hSetEncoding h utf8 diff --git a/hoogle-test/ref/Bug806/test.txt b/hoogle-test/ref/Bug806/test.txt index d9a908b3..67e9fd61 100644 --- a/hoogle-test/ref/Bug806/test.txt +++ b/hoogle-test/ref/Bug806/test.txt @@ -21,4 +21,5 @@ class C a where { -- | AT docs type family AT a; + type AT a = Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy))))))))); } diff --git a/hoogle-test/src/Bug806/Bug806.hs b/hoogle-test/src/Bug806/Bug806.hs index 6efcb5cf..45efda77 100644 --- a/hoogle-test/src/Bug806/Bug806.hs +++ b/hoogle-test/src/Bug806/Bug806.hs @@ -21,3 +21,4 @@ v = 42 class C a where -- | 'AT' docs type AT a + type AT a = Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy))))))))) -- cgit v1.2.3 From 197057d07a1c646095bd7199d0de96f24b2273ff Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Thu, 19 Jul 2018 12:29:32 +0200 Subject: haddock-library: Bump bounds for containers --- haddock-library/haddock-library.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index df2dbf93..1fc3f772 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -24,7 +24,7 @@ library build-depends: base >= 4.5 && < 4.13 , bytestring >= 0.9.2.1 && < 0.11 - , containers >= 0.4.2.1 && < 0.6 + , containers >= 0.4.2.1 && < 0.7 , transformers >= 0.3.0 && < 0.6 , text >= 1.2.3.0 && < 1.3 , parsec >= 3.1.13.0 && < 3.2 @@ -74,7 +74,7 @@ test-suite spec base >= 4.5 && < 4.12 , base-compat >= 0.9.3 && < 0.11 , bytestring >= 0.9.2.1 && < 0.11 - , containers >= 0.4.2.1 && < 0.6 + , containers >= 0.4.2.1 && < 0.7 , transformers >= 0.3.0 && < 0.6 , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 -- cgit v1.2.3 From c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Thu, 19 Jul 2018 13:36:45 +0200 Subject: tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes #879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] --- haddock-api/src/Haddock/Convert.hs | 48 ++++++++++++++++++++++++++++++++++++-- 1 file changed, 46 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index 8b227c50..7595f798 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -31,7 +31,7 @@ import NameSet ( emptyNameSet ) import RdrName ( mkVarUnqual ) import PatSyn import SrcLoc ( Located, noLoc, unLoc, GenLocated(..), srcLocSpan ) -import TcType ( tcSplitSigmaTy ) +import TcType import TyCon import Type import TyCoRep @@ -515,7 +515,7 @@ synifyType _ (FunTy t1 t2) = let s2 = synifyType WithinType t2 in noLoc $ HsFunTy s1 s2 synifyType s forallty@(ForAllTy _tv _ty) = - let (tvs, ctx, tau) = tcSplitSigmaTy forallty + let (tvs, ctx, tau) = tcSplitSigmaTyPreserveSynonyms forallty sPhi = HsQualTy { hst_ctxt = synifyCtx ctx , hst_body = synifyType WithinType tau } in case s of @@ -610,3 +610,47 @@ synifyFamInst fi opaque = do ts' = synifyTypes ts annot_ts = zipWith3 annotHsType is_poly_tvs ts ts' is_poly_tvs = mkIsPolyTvs (tyConVisibleTyVars fam_tc) + +{- +Note [Invariant: Never expand type synonyms] + +In haddock, we never want to expand a type synonym that may be presented to the +user, as we want to keep the link to the abstraction captured in the synonym. + +All code in Haddock.Convert must make sure that this invariant holds. + +See https://github.com/haskell/haddock/issues/879 for a bug where this +invariant didn't hold. +-} + +-- | A version of 'TcType.tcSplitSigmaTy' that preserves type synonyms. +-- +-- See Note [Invariant: Never expand type synonyms] +tcSplitSigmaTyPreserveSynonyms :: Type -> ([TyVar], ThetaType, Type) +tcSplitSigmaTyPreserveSynonyms ty = + case tcSplitForAllTysPreserveSynonyms ty of + (tvs, rho) -> case tcSplitPhiTyPreserveSynonyms rho of + (theta, tau) -> (tvs, theta, tau) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitForAllTysPreserveSynonyms :: Type -> ([TyVar], Type) +tcSplitForAllTysPreserveSynonyms ty = split ty ty [] + where + split _ (ForAllTy (TvBndr tv _) ty') tvs = split ty' ty' (tv:tvs) + split orig_ty _ tvs = (reverse tvs, orig_ty) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitPhiTyPreserveSynonyms :: Type -> (ThetaType, Type) +tcSplitPhiTyPreserveSynonyms ty0 = split ty0 [] + where + split ty ts + = case tcSplitPredFunTyPreserveSynonyms_maybe ty of + Just (pred_, ty') -> split ty' (pred_:ts) + Nothing -> (reverse ts, ty) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitPredFunTyPreserveSynonyms_maybe :: Type -> Maybe (PredType, Type) +tcSplitPredFunTyPreserveSynonyms_maybe (FunTy arg res) + | isPredTy arg = Just (arg, res) +tcSplitPredFunTyPreserveSynonyms_maybe _ + = Nothing -- cgit v1.2.3 From 133e9c2c168db19c1135479f7ab144c4e33af2a4 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Fri, 20 Jul 2018 03:01:49 -0700 Subject: Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output --- haddock-api/src/Haddock/Interface/Create.hs | 7 +++++-- haddock-api/src/Haddock/Types.hs | 3 +++ html-test/ref/TypeFamilies.html | 30 +++++++++++++++++++---------- html-test/ref/TypeFamilies2.html | 18 +++++++++++------ 4 files changed, 40 insertions(+), 18 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index a35e2053..ced7cae5 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -419,9 +419,12 @@ mkMaps dflags pkgName gre instances decls = do instanceMap = M.fromList [ (getSrcSpan n, n) | n <- instances ] names :: SrcSpan -> HsDecl GhcRn -> [Name] - names l (InstD d) = maybeToList (M.lookup loc instanceMap) -- See note [2]. + names _ (InstD d) = maybeToList (M.lookup loc instanceMap) -- See note [2]. where loc = case d of - TyFamInstD _ -> l -- The CoAx's loc is the whole line, but only for TFs + -- The CoAx's loc is the whole line, but only for TFs. The + -- workaround is to dig into the family instance declaration and + -- get the identifier with the right location. + TyFamInstD (TyFamInstDecl d') -> getLoc (feqn_tycon (hsib_body d')) _ -> getInstLoc d names l (DerivD {}) = maybeToList (M.lookup l instanceMap) -- See note [2]. names _ decl = getMainDeclBinder decl diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 36ed7baf..5ef5a7b9 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -28,6 +28,7 @@ module Haddock.Types ( import Control.Exception import Control.Arrow hiding ((<+>)) import Control.DeepSeq +import Control.Monad.IO.Class (MonadIO(..)) import Data.Typeable import Data.Map (Map) import Data.Data (Data) @@ -661,6 +662,8 @@ instance Monad ErrMsgGhc where m >>= k = WriterGhc $ runWriterGhc m >>= \ (a, msgs1) -> fmap (second (msgs1 ++)) (runWriterGhc (k a)) +instance MonadIO ErrMsgGhc where + liftIO m = WriterGhc (fmap (\x -> (x, [])) (liftIO m)) ----------------------------------------------------------------------------- -- * Pass sensitive types diff --git a/html-test/ref/TypeFamilies.html b/html-test/ref/TypeFamilies.html index 190f376e..1fe20c4b 100644 --- a/html-test/ref/TypeFamilies.html +++ b/html-test/ref/TypeFamilies.html @@ -352,8 +352,10 @@ > #

                  External instance

                  #

                  Doc for: type instance Foo X = Y

                  #

                  Doc for: type instance Foo Y = X

                  #

                  Doc for: type instance Foo Y = X

                  #

                  Doc for: type instance Foo X = Y

                  #

                  Should be visible, but with a hidden right hand side

                  #

                  Should be visible, but with a hidden right hand side

                  #

                  External instance

                  Date: Fri, 20 Jul 2018 03:02:16 -0700 Subject: Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. --- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 8 +++--- haddock-api/src/Haddock/Backends/Xhtml/Layout.hs | 33 +++++++++++++----------- 2 files changed, 22 insertions(+), 19 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 1daf9ace..01380c94 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -572,9 +572,9 @@ ppInstances links origin instances splice unicode pkg qual -- force Splice = True to use line URLs where instName = getOccString origin - instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) + instDecl :: Int -> DocInstance DocNameI -> (SubDecl, Maybe Module, Located DocName) instDecl no (inst, mdoc, loc, mdl) = - ((ppInstHead links splice unicode qual mdoc origin False no inst mdl), loc) + ((ppInstHead links splice unicode qual mdoc origin False no inst mdl), mdl, loc) ppOrphanInstances :: LinksInfo @@ -587,9 +587,9 @@ ppOrphanInstances links instances splice unicode pkg qual instOrigin :: InstHead name -> InstOrigin (IdP name) instOrigin inst = OriginClass (ihdClsName inst) - instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) + instDecl :: Int -> DocInstance DocNameI -> (SubDecl, Maybe Module, Located DocName) instDecl no (inst, mdoc, loc, mdl) = - ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst mdl), loc) + ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst Nothing), mdl, loc) ppInstHead :: LinksInfo -> Splice -> Unicode -> Qualification diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index 501caa4b..1c44ffda 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -40,7 +40,6 @@ module Haddock.Backends.Xhtml.Layout ( topDeclElem, declElem, ) where - import Haddock.Backends.Xhtml.DocMarkup import Haddock.Backends.Xhtml.Types import Haddock.Backends.Xhtml.Utils @@ -48,6 +47,7 @@ import Haddock.Types import Haddock.Utils (makeAnchorId, nameAnchorId) import qualified Data.Map as Map import Text.XHtml hiding ( name, title, quote ) +import Data.Maybe (fromMaybe) import FastString ( unpackFS ) import GHC @@ -151,20 +151,22 @@ subTable pkg qual decls = Just $ table << aboves (concatMap subRow decls) -- | Sub table with source information (optional). subTableSrc :: Maybe Package -> Qualification -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Maybe Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Maybe Html subTableSrc _ _ _ _ [] = Nothing subTableSrc pkg qual lnks splice decls = Just $ table << aboves (concatMap subRow decls) where - subRow ((decl, mdoc, subs),L loc dn) = + subRow ((decl, mdoc, subs), mdl, L loc dn) = (td ! [theclass "src clearfix"] << (thespan ! [theclass "inst-left"] << decl) - <+> linkHtml loc dn + <+> linkHtml loc mdl dn <-> docElement td << fmap (docToHtml Nothing pkg qual) mdoc ) : map (cell . (td <<)) subs - linkHtml loc@(RealSrcSpan _) dn = links lnks loc splice dn - linkHtml _ _ = noHtml + + linkHtml :: SrcSpan -> Maybe Module -> DocName -> Html + linkHtml loc@(RealSrcSpan _) mdl dn = links lnks loc splice mdl dn + linkHtml _ _ _ = noHtml subBlock :: [Html] -> Maybe Html subBlock [] = Nothing @@ -197,7 +199,7 @@ subEquations pkg qual = divSubDecls "equations" "Equations" . subTable pkg qual subInstances :: Maybe Package -> Qualification -> String -- ^ Class name, used for anchor generation -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Html subInstances pkg qual nm lnks splice = maybe noHtml wrap . instTable where wrap contents = subSection (collapseDetails id_ DetailsOpen (summary +++ contents)) @@ -209,7 +211,7 @@ subInstances pkg qual nm lnks splice = maybe noHtml wrap . instTable subOrphanInstances :: Maybe Package -> Qualification -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Html subOrphanInstances pkg qual lnks splice = maybe noHtml wrap . instTable where wrap = ((h1 << "Orphan instances") +++) @@ -268,13 +270,13 @@ declElem = paragraph ! [theclass "src"] -- it adds a source and wiki link at the right hand side of the box topDeclElem :: LinksInfo -> SrcSpan -> Bool -> [DocName] -> Html -> Html topDeclElem lnks loc splice names html = - declElem << (html <+> (links lnks loc splice $ head names)) + declElem << (html <+> (links lnks loc splice Nothing $ head names)) -- FIXME: is it ok to simply take the first name? -- | Adds a source and wiki link at the right hand side of the box. -- Name must be documented, otherwise we wouldn't get here. -links :: LinksInfo -> SrcSpan -> Bool -> DocName -> Html -links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice docName@(Documented n mdl) = +links :: LinksInfo -> SrcSpan -> Bool -> Maybe Module -> DocName -> Html +links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice mdl' docName@(Documented n mdl) = srcLink <+> wikiLink <+> (selfLink ! [theclass "selflink"] << "#") where selfLink = linkedAnchor (nameAnchorId (nameOccName (getName docName))) @@ -298,12 +300,13 @@ links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice docName@(Docume -- For source links, we want to point to the original module, -- because only that will have the source. - -- TODO: do something about type instances. They will point to - -- the module defining the type family, which is wrong. - origMod = nameModule n + -- + -- 'mdl'' is a way of "overriding" the module. Without it, instances + -- will point to the module defining the class/family, which is wrong. + origMod = fromMaybe (nameModule n) mdl' origPkg = moduleUnitId origMod fname = case loc of RealSrcSpan l -> unpackFS (srcSpanFile l) UnhelpfulSpan _ -> error "links: UnhelpfulSpan" -links _ _ _ _ = noHtml +links _ _ _ _ _ = noHtml -- cgit v1.2.3 From 5ec7715d418bfac0f26aec6039792a99a6e89370 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Fri, 20 Jul 2018 04:49:47 -0700 Subject: Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see #191). A regression test never hurt anyone. :) --- html-test/ref/Unicode2.html | 100 ++++++++++++++++++++++++++++++++++++++++++++ html-test/src/Unicode2.hs | 18 ++++++++ 2 files changed, 118 insertions(+) create mode 100644 html-test/ref/Unicode2.html create mode 100644 html-test/src/Unicode2.hs diff --git a/html-test/ref/Unicode2.html b/html-test/ref/Unicode2.html new file mode 100644 index 00000000..bf667bae --- /dev/null +++ b/html-test/ref/Unicode2.html @@ -0,0 +1,100 @@ +Unicode2
                  Safe HaskellSafe

                  Unicode2

                  Synopsis

                  Documentation

                  ü :: () #

                  All of the following work with a unicode character ü:

                  • an italicized ü
                  • inline code ü
                  • a code block:
                  ü
                  \ No newline at end of file diff --git a/html-test/src/Unicode2.hs b/html-test/src/Unicode2.hs new file mode 100644 index 00000000..ca6b18ba --- /dev/null +++ b/html-test/src/Unicode2.hs @@ -0,0 +1,18 @@ +module Unicode2 where + +-- | All of the following work with a unicode character ü: +-- +-- * an italicized /ü/ +-- +-- * inline code @ü@ +-- +-- * a code block: +-- +-- > ü +-- +-- * a url +-- +-- * a link to 'ü' +-- +ü :: () +ü = () -- cgit v1.2.3 From 0861affeca4d72938f05a2eceddfae2c19199071 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Fri, 20 Jul 2018 15:06:06 +0200 Subject: Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers --- doc/markup.rst | 13 ++---- .../test/Documentation/Haddock/ParserSpec.hs | 48 +++++++++++++++++++++- 2 files changed, 51 insertions(+), 10 deletions(-) diff --git a/doc/markup.rst b/doc/markup.rst index acabaa28..590bee00 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -845,10 +845,13 @@ Hyperlinked Identifiers ~~~~~~~~~~~~~~~~~~~~~~~ Referring to a Haskell identifier, whether it be a type, class, -constructor, or function, is done by surrounding it with single quotes: :: +constructor, or function, is done by surrounding it with a combination +of single quotes and backticks. For example: :: -- | This module defines the type 'T'. +```T``` is also ok. ``'T``` and ```T'`` are accepted but less common. + If there is an entity ``T`` in scope in the current module, then the documentation will hyperlink the reference in the text to the definition of ``T`` (if the output format supports hyperlinking, of course; in a @@ -876,14 +879,6 @@ apostrophes themselves: to hyperlink ``foo'`` one would simply type ``'foo''``. To hyperlink identifiers written in infix form, simply put them in quotes as always: ``'`elem`'``. -For compatibility with other systems, the following alternative form of -markup is accepted [3]_: ```T'``. - -.. [3] - We chose not to use this as the primary markup for identifiers - because strictly speaking the ````` character should not be used as a - left quote, it is a grave accent. - Emphasis, Bold and Monospaced Text ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs index 86ed3b35..0449c917 100644 --- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs +++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs @@ -86,6 +86,18 @@ spec = do it "parses identifiers enclosed within backticks" $ do "`foo`" `shouldParseTo` DocIdentifier "foo" + it "parses identifiers preceded by a backtick and followed by a single quote" $ do + "`foo'" `shouldParseTo` DocIdentifier "foo" + + it "parses identifiers preceded by a single quote and followed by a backtick" $ do + "'foo`" `shouldParseTo` DocIdentifier "foo" + + it "can parse a constructor identifier" $ do + "'Foo'" `shouldParseTo` DocIdentifier "Foo" + + it "can parse a qualified identifier" $ do + "'Foo.bar'" `shouldParseTo` DocIdentifier "Foo.bar" + it "parses a word with an one of the delimiters in it as DocString" $ do "don't" `shouldParseTo` "don't" @@ -99,9 +111,43 @@ spec = do it "doesn't parse empty identifiers" $ do "``" `shouldParseTo` "``" - it "can parse infix identifiers" $ do + it "can parse an identifier in infix notation enclosed within backticks" $ do "``infix``" `shouldParseTo` "`" <> DocIdentifier "infix" <> "`" + it "can parse identifiers containing a single quote" $ do + "'don't'" `shouldParseTo` DocIdentifier "don't" + + it "can parse identifiers ending with a single quote" $ do + "'foo''" `shouldParseTo` DocIdentifier "foo'" + + it "can parse an identifier containing a digit" $ do + "'f0'" `shouldParseTo` DocIdentifier "f0" + + it "can parse an identifier containing unicode characters" $ do + "'λ'" `shouldParseTo` DocIdentifier "λ" + + it "can parse a single quote followed by an identifier" $ do + "''foo'" `shouldParseTo` "'" <> DocIdentifier "foo" + + it "can parse an identifier that starts with an underscore" $ do + "'_x'" `shouldParseTo` DocIdentifier "_x" + + context "when parsing operators" $ do + it "can parse an operator enclosed within single quotes" $ do + "'.='" `shouldParseTo` DocIdentifier ".=" + + it "can parse a qualified operator" $ do + "'F..'" `shouldParseTo` DocIdentifier "F.." + + it "can parse a constructor operator" $ do + "':='" `shouldParseTo` DocIdentifier ":=" + + it "can parse a qualified constructor operator" $ do + "'F.:='" `shouldParseTo` DocIdentifier "F.:=" + + it "can parse a unicode operator" $ do + "'∧'" `shouldParseTo` DocIdentifier "∧" + context "when parsing URLs" $ do it "parses a URL" $ do "" `shouldParseTo` hyperlink "http://example.com/" Nothing -- cgit v1.2.3 From ab9cb915c95a2436d76ed86a1e36f00ad92c1699 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Fri, 20 Jul 2018 16:02:02 +0200 Subject: Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes #879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes #873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes #877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see #191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) --- README.md | 41 +- doc/markup.rst | 13 +- haddock-api/haddock-api.cabal | 4 +- haddock-api/src/Haddock/Backends/Hoogle.hs | 14 +- haddock-api/src/Haddock/Backends/LaTeX.hs | 123 ++-- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 130 ++-- haddock-api/src/Haddock/Backends/Xhtml/Layout.hs | 33 +- haddock-api/src/Haddock/Convert.hs | 48 +- haddock-api/src/Haddock/GhcUtils.hs | 96 +++ haddock-api/src/Haddock/Interface/Create.hs | 7 +- haddock-api/src/Haddock/Types.hs | 3 + .../test/Documentation/Haddock/ParserSpec.hs | 48 +- haddock-test/src/Test/Haddock.hs | 4 +- haddock.cabal | 2 +- hoogle-test/ref/Bug722/test.txt | 16 + hoogle-test/ref/Bug806/test.txt | 1 + hoogle-test/ref/Bug873/test.txt | 26 + hoogle-test/ref/type-sigs/test.txt | 4 +- hoogle-test/src/Bug722/Bug722.hs | 13 + hoogle-test/src/Bug806/Bug806.hs | 1 + hoogle-test/src/Bug873/Bug873.hs | 5 + html-test/ref/A.html | 24 +- html-test/ref/Bug280.html | 4 +- html-test/ref/Bug3.html | 8 +- html-test/ref/Bug310.html | 44 +- html-test/ref/Bug387.html | 16 +- html-test/ref/Bug4.html | 8 +- html-test/ref/Bug546.html | 20 +- html-test/ref/Bug548.html | 270 ++++++-- html-test/ref/Bug574.html | 86 +++ html-test/ref/Bug6.html | 60 +- html-test/ref/Bug613.html | 10 +- html-test/ref/Bug8.html | 4 +- html-test/ref/BugDeprecated.html | 48 +- html-test/ref/BugExportHeadings.html | 48 +- html-test/ref/Bugs.html | 4 +- html-test/ref/BundledPatterns.html | 20 +- html-test/ref/BundledPatterns2.html | 20 +- html-test/ref/ConstructorArgs.html | 720 +++++++++++++++++++++ html-test/ref/ConstructorPatternExport.html | 26 +- html-test/ref/DeprecatedFunction.html | 16 +- html-test/ref/DeprecatedFunction2.html | 8 +- html-test/ref/DeprecatedFunction3.html | 8 +- html-test/ref/DeprecatedModule.html | 4 +- html-test/ref/DeprecatedModule2.html | 4 +- html-test/ref/DeprecatedNewtype.html | 16 +- html-test/ref/DeprecatedReExport.html | 8 +- html-test/ref/DeprecatedRecord.html | 16 +- html-test/ref/DeprecatedTypeSynonym.html | 16 +- html-test/ref/Examples.html | 16 +- html-test/ref/FunArgs.html | 16 +- html-test/ref/GADTRecords.html | 32 +- html-test/ref/GadtConstructorArgs.html | 192 ++++++ html-test/ref/Hash.html | 96 ++- html-test/ref/HiddenInstances.html | 26 +- html-test/ref/Hyperlinks.html | 8 +- html-test/ref/Instances.html | 398 ++++++++++-- html-test/ref/Math.html | 8 +- html-test/ref/ModuleWithWarning.html | 4 +- html-test/ref/NoLayout.html | 8 +- html-test/ref/OrphanInstances.html | 4 +- html-test/ref/OrphanInstancesClass.html | 8 +- html-test/ref/OrphanInstancesType.html | 8 +- html-test/ref/PatternSyns.html | 24 +- html-test/ref/PromotedTypes.html | 8 +- html-test/ref/Properties.html | 16 +- html-test/ref/QuantifiedConstraints.html | 100 +++ html-test/ref/QuasiExpr.html | 80 ++- html-test/ref/QuasiQuote.html | 4 +- html-test/ref/SpuriousSuperclassConstraints.html | 38 +- html-test/ref/TH.html | 6 +- html-test/ref/Test.html | 320 +++++++-- html-test/ref/Threaded.html | 8 +- html-test/ref/Threaded_TH.html | 12 +- html-test/ref/Ticket112.html | 4 +- html-test/ref/Ticket75.html | 8 +- html-test/ref/TitledPicture.html | 16 +- html-test/ref/TypeFamilies.html | 98 ++- html-test/ref/TypeFamilies2.html | 18 +- html-test/ref/Unicode.html | 8 +- html-test/ref/Unicode2.html | 100 +++ html-test/ref/Visible.html | 6 +- html-test/src/Bug745.hs | 8 + html-test/src/ConstructorArgs.hs | 56 ++ html-test/src/GadtConstructorArgs.hs | 13 + html-test/src/QuantifiedConstraints.hs | 11 + html-test/src/Unicode2.hs | 18 + latex-test/ref/ConstructorArgs/ConstructorArgs.tex | 69 ++ latex-test/ref/ConstructorArgs/haddock.sty | 57 ++ latex-test/ref/ConstructorArgs/main.tex | 11 + .../GadtConstructorArgs/GadtConstructorArgs.tex | 25 + latex-test/ref/GadtConstructorArgs/haddock.sty | 57 ++ latex-test/ref/GadtConstructorArgs/main.tex | 11 + latex-test/src/ConstructorArgs/ConstructorArgs.hs | 56 ++ .../src/GadtConstructorArgs/GadtConstructorArgs.hs | 13 + 95 files changed, 3658 insertions(+), 613 deletions(-) create mode 100644 hoogle-test/ref/Bug722/test.txt create mode 100644 hoogle-test/ref/Bug873/test.txt create mode 100644 hoogle-test/src/Bug722/Bug722.hs create mode 100644 hoogle-test/src/Bug873/Bug873.hs create mode 100644 html-test/ref/Bug574.html create mode 100644 html-test/ref/ConstructorArgs.html create mode 100644 html-test/ref/GadtConstructorArgs.html create mode 100644 html-test/ref/QuantifiedConstraints.html create mode 100644 html-test/ref/Unicode2.html create mode 100644 html-test/src/Bug745.hs create mode 100644 html-test/src/ConstructorArgs.hs create mode 100644 html-test/src/GadtConstructorArgs.hs create mode 100644 html-test/src/QuantifiedConstraints.hs create mode 100644 html-test/src/Unicode2.hs create mode 100644 latex-test/ref/ConstructorArgs/ConstructorArgs.tex create mode 100644 latex-test/ref/ConstructorArgs/haddock.sty create mode 100644 latex-test/ref/ConstructorArgs/main.tex create mode 100644 latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex create mode 100644 latex-test/ref/GadtConstructorArgs/haddock.sty create mode 100644 latex-test/ref/GadtConstructorArgs/main.tex create mode 100644 latex-test/src/ConstructorArgs/ConstructorArgs.hs create mode 100644 latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs diff --git a/README.md b/README.md index bfc2261b..51642aab 100644 --- a/README.md +++ b/README.md @@ -11,6 +11,32 @@ Full documentation can be found in the `doc/` subdirectory, in [reStructedText format](http://www.sphinx-doc.org/en/stable/rest.html) format. + +## Project overview + +This project consists of three packages: + +* haddock +* haddock-api +* haddock-library + +### haddock + +The haddock package provides the `haddock` executable. It is implemented as a +tiny wrapper around haddock-api's `Documentation.Haddock.haddock` function. + +### haddock-api + +haddock-api contains the program logic of the `haddock` tool. [The haddocks for +the `Documentation.Haddock` module](http://hackage.haskell.org/package/haddock-api-2.19.0.1/docs/Documentation-Haddock.html) +offer a good overview of haddock-api's functionality. + +### haddock-library + +haddock-library is concerned with the parsing and processing of the Haddock +markup language. + + ## Contributing Please create issues when you have any problems and pull requests if you have some code. @@ -33,7 +59,7 @@ and then proceed using your favourite build tool. ```bash cabal new-build -w ghc-8.4.1 # build & run the test suite -cabal new-test -w ghc-8.4.1 +cabal new-test -w ghc-8.4.1 all ``` #### Using Cabal sandboxes @@ -65,11 +91,16 @@ stack test ### Git Branches If you're a GHC developer and want to update Haddock to work with your -changes, you should be working on `ghc-head` branch instead of `master`. +changes, you should be working on `ghc-head` branch. See instructions at https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/Git/Submodules for an example workflow. -The `master` branch usually requires a GHC from the latest GHC stable -branch. The required GHC version can be inferred from the version -bounds on `ghc` in the respective `.cabal` files. +### Updating `html-test` + +When accepting any changes in the output of `html-test`, it is important +to use the `--haddock-path` option. For example: + +``` +cabal new-run -- html-test --haddock-path $(find dist-newstyle/ -executable -type f -name haddock) --accept +``` diff --git a/doc/markup.rst b/doc/markup.rst index 1a278da3..a9878837 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -859,10 +859,13 @@ Hyperlinked Identifiers ~~~~~~~~~~~~~~~~~~~~~~~ Referring to a Haskell identifier, whether it be a type, class, -constructor, or function, is done by surrounding it with single quotes: :: +constructor, or function, is done by surrounding it with a combination +of single quotes and backticks. For example: :: -- | This module defines the type 'T'. +```T``` is also ok. ``'T``` and ```T'`` are accepted but less common. + If there is an entity ``T`` in scope in the current module, then the documentation will hyperlink the reference in the text to the definition of ``T`` (if the output format supports hyperlinking, of course; in a @@ -890,14 +893,6 @@ apostrophes themselves: to hyperlink ``foo'`` one would simply type ``'foo''``. To hyperlink identifiers written in infix form, simply put them in quotes as always: ``'`elem`'``. -For compatibility with other systems, the following alternative form of -markup is accepted [3]_: ```T'``. - -.. [3] - We chose not to use this as the primary markup for identifiers - because strictly speaking the ````` character should not be used as a - left quote, it is a grave accent. - Emphasis, Bold and Monospaced Text ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index e1a52824..6a7a932b 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -42,7 +42,7 @@ library -- this package typically supports only single major versions build-depends: base ^>= 4.12.0 , Cabal ^>= 2.3.0 - , ghc ^>= 8.6 + , ghc ^>= 8.5 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 @@ -167,7 +167,7 @@ test-suite spec Haddock.Backends.Hyperlinker.Types build-depends: Cabal ^>= 2.3 - , ghc ^>= 8.6 + , ghc ^>= 8.5 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 257a8d6d..885c608b 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -46,13 +46,15 @@ prefix = ["-- Hoogle documentation, generated by Haddock" ppHoogle :: DynFlags -> String -> Version -> String -> Maybe (Doc RdrName) -> [Interface] -> FilePath -> IO () ppHoogle dflags package version synopsis prologue ifaces odir = do - let filename = package ++ ".txt" + let -- Since Hoogle is line based, we want to avoid breaking long lines. + dflags' = dflags{ pprCols = maxBound } + filename = package ++ ".txt" contents = prefix ++ - docWith dflags (drop 2 $ dropWhile (/= ':') synopsis) prologue ++ + docWith dflags' (drop 2 $ dropWhile (/= ':') synopsis) prologue ++ ["@package " ++ package] ++ ["@version " ++ showVersion version | not (null (versionBranch version)) ] ++ - concat [ppModule dflags i | i <- ifaces, OptHide `notElem` ifaceOptions i] + concat [ppModule dflags' i | i <- ifaces, OptHide `notElem` ifaceOptions i] createDirectoryIfMissing True odir h <- openFile (odir filename) WriteMode hSetEncoding h utf8 @@ -89,7 +91,7 @@ dropHsDocTy = f outHsType :: (a ~ GhcPass p, OutputableBndrId a) => DynFlags -> HsType a -> String -outHsType dflags = out dflags . dropHsDocTy +outHsType dflags = out dflags . reparenType . dropHsDocTy dropComment :: String -> String @@ -123,7 +125,7 @@ ppExport dflags ExportDecl { expItemDecl = L _ decl , expItemMbDoc = (dc, _) , expItemSubDocs = subdocs , expItemFixities = fixities - } = ppDocumentation dflags dc ++ f decl + } = ppDocumentation dflags dc ++ f decl ++ ppFixities where f (TyClD _ d@DataDecl{}) = ppData dflags d subdocs f (TyClD _ d@SynDecl{}) = ppSynonym dflags d @@ -131,7 +133,7 @@ ppExport dflags ExportDecl { expItemDecl = L _ decl f (TyClD _ (FamDecl _ d)) = ppFam dflags d f (ForD _ (ForeignImport _ name typ _)) = [pp_sig dflags [name] (hsSigType typ)] f (ForD _ (ForeignExport _ name typ _)) = [pp_sig dflags [name] (hsSigType typ)] - f (SigD _ sig) = ppSig dflags sig ++ ppFixities + f (SigD _ sig) = ppSig dflags sig f _ = [] ppFixities = concatMap (ppFixity dflags) fixities diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index c0da1f0c..4a3e9d03 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -906,24 +906,6 @@ sumParens = ubxparens . hsep . punctuate (text " | ") -- Stolen from Html and tweaked for LaTeX generation ------------------------------------------------------------------------------- - -pREC_TOP, pREC_FUN, pREC_OP, pREC_CON :: Int - -pREC_TOP = (0 :: Int) -- type in ParseIface.y in GHC -pREC_FUN = (1 :: Int) -- btype in ParseIface.y in GHC - -- Used for LH arg of (->) -pREC_OP = (2 :: Int) -- Used for arg of any infix operator - -- (we don't keep their fixities around) -pREC_CON = (3 :: Int) -- Used for arg of type applicn: - -- always parenthesise unless atomic - -maybeParen :: Int -- Precedence of context - -> Int -- Precedence of top-level operator - -> LaTeX -> LaTeX -- Wrap in parens if (ctxt >= op) -maybeParen ctxt_prec op_prec p | ctxt_prec >= op_prec = parens p - | otherwise = p - - ppLType, ppLParendType, ppLFunLhType :: Bool -> Located (HsType DocNameI) -> LaTeX ppLType unicode y = ppType unicode (unLoc y) ppLParendType unicode y = ppParendType unicode (unLoc y) @@ -931,72 +913,70 @@ ppLFunLhType unicode y = ppFunLhType unicode (unLoc y) ppType, ppParendType, ppFunLhType :: Bool -> HsType DocNameI -> LaTeX -ppType unicode ty = ppr_mono_ty pREC_TOP ty unicode -ppParendType unicode ty = ppr_mono_ty pREC_CON ty unicode -ppFunLhType unicode ty = ppr_mono_ty pREC_FUN ty unicode +ppType unicode ty = ppr_mono_ty (reparenTypePrec PREC_TOP ty) unicode +ppParendType unicode ty = ppr_mono_ty (reparenTypePrec PREC_TOP ty) unicode +ppFunLhType unicode ty = ppr_mono_ty (reparenTypePrec PREC_FUN ty) unicode ppLKind :: Bool -> LHsKind DocNameI -> LaTeX ppLKind unicode y = ppKind unicode (unLoc y) ppKind :: Bool -> HsKind DocNameI -> LaTeX -ppKind unicode ki = ppr_mono_ty pREC_TOP ki unicode +ppKind unicode ki = ppr_mono_ty (reparenTypePrec PREC_TOP ki) unicode -- Drop top-level for-all type variables in user style -- since they are implicit in Haskell -ppr_mono_lty :: Int -> LHsType DocNameI -> Bool -> LaTeX -ppr_mono_lty ctxt_prec ty unicode = ppr_mono_ty ctxt_prec (unLoc ty) unicode - - -ppr_mono_ty :: Int -> HsType DocNameI -> Bool -> LaTeX -ppr_mono_ty ctxt_prec (HsForAllTy _ tvs ty) unicode - = maybeParen ctxt_prec pREC_FUN $ - sep [ hsep (forallSymbol unicode : ppTyVars tvs) <> dot - , ppr_mono_lty pREC_TOP ty unicode ] -ppr_mono_ty ctxt_prec (HsQualTy _ ctxt ty) unicode - = maybeParen ctxt_prec pREC_FUN $ - sep [ ppLContext ctxt unicode - , ppr_mono_lty pREC_TOP ty unicode ] - -ppr_mono_ty _ (HsBangTy _ b ty) u = ppBang b <> ppLParendType u ty -ppr_mono_ty _ (HsTyVar _ NotPromoted (L _ name)) _ = ppDocName name -ppr_mono_ty _ (HsTyVar _ Promoted (L _ name)) _ = char '\'' <> ppDocName name -ppr_mono_ty ctxt_prec (HsFunTy _ ty1 ty2) u = ppr_fun_ty ctxt_prec ty1 ty2 u -ppr_mono_ty _ (HsTupleTy _ con tys) u = tupleParens con (map (ppLType u) tys) -ppr_mono_ty _ (HsSumTy _ tys) u = sumParens (map (ppLType u) tys) -ppr_mono_ty _ (HsKindSig _ ty kind) u = parens (ppr_mono_lty pREC_TOP ty u <+> dcolon u <+> ppLKind u kind) -ppr_mono_ty _ (HsListTy _ ty) u = brackets (ppr_mono_lty pREC_TOP ty u) -ppr_mono_ty _ (HsIParamTy _ (L _ n) ty) u = brackets (ppIPName n <+> dcolon u <+> ppr_mono_lty pREC_TOP ty u) -ppr_mono_ty _ (HsSpliceTy {}) _ = error "ppr_mono_ty HsSpliceTy" -ppr_mono_ty _ (HsRecTy {}) _ = text "{..}" -ppr_mono_ty _ (XHsType (NHsCoreTy {})) _ = error "ppr_mono_ty HsCoreTy" -ppr_mono_ty _ (HsExplicitListTy _ Promoted tys) u = Pretty.quote $ brackets $ hsep $ punctuate comma $ map (ppLType u) tys -ppr_mono_ty _ (HsExplicitListTy _ NotPromoted tys) u = brackets $ hsep $ punctuate comma $ map (ppLType u) tys -ppr_mono_ty _ (HsExplicitTupleTy _ tys) u = Pretty.quote $ parenList $ map (ppLType u) tys - -ppr_mono_ty ctxt_prec (HsAppTy _ fun_ty arg_ty) unicode - = maybeParen ctxt_prec pREC_CON $ - hsep [ppr_mono_lty pREC_FUN fun_ty unicode, ppr_mono_lty pREC_CON arg_ty unicode] - -ppr_mono_ty ctxt_prec (HsOpTy _ ty1 op ty2) unicode - = maybeParen ctxt_prec pREC_FUN $ - ppr_mono_lty pREC_OP ty1 unicode <+> ppr_op <+> ppr_mono_lty pREC_OP ty2 unicode +ppr_mono_lty :: LHsType DocNameI -> Bool -> LaTeX +ppr_mono_lty ty unicode = ppr_mono_ty (unLoc ty) unicode + + +ppr_mono_ty :: HsType DocNameI -> Bool -> LaTeX +ppr_mono_ty (HsForAllTy _ tvs ty) unicode + = sep [ hsep (forallSymbol unicode : ppTyVars tvs) <> dot + , ppr_mono_lty ty unicode ] +ppr_mono_ty (HsQualTy _ ctxt ty) unicode + = sep [ ppLContext ctxt unicode + , ppr_mono_lty ty unicode ] +ppr_mono_ty (HsFunTy _ ty1 ty2) u + = sep [ ppr_mono_lty ty1 u + , arrow u <+> ppr_mono_lty ty2 u ] + +ppr_mono_ty (HsBangTy _ b ty) u = ppBang b <> ppLParendType u ty +ppr_mono_ty (HsTyVar _ NotPromoted (L _ name)) _ = ppDocName name +ppr_mono_ty (HsTyVar _ Promoted (L _ name)) _ = char '\'' <> ppDocName name +ppr_mono_ty (HsTupleTy _ con tys) u = tupleParens con (map (ppLType u) tys) +ppr_mono_ty (HsSumTy _ tys) u = sumParens (map (ppLType u) tys) +ppr_mono_ty (HsKindSig _ ty kind) u = parens (ppr_mono_lty ty u <+> dcolon u <+> ppLKind u kind) +ppr_mono_ty (HsListTy _ ty) u = brackets (ppr_mono_lty ty u) +ppr_mono_ty (HsIParamTy _ (L _ n) ty) u = brackets (ppIPName n <+> dcolon u <+> ppr_mono_lty ty u) +ppr_mono_ty (HsSpliceTy {}) _ = error "ppr_mono_ty HsSpliceTy" +ppr_mono_ty (HsRecTy {}) _ = text "{..}" +ppr_mono_ty (XHsType (NHsCoreTy {})) _ = error "ppr_mono_ty HsCoreTy" +ppr_mono_ty (HsExplicitListTy _ Promoted tys) u = Pretty.quote $ brackets $ hsep $ punctuate comma $ map (ppLType u) tys +ppr_mono_ty (HsExplicitListTy _ NotPromoted tys) u = brackets $ hsep $ punctuate comma $ map (ppLType u) tys +ppr_mono_ty (HsExplicitTupleTy _ tys) u = Pretty.quote $ parenList $ map (ppLType u) tys + +ppr_mono_ty (HsAppTy _ fun_ty arg_ty) unicode + = hsep [ppr_mono_lty fun_ty unicode, ppr_mono_lty arg_ty unicode] + +ppr_mono_ty (HsOpTy _ ty1 op ty2) unicode + = ppr_mono_lty ty1 unicode <+> ppr_op <+> ppr_mono_lty ty2 unicode where ppr_op = if not (isSymOcc occName) then char '`' <> ppLDocName op <> char '`' else ppLDocName op occName = nameOccName . getName . unLoc $ op -ppr_mono_ty ctxt_prec (HsParTy _ ty) unicode --- = parens (ppr_mono_lty pREC_TOP ty) - = ppr_mono_lty ctxt_prec ty unicode +ppr_mono_ty (HsParTy _ ty) unicode + = parens (ppr_mono_lty ty unicode) +-- = ppr_mono_lty ty unicode -ppr_mono_ty ctxt_prec (HsDocTy _ ty _) unicode - = ppr_mono_lty ctxt_prec ty unicode +ppr_mono_ty (HsDocTy _ ty _) unicode + = ppr_mono_lty ty unicode -ppr_mono_ty _ (HsWildCardTy (AnonWildCard _)) _ = char '_' +ppr_mono_ty (HsWildCardTy (AnonWildCard _)) _ = char '_' -ppr_mono_ty _ (HsTyLit _ t) u = ppr_tylit t u -ppr_mono_ty _ (HsStarTy _ isUni) unicode = starSymbol (isUni || unicode) +ppr_mono_ty (HsTyLit _ t) u = ppr_tylit t u +ppr_mono_ty (HsStarTy _ isUni) unicode = starSymbol (isUni || unicode) ppr_tylit :: HsTyLit -> Bool -> LaTeX @@ -1006,15 +986,6 @@ ppr_tylit (HsStrTy _ s) _ = text (show s) -- XXX: Do something with Unicode parameter? -ppr_fun_ty :: Int -> LHsType DocNameI -> LHsType DocNameI -> Bool -> LaTeX -ppr_fun_ty ctxt_prec ty1 ty2 unicode - = let p1 = ppr_mono_lty pREC_FUN ty1 unicode - p2 = ppr_mono_lty pREC_TOP ty2 unicode - in - maybeParen ctxt_prec pREC_FUN $ - sep [p1, arrow unicode <+> p2] - - ------------------------------------------------------------------------------- -- * Names ------------------------------------------------------------------------------- diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index fdb80141..cc271fef 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -620,9 +620,9 @@ ppInstances links origin instances splice unicode pkg qual -- force Splice = True to use line URLs where instName = getOccString origin - instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) + instDecl :: Int -> DocInstance DocNameI -> (SubDecl, Maybe Module, Located DocName) instDecl no (inst, mdoc, loc, mdl) = - ((ppInstHead links splice unicode qual mdoc origin False no inst mdl), loc) + ((ppInstHead links splice unicode qual mdoc origin False no inst mdl), mdl, loc) ppOrphanInstances :: LinksInfo @@ -635,9 +635,9 @@ ppOrphanInstances links instances splice unicode pkg qual instOrigin :: InstHead name -> InstOrigin (IdP name) instOrigin inst = OriginClass (ihdClsName inst) - instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) + instDecl :: Int -> DocInstance DocNameI -> (SubDecl, Maybe Module, Located DocName) instDecl no (inst, mdoc, loc, mdl) = - ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst mdl), loc) + ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst Nothing), mdl, loc) ppInstHead :: LinksInfo -> Splice -> Unicode -> Qualification @@ -1101,38 +1101,18 @@ sumParens = ubxSumList -- * Rendering of HsType -------------------------------------------------------------------------------- - -pREC_TOP, pREC_CTX, pREC_FUN, pREC_OP, pREC_CON :: Int - -pREC_TOP = 0 :: Int -- type in ParseIface.y in GHC -pREC_CTX = 1 :: Int -- Used for single contexts, eg. ctx => type - -- (as opposed to (ctx1, ctx2) => type) -pREC_FUN = 2 :: Int -- btype in ParseIface.y in GHC - -- Used for LH arg of (->) -pREC_OP = 3 :: Int -- Used for arg of any infix operator - -- (we don't keep their fixities around) -pREC_CON = 4 :: Int -- Used for arg of type applicn: - -- always parenthesise unless atomic - -maybeParen :: Int -- Precedence of context - -> Int -- Precedence of top-level operator - -> Html -> Html -- Wrap in parens if (ctxt >= op) -maybeParen ctxt_prec op_prec p | ctxt_prec >= op_prec = parens p - | otherwise = p - - ppLType, ppLParendType, ppLFunLhType :: Unicode -> Qualification -> HideEmptyContexts -> Located (HsType DocNameI) -> Html ppLType unicode qual emptyCtxts y = ppType unicode qual emptyCtxts (unLoc y) ppLParendType unicode qual emptyCtxts y = ppParendType unicode qual emptyCtxts (unLoc y) ppLFunLhType unicode qual emptyCtxts y = ppFunLhType unicode qual emptyCtxts (unLoc y) ppCtxType :: Unicode -> Qualification -> HsType DocNameI -> Html -ppCtxType unicode qual ty = ppr_mono_ty pREC_CTX ty unicode qual HideEmptyContexts +ppCtxType unicode qual ty = ppr_mono_ty (reparenTypePrec PREC_CTX ty) unicode qual HideEmptyContexts ppType, ppParendType, ppFunLhType :: Unicode -> Qualification -> HideEmptyContexts -> HsType DocNameI -> Html -ppType unicode qual emptyCtxts ty = ppr_mono_ty pREC_TOP ty unicode qual emptyCtxts -ppParendType unicode qual emptyCtxts ty = ppr_mono_ty pREC_CON ty unicode qual emptyCtxts -ppFunLhType unicode qual emptyCtxts ty = ppr_mono_ty pREC_FUN ty unicode qual emptyCtxts +ppType unicode qual emptyCtxts ty = ppr_mono_ty (reparenTypePrec PREC_TOP ty) unicode qual emptyCtxts +ppParendType unicode qual emptyCtxts ty = ppr_mono_ty (reparenTypePrec PREC_CON ty) unicode qual emptyCtxts +ppFunLhType unicode qual emptyCtxts ty = ppr_mono_ty (reparenTypePrec PREC_FUN ty) unicode qual emptyCtxts ppHsTyVarBndr :: Unicode -> Qualification -> HsTyVarBndr DocNameI -> Html ppHsTyVarBndr _ qual (UserTyVar _ (L _ name)) = @@ -1146,7 +1126,7 @@ ppLKind :: Unicode -> Qualification -> LHsKind DocNameI -> Html ppLKind unicode qual y = ppKind unicode qual (unLoc y) ppKind :: Unicode -> Qualification -> HsKind DocNameI -> Html -ppKind unicode qual ki = ppr_mono_ty pREC_TOP ki unicode qual HideEmptyContexts +ppKind unicode qual ki = ppr_mono_ty (reparenTypePrec PREC_TOP ki) unicode qual HideEmptyContexts patSigContext :: LHsType name -> HideEmptyContexts patSigContext typ | hasNonEmptyContext typ && isFirstContextEmpty typ = ShowEmptyToplevelContexts @@ -1177,57 +1157,56 @@ ppPatSigType unicode qual typ = ppForAllPart :: Unicode -> Qualification -> [LHsTyVarBndr DocNameI] -> Html ppForAllPart unicode qual tvs = hsep (forallSymbol unicode : ppTyVars unicode qual tvs) +++ dot -ppr_mono_lty :: Int -> LHsType DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html -ppr_mono_lty ctxt_prec ty = ppr_mono_ty ctxt_prec (unLoc ty) +ppr_mono_lty :: LHsType DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html +ppr_mono_lty ty = ppr_mono_ty (unLoc ty) -ppr_mono_ty :: Int -> HsType DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html -ppr_mono_ty ctxt_prec (HsForAllTy _ tvs ty) unicode qual emptyCtxts - = maybeParen ctxt_prec pREC_FUN $ - ppForAllPart unicode qual tvs <+> ppr_mono_lty pREC_TOP ty unicode qual emptyCtxts +ppr_mono_ty :: HsType DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html +ppr_mono_ty (HsForAllTy _ tvs ty) unicode qual emptyCtxts + = ppForAllPart unicode qual tvs <+> ppr_mono_lty ty unicode qual emptyCtxts -ppr_mono_ty ctxt_prec (HsQualTy _ ctxt ty) unicode qual emptyCtxts - = maybeParen ctxt_prec pREC_FUN $ - ppLContext ctxt unicode qual emptyCtxts <+> ppr_mono_lty pREC_TOP ty unicode qual emptyCtxts +ppr_mono_ty (HsQualTy _ ctxt ty) unicode qual emptyCtxts + = ppLContext ctxt unicode qual emptyCtxts <+> ppr_mono_lty ty unicode qual emptyCtxts -- UnicodeSyntax alternatives -ppr_mono_ty _ (HsTyVar _ _ (L _ name)) True _ _ +ppr_mono_ty (HsTyVar _ _ (L _ name)) True _ _ | getOccString (getName name) == "(->)" = toHtml "(→)" -ppr_mono_ty _ (HsBangTy _ b ty) u q _ = +ppr_mono_ty (HsBangTy _ b ty) u q _ = ppBang b +++ ppLParendType u q HideEmptyContexts ty -ppr_mono_ty _ (HsTyVar _ _ (L _ name)) _ q _ = +ppr_mono_ty (HsTyVar _ _ (L _ name)) _ q _ = ppDocName q Prefix True name -ppr_mono_ty _ (HsStarTy _ isUni) u _ _ = +ppr_mono_ty (HsStarTy _ isUni) u _ _ = toHtml (if u || isUni then "★" else "*") -ppr_mono_ty ctxt_prec (HsFunTy _ ty1 ty2) u q e = - ppr_fun_ty ctxt_prec ty1 ty2 u q e -ppr_mono_ty _ (HsTupleTy _ con tys) u q _ = +ppr_mono_ty (HsFunTy _ ty1 ty2) u q e = + hsep [ ppr_mono_lty ty1 u q HideEmptyContexts + , arrow u <+> ppr_mono_lty ty2 u q e + ] +ppr_mono_ty (HsTupleTy _ con tys) u q _ = tupleParens con (map (ppLType u q HideEmptyContexts) tys) -ppr_mono_ty _ (HsSumTy _ tys) u q _ = +ppr_mono_ty (HsSumTy _ tys) u q _ = sumParens (map (ppLType u q HideEmptyContexts) tys) -ppr_mono_ty _ (HsKindSig _ ty kind) u q e = - parens (ppr_mono_lty pREC_TOP ty u q e <+> dcolon u <+> ppLKind u q kind) -ppr_mono_ty _ (HsListTy _ ty) u q _ = brackets (ppr_mono_lty pREC_TOP ty u q HideEmptyContexts) -ppr_mono_ty ctxt_prec (HsIParamTy _ (L _ n) ty) u q _ = - maybeParen ctxt_prec pREC_CTX $ ppIPName n <+> dcolon u <+> ppr_mono_lty pREC_TOP ty u q HideEmptyContexts -ppr_mono_ty _ (HsSpliceTy {}) _ _ _ = error "ppr_mono_ty HsSpliceTy" -ppr_mono_ty _ (HsRecTy {}) _ _ _ = toHtml "{..}" +ppr_mono_ty (HsKindSig _ ty kind) u q e = + parens (ppr_mono_lty ty u q e <+> dcolon u <+> ppLKind u q kind) +ppr_mono_ty (HsListTy _ ty) u q _ = brackets (ppr_mono_lty ty u q HideEmptyContexts) +ppr_mono_ty (HsIParamTy _ (L _ n) ty) u q _ = + ppIPName n <+> dcolon u <+> ppr_mono_lty ty u q HideEmptyContexts +ppr_mono_ty (HsSpliceTy {}) _ _ _ = error "ppr_mono_ty HsSpliceTy" +ppr_mono_ty (HsRecTy {}) _ _ _ = toHtml "{..}" -- Can now legally occur in ConDeclGADT, the output here is to provide a -- placeholder in the signature, which is followed by the field -- declarations. -ppr_mono_ty _ (XHsType (NHsCoreTy {})) _ _ _ = error "ppr_mono_ty HsCoreTy" -ppr_mono_ty _ (HsExplicitListTy _ Promoted tys) u q _ = promoQuote $ brackets $ hsep $ punctuate comma $ map (ppLType u q HideEmptyContexts) tys -ppr_mono_ty _ (HsExplicitListTy _ NotPromoted tys) u q _ = brackets $ hsep $ punctuate comma $ map (ppLType u q HideEmptyContexts) tys -ppr_mono_ty _ (HsExplicitTupleTy _ tys) u q _ = promoQuote $ parenList $ map (ppLType u q HideEmptyContexts) tys - -ppr_mono_ty ctxt_prec (HsAppTy _ fun_ty arg_ty) unicode qual _ - = maybeParen ctxt_prec pREC_CON $ - hsep [ppr_mono_lty pREC_FUN fun_ty unicode qual HideEmptyContexts, ppr_mono_lty pREC_CON arg_ty unicode qual HideEmptyContexts] - -ppr_mono_ty ctxt_prec (HsOpTy _ ty1 op ty2) unicode qual _ - = maybeParen ctxt_prec pREC_FUN $ - ppr_mono_lty pREC_OP ty1 unicode qual HideEmptyContexts <+> ppr_op <+> ppr_mono_lty pREC_OP ty2 unicode qual HideEmptyContexts +ppr_mono_ty (XHsType (NHsCoreTy {})) _ _ _ = error "ppr_mono_ty HsCoreTy" +ppr_mono_ty (HsExplicitListTy _ Promoted tys) u q _ = promoQuote $ brackets $ hsep $ punctuate comma $ map (ppLType u q HideEmptyContexts) tys +ppr_mono_ty (HsExplicitListTy _ NotPromoted tys) u q _ = brackets $ hsep $ punctuate comma $ map (ppLType u q HideEmptyContexts) tys +ppr_mono_ty (HsExplicitTupleTy _ tys) u q _ = promoQuote $ parenList $ map (ppLType u q HideEmptyContexts) tys + +ppr_mono_ty (HsAppTy _ fun_ty arg_ty) unicode qual _ + = hsep [ ppr_mono_lty fun_ty unicode qual HideEmptyContexts + , ppr_mono_lty arg_ty unicode qual HideEmptyContexts ] + +ppr_mono_ty (HsOpTy _ ty1 op ty2) unicode qual _ + = ppr_mono_lty ty1 unicode qual HideEmptyContexts <+> ppr_op <+> ppr_mono_lty ty2 unicode qual HideEmptyContexts where -- `(:)` is valid in type signature only as constructor to promoted list -- and needs to be quoted in code so we explicitly quote it here too. @@ -1236,24 +1215,17 @@ ppr_mono_ty ctxt_prec (HsOpTy _ ty1 op ty2) unicode qual _ | otherwise = ppr_op' ppr_op' = ppLDocName qual Infix op -ppr_mono_ty ctxt_prec (HsParTy _ ty) unicode qual emptyCtxts --- = parens (ppr_mono_lty pREC_TOP ty) - = ppr_mono_lty ctxt_prec ty unicode qual emptyCtxts +ppr_mono_ty (HsParTy _ ty) unicode qual emptyCtxts + = parens (ppr_mono_lty ty unicode qual emptyCtxts) +-- = parens (ppr_mono_lty ctxt_prec ty unicode qual emptyCtxts) -ppr_mono_ty ctxt_prec (HsDocTy _ ty _) unicode qual emptyCtxts - = ppr_mono_lty ctxt_prec ty unicode qual emptyCtxts +ppr_mono_ty (HsDocTy _ ty _) unicode qual emptyCtxts + = ppr_mono_lty ty unicode qual emptyCtxts -ppr_mono_ty _ (HsWildCardTy (AnonWildCard _)) _ _ _ = char '_' -ppr_mono_ty _ (HsTyLit _ n) _ _ _ = ppr_tylit n +ppr_mono_ty (HsWildCardTy (AnonWildCard _)) _ _ _ = char '_' +ppr_mono_ty (HsTyLit _ n) _ _ _ = ppr_tylit n ppr_tylit :: HsTyLit -> Html ppr_tylit (HsNumTy _ n) = toHtml (show n) ppr_tylit (HsStrTy _ s) = toHtml (show s) -ppr_fun_ty :: Int -> LHsType DocNameI -> LHsType DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html -ppr_fun_ty ctxt_prec ty1 ty2 unicode qual emptyCtxts - = let p1 = ppr_mono_lty pREC_FUN ty1 unicode qual HideEmptyContexts - p2 = ppr_mono_lty pREC_TOP ty2 unicode qual emptyCtxts - in - maybeParen ctxt_prec pREC_FUN $ - hsep [p1, arrow unicode <+> p2] diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index 501caa4b..1c44ffda 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -40,7 +40,6 @@ module Haddock.Backends.Xhtml.Layout ( topDeclElem, declElem, ) where - import Haddock.Backends.Xhtml.DocMarkup import Haddock.Backends.Xhtml.Types import Haddock.Backends.Xhtml.Utils @@ -48,6 +47,7 @@ import Haddock.Types import Haddock.Utils (makeAnchorId, nameAnchorId) import qualified Data.Map as Map import Text.XHtml hiding ( name, title, quote ) +import Data.Maybe (fromMaybe) import FastString ( unpackFS ) import GHC @@ -151,20 +151,22 @@ subTable pkg qual decls = Just $ table << aboves (concatMap subRow decls) -- | Sub table with source information (optional). subTableSrc :: Maybe Package -> Qualification -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Maybe Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Maybe Html subTableSrc _ _ _ _ [] = Nothing subTableSrc pkg qual lnks splice decls = Just $ table << aboves (concatMap subRow decls) where - subRow ((decl, mdoc, subs),L loc dn) = + subRow ((decl, mdoc, subs), mdl, L loc dn) = (td ! [theclass "src clearfix"] << (thespan ! [theclass "inst-left"] << decl) - <+> linkHtml loc dn + <+> linkHtml loc mdl dn <-> docElement td << fmap (docToHtml Nothing pkg qual) mdoc ) : map (cell . (td <<)) subs - linkHtml loc@(RealSrcSpan _) dn = links lnks loc splice dn - linkHtml _ _ = noHtml + + linkHtml :: SrcSpan -> Maybe Module -> DocName -> Html + linkHtml loc@(RealSrcSpan _) mdl dn = links lnks loc splice mdl dn + linkHtml _ _ _ = noHtml subBlock :: [Html] -> Maybe Html subBlock [] = Nothing @@ -197,7 +199,7 @@ subEquations pkg qual = divSubDecls "equations" "Equations" . subTable pkg qual subInstances :: Maybe Package -> Qualification -> String -- ^ Class name, used for anchor generation -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Html subInstances pkg qual nm lnks splice = maybe noHtml wrap . instTable where wrap contents = subSection (collapseDetails id_ DetailsOpen (summary +++ contents)) @@ -209,7 +211,7 @@ subInstances pkg qual nm lnks splice = maybe noHtml wrap . instTable subOrphanInstances :: Maybe Package -> Qualification -> LinksInfo -> Bool - -> [(SubDecl,Located DocName)] -> Html + -> [(SubDecl, Maybe Module, Located DocName)] -> Html subOrphanInstances pkg qual lnks splice = maybe noHtml wrap . instTable where wrap = ((h1 << "Orphan instances") +++) @@ -268,13 +270,13 @@ declElem = paragraph ! [theclass "src"] -- it adds a source and wiki link at the right hand side of the box topDeclElem :: LinksInfo -> SrcSpan -> Bool -> [DocName] -> Html -> Html topDeclElem lnks loc splice names html = - declElem << (html <+> (links lnks loc splice $ head names)) + declElem << (html <+> (links lnks loc splice Nothing $ head names)) -- FIXME: is it ok to simply take the first name? -- | Adds a source and wiki link at the right hand side of the box. -- Name must be documented, otherwise we wouldn't get here. -links :: LinksInfo -> SrcSpan -> Bool -> DocName -> Html -links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice docName@(Documented n mdl) = +links :: LinksInfo -> SrcSpan -> Bool -> Maybe Module -> DocName -> Html +links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice mdl' docName@(Documented n mdl) = srcLink <+> wikiLink <+> (selfLink ! [theclass "selflink"] << "#") where selfLink = linkedAnchor (nameAnchorId (nameOccName (getName docName))) @@ -298,12 +300,13 @@ links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice docName@(Docume -- For source links, we want to point to the original module, -- because only that will have the source. - -- TODO: do something about type instances. They will point to - -- the module defining the type family, which is wrong. - origMod = nameModule n + -- + -- 'mdl'' is a way of "overriding" the module. Without it, instances + -- will point to the module defining the class/family, which is wrong. + origMod = fromMaybe (nameModule n) mdl' origPkg = moduleUnitId origMod fname = case loc of RealSrcSpan l -> unpackFS (srcSpanFile l) UnhelpfulSpan _ -> error "links: UnhelpfulSpan" -links _ _ _ _ = noHtml +links _ _ _ _ _ = noHtml diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index bf6fbab0..6eee353b 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -31,7 +31,7 @@ import NameSet ( emptyNameSet ) import RdrName ( mkVarUnqual ) import PatSyn import SrcLoc ( Located, noLoc, unLoc, GenLocated(..), srcLocSpan ) -import TcType ( tcSplitSigmaTy ) +import TcType import TyCon import Type import TyCoRep @@ -527,7 +527,7 @@ synifyType _ (FunTy t1 t2) = let s2 = synifyType WithinType t2 in noLoc $ HsFunTy noExt s1 s2 synifyType s forallty@(ForAllTy _tv _ty) = - let (tvs, ctx, tau) = tcSplitSigmaTy forallty + let (tvs, ctx, tau) = tcSplitSigmaTyPreserveSynonyms forallty sPhi = HsQualTy { hst_ctxt = synifyCtx ctx , hst_xqual = noExt , hst_body = synifyType WithinType tau } @@ -626,3 +626,47 @@ synifyFamInst fi opaque = do ts' = synifyTypes ts annot_ts = zipWith3 annotHsType is_poly_tvs ts ts' is_poly_tvs = mkIsPolyTvs (tyConVisibleTyVars fam_tc) + +{- +Note [Invariant: Never expand type synonyms] + +In haddock, we never want to expand a type synonym that may be presented to the +user, as we want to keep the link to the abstraction captured in the synonym. + +All code in Haddock.Convert must make sure that this invariant holds. + +See https://github.com/haskell/haddock/issues/879 for a bug where this +invariant didn't hold. +-} + +-- | A version of 'TcType.tcSplitSigmaTy' that preserves type synonyms. +-- +-- See Note [Invariant: Never expand type synonyms] +tcSplitSigmaTyPreserveSynonyms :: Type -> ([TyVar], ThetaType, Type) +tcSplitSigmaTyPreserveSynonyms ty = + case tcSplitForAllTysPreserveSynonyms ty of + (tvs, rho) -> case tcSplitPhiTyPreserveSynonyms rho of + (theta, tau) -> (tvs, theta, tau) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitForAllTysPreserveSynonyms :: Type -> ([TyVar], Type) +tcSplitForAllTysPreserveSynonyms ty = split ty ty [] + where + split _ (ForAllTy (TvBndr tv _) ty') tvs = split ty' ty' (tv:tvs) + split orig_ty _ tvs = (reverse tvs, orig_ty) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitPhiTyPreserveSynonyms :: Type -> (ThetaType, Type) +tcSplitPhiTyPreserveSynonyms ty0 = split ty0 [] + where + split ty ts + = case tcSplitPredFunTyPreserveSynonyms_maybe ty of + Just (pred_, ty') -> split ty' (pred_:ts) + Nothing -> (reverse ts, ty) + +-- | See Note [Invariant: Never expand type synonyms] +tcSplitPredFunTyPreserveSynonyms_maybe :: Type -> Maybe (PredType, Type) +tcSplitPredFunTyPreserveSynonyms_maybe (FunTy arg res) + | isPredTy arg = Just (arg, res) +tcSplitPredFunTyPreserveSynonyms_maybe _ + = Nothing diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index b2c34bb4..e7d80969 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -31,6 +31,8 @@ import GHC import Class import DynFlags +import HsTypes (HsType(..)) + moduleString :: Module -> String moduleString = moduleNameString . moduleName @@ -226,6 +228,100 @@ getGADTConTypeG (ConDeclH98 {}) = panic "getGADTConTypeG" -- Should only be called on ConDeclGADT getGADTConTypeG (XConDecl {}) = panic "getGADTConTypeG" + +------------------------------------------------------------------------------- +-- * Parenthesization +------------------------------------------------------------------------------- + +-- | Precedence level (inside the 'HsType' AST). +data Precedence + = PREC_TOP -- ^ precedence of 'type' production in GHC's parser + + | PREC_CTX -- ^ Used for single contexts, eg. ctx => type + -- (as opposed to (ctx1, ctx2) => type) + + | PREC_FUN -- ^ precedence of 'btype' production in GHC's parser + -- (used for LH arg of (->)) + + | PREC_OP -- ^ arg of any infix operator + -- (we don't keep have fixity info) + + | PREC_CON -- ^ arg of type application: always parenthesize unless atomic + deriving (Eq, Ord) + +-- | Add in extra 'HsParTy' where needed to ensure that what would be printed +-- out using 'ppr' has enough parentheses to be re-parsed properly. +-- +-- We cannot add parens that may be required by fixities because we do not have +-- any fixity information to work with in the first place :(. +reparenTypePrec :: (XParTy a ~ NoExt) => Precedence -> HsType a -> HsType a +reparenTypePrec = go + where + + -- Shorter name for 'reparenType' + go :: (XParTy a ~ NoExt) => Precedence -> HsType a -> HsType a + go _ (HsBangTy x b ty) = HsBangTy x b (reparenLType ty) + go _ (HsTupleTy x con tys) = HsTupleTy x con (map reparenLType tys) + go _ (HsSumTy x tys) = HsSumTy x (map reparenLType tys) + go _ (HsKindSig x ty kind) = HsKindSig x (reparenLType ty) (reparenLType kind) + go _ (HsListTy x ty) = HsListTy x (reparenLType ty) + go _ (HsRecTy x flds) = HsRecTy x (map (fmap reparenConDeclField) flds) + go p (HsDocTy x ty d) = HsDocTy x (goL p ty) d + go _ (HsExplicitListTy x p tys) = HsExplicitListTy x p (map reparenLType tys) + go _ (HsExplicitTupleTy x tys) = HsExplicitTupleTy x (map reparenLType tys) + go p (HsIParamTy x n ty) + = paren p PREC_CTX $ HsIParamTy x n (reparenLType ty) + go p (HsForAllTy x tvs ty) + = paren p PREC_CTX $ HsForAllTy x (map (fmap reparenTyVar) tvs) (reparenLType ty) + go p (HsQualTy x ctxt ty) + = paren p PREC_FUN $ HsQualTy x (fmap (map reparenLType) ctxt) (reparenLType ty) + go p (HsFunTy x ty1 ty2) + = paren p PREC_FUN $ HsFunTy x (goL PREC_FUN ty1) (goL PREC_TOP ty2) + go p (HsAppTy x fun_ty arg_ty) + = paren p PREC_CON $ HsAppTy x (goL PREC_FUN fun_ty) (goL PREC_CON arg_ty) + go p (HsOpTy x ty1 op ty2) + = paren p PREC_FUN $ HsOpTy x (goL PREC_OP ty1) op (goL PREC_OP ty2) + go p (HsParTy _ t) = unLoc $ goL p t -- pretend the paren doesn't exist - it will be added back if needed + go _ t@HsTyVar{} = t + go _ t@HsStarTy{} = t + go _ t@HsSpliceTy{} = t + go _ t@HsTyLit{} = t + go _ t@HsWildCardTy{} = t + go _ t@XHsType{} = t + + -- Located variant of 'go' + goL :: (XParTy a ~ NoExt) => Precedence -> LHsType a -> LHsType a + goL ctxt_prec = fmap (go ctxt_prec) + + -- Optionally wrap a type in parens + paren :: (XParTy a ~ NoExt) + => Precedence -- Precedence of context + -> Precedence -- Precedence of top-level operator + -> HsType a -> HsType a -- Wrap in parens if (ctxt >= op) + paren ctxt_prec op_prec | ctxt_prec >= op_prec = HsParTy NoExt . noLoc + | otherwise = id + + +-- | Add parenthesis around the types in a 'HsType' (see 'reparenTypePrec') +reparenType :: (XParTy a ~ NoExt) => HsType a -> HsType a +reparenType = reparenTypePrec PREC_TOP + +-- | Add parenthesis around the types in a 'LHsType' (see 'reparenTypePrec') +reparenLType :: (XParTy a ~ NoExt) => LHsType a -> LHsType a +reparenLType = fmap reparenType + +-- | Add parenthesis around the types in a 'HsTyVarBndr' (see 'reparenTypePrec') +reparenTyVar :: (XParTy a ~ NoExt) => HsTyVarBndr a -> HsTyVarBndr a +reparenTyVar (UserTyVar x n) = UserTyVar x n +reparenTyVar (KindedTyVar x n kind) = KindedTyVar x n (reparenLType kind) +reparenTyVar v@XTyVarBndr{} = v + +-- | Add parenthesis around the types in a 'ConDeclField' (see 'reparenTypePrec') +reparenConDeclField :: (XParTy a ~ NoExt) => ConDeclField a -> ConDeclField a +reparenConDeclField (ConDeclField x n t d) = ConDeclField x n (reparenLType t) d +reparenConDeclField c@XConDeclField{} = c + + ------------------------------------------------------------------------------- -- * Located ------------------------------------------------------------------------------- diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 78242990..c4df2090 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -419,9 +419,12 @@ mkMaps dflags pkgName gre instances decls = do instanceMap = M.fromList [ (getSrcSpan n, n) | n <- instances ] names :: SrcSpan -> HsDecl GhcRn -> [Name] - names l (InstD _ d) = maybeToList (M.lookup loc instanceMap) -- See note [2]. + names _ (InstD _ d) = maybeToList (M.lookup loc instanceMap) -- See note [2]. where loc = case d of - TyFamInstD _ _ -> l -- The CoAx's loc is the whole line, but only for TFs + -- The CoAx's loc is the whole line, but only for TFs. The + -- workaround is to dig into the family instance declaration and + -- get the identifier with the right location. + TyFamInstD _ (TyFamInstDecl d') -> getLoc (feqn_tycon (hsib_body d')) _ -> getInstLoc d names l (DerivD {}) = maybeToList (M.lookup l instanceMap) -- See note [2]. names _ decl = getMainDeclBinder decl diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index da422562..ea74043d 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -28,6 +28,7 @@ module Haddock.Types ( import Control.Exception import Control.Arrow hiding ((<+>)) import Control.DeepSeq +import Control.Monad.IO.Class (MonadIO(..)) import Data.Typeable import Data.Map (Map) import Data.Data (Data) @@ -661,6 +662,8 @@ instance Monad ErrMsgGhc where m >>= k = WriterGhc $ runWriterGhc m >>= \ (a, msgs1) -> fmap (second (msgs1 ++)) (runWriterGhc (k a)) +instance MonadIO ErrMsgGhc where + liftIO m = WriterGhc (fmap (\x -> (x, [])) (liftIO m)) ----------------------------------------------------------------------------- -- * Pass sensitive types diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs index 86ed3b35..0449c917 100644 --- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs +++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs @@ -86,6 +86,18 @@ spec = do it "parses identifiers enclosed within backticks" $ do "`foo`" `shouldParseTo` DocIdentifier "foo" + it "parses identifiers preceded by a backtick and followed by a single quote" $ do + "`foo'" `shouldParseTo` DocIdentifier "foo" + + it "parses identifiers preceded by a single quote and followed by a backtick" $ do + "'foo`" `shouldParseTo` DocIdentifier "foo" + + it "can parse a constructor identifier" $ do + "'Foo'" `shouldParseTo` DocIdentifier "Foo" + + it "can parse a qualified identifier" $ do + "'Foo.bar'" `shouldParseTo` DocIdentifier "Foo.bar" + it "parses a word with an one of the delimiters in it as DocString" $ do "don't" `shouldParseTo` "don't" @@ -99,9 +111,43 @@ spec = do it "doesn't parse empty identifiers" $ do "``" `shouldParseTo` "``" - it "can parse infix identifiers" $ do + it "can parse an identifier in infix notation enclosed within backticks" $ do "``infix``" `shouldParseTo` "`" <> DocIdentifier "infix" <> "`" + it "can parse identifiers containing a single quote" $ do + "'don't'" `shouldParseTo` DocIdentifier "don't" + + it "can parse identifiers ending with a single quote" $ do + "'foo''" `shouldParseTo` DocIdentifier "foo'" + + it "can parse an identifier containing a digit" $ do + "'f0'" `shouldParseTo` DocIdentifier "f0" + + it "can parse an identifier containing unicode characters" $ do + "'λ'" `shouldParseTo` DocIdentifier "λ" + + it "can parse a single quote followed by an identifier" $ do + "''foo'" `shouldParseTo` "'" <> DocIdentifier "foo" + + it "can parse an identifier that starts with an underscore" $ do + "'_x'" `shouldParseTo` DocIdentifier "_x" + + context "when parsing operators" $ do + it "can parse an operator enclosed within single quotes" $ do + "'.='" `shouldParseTo` DocIdentifier ".=" + + it "can parse a qualified operator" $ do + "'F..'" `shouldParseTo` DocIdentifier "F.." + + it "can parse a constructor operator" $ do + "':='" `shouldParseTo` DocIdentifier ":=" + + it "can parse a qualified constructor operator" $ do + "'F.:='" `shouldParseTo` DocIdentifier "F.:=" + + it "can parse a unicode operator" $ do + "'∧'" `shouldParseTo` DocIdentifier "∧" + context "when parsing URLs" $ do it "parses a URL" $ do "" `shouldParseTo` hyperlink "http://example.com/" Nothing diff --git a/haddock-test/src/Test/Haddock.hs b/haddock-test/src/Test/Haddock.hs index f372f773..942c0587 100644 --- a/haddock-test/src/Test/Haddock.hs +++ b/haddock-test/src/Test/Haddock.hs @@ -158,7 +158,9 @@ maybeAcceptFile :: Config c -> FilePath -> CheckResult -> IO CheckResult maybeAcceptFile cfg file result | cfgAccept cfg && result `elem` [NoRef, Fail] = do Just out <- readOut cfg file - writeFile (refFile dcfg file) $ ccfgDump ccfg out + let ref = refFile dcfg file + createDirectoryIfMissing True (takeDirectory ref) + writeFile ref $ ccfgDump ccfg out pure Accepted where dcfg = cfgDirConfig cfg diff --git a/haddock.cabal b/haddock.cabal index 29d3d114..af606894 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -78,7 +78,7 @@ executable haddock xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, ghc-boot, - ghc == 8.6.*, + ghc == 8.5.*, bytestring, parsec, text, diff --git a/hoogle-test/ref/Bug722/test.txt b/hoogle-test/ref/Bug722/test.txt new file mode 100644 index 00000000..96f3747b --- /dev/null +++ b/hoogle-test/ref/Bug722/test.txt @@ -0,0 +1,16 @@ +-- Hoogle documentation, generated by Haddock +-- See Hoogle, http://www.haskell.org/hoogle/ + +@package test +@version 0.0.0 + +module Bug722 +class Foo a +(!@#) :: Foo a => a -> a -> a +infixl 4 !@# +type family &* :: * -> * -> * +infixr 3 &* +data a :-& b +(:^&) :: a -> b -> (:-&) a b +infixl 6 :-& +infixl 6 :^& diff --git a/hoogle-test/ref/Bug806/test.txt b/hoogle-test/ref/Bug806/test.txt index d9a908b3..67e9fd61 100644 --- a/hoogle-test/ref/Bug806/test.txt +++ b/hoogle-test/ref/Bug806/test.txt @@ -21,4 +21,5 @@ class C a where { -- | AT docs type family AT a; + type AT a = Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy))))))))); } diff --git a/hoogle-test/ref/Bug873/test.txt b/hoogle-test/ref/Bug873/test.txt new file mode 100644 index 00000000..19100212 --- /dev/null +++ b/hoogle-test/ref/Bug873/test.txt @@ -0,0 +1,26 @@ +-- Hoogle documentation, generated by Haddock +-- See Hoogle, http://www.haskell.org/hoogle/ + +@package test +@version 0.0.0 + +module Bug873 + +-- | Application operator. This operator is redundant, since ordinary +-- application (f x) means the same as (f $ x). +-- However, $ has low, right-associative binding precedence, so it +-- sometimes allows parentheses to be omitted; for example: +-- +--
                  +--   f $ g $ h x  =  f (g (h x))
                  +--   
                  +-- +-- It is also useful in higher-order situations, such as map +-- ($ 0) xs, or zipWith ($) fs xs. +-- +-- Note that ($) is levity-polymorphic in its result type, so +-- that foo $ True where foo :: Bool -> Int# is well-typed +($) :: () => (a -> b) -> a -> b +infixr 0 $ +($$) :: (a -> b) -> a -> b +infixr 0 $$ diff --git a/hoogle-test/ref/type-sigs/test.txt b/hoogle-test/ref/type-sigs/test.txt index ec5f5043..1209279c 100644 --- a/hoogle-test/ref/type-sigs/test.txt +++ b/hoogle-test/ref/type-sigs/test.txt @@ -6,11 +6,11 @@ module ReaderT newtype ReaderT r m a -ReaderT :: r -> m a -> ReaderT r m a +ReaderT :: (r -> m a) -> ReaderT r m a [runReaderT] :: ReaderT r m a -> r -> m a module ReaderTReexport newtype ReaderT r m a -ReaderT :: r -> m a -> ReaderT r m a +ReaderT :: (r -> m a) -> ReaderT r m a [runReaderT] :: ReaderT r m a -> r -> m a runReaderT :: ReaderT r m a -> r -> m a diff --git a/hoogle-test/src/Bug722/Bug722.hs b/hoogle-test/src/Bug722/Bug722.hs new file mode 100644 index 00000000..a33d5b24 --- /dev/null +++ b/hoogle-test/src/Bug722/Bug722.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TypeOperators, TypeFamilies #-} +module Bug722 where + +class Foo a where + (!@#) :: a -> a -> a +infixl 4 !@# + +type family (&*) :: * -> * -> * +infixr 3 &* + +data a :-& b = a :^& b +infixl 6 :-&, :^& + diff --git a/hoogle-test/src/Bug806/Bug806.hs b/hoogle-test/src/Bug806/Bug806.hs index 6efcb5cf..45efda77 100644 --- a/hoogle-test/src/Bug806/Bug806.hs +++ b/hoogle-test/src/Bug806/Bug806.hs @@ -21,3 +21,4 @@ v = 42 class C a where -- | 'AT' docs type AT a + type AT a = Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy))))))))) diff --git a/hoogle-test/src/Bug873/Bug873.hs b/hoogle-test/src/Bug873/Bug873.hs new file mode 100644 index 00000000..3a9a5383 --- /dev/null +++ b/hoogle-test/src/Bug873/Bug873.hs @@ -0,0 +1,5 @@ +module Bug873 (($), ($$)) where +infixr 0 $$ + +($$) :: (a -> b) -> a -> b +f $$ x = f x diff --git a/html-test/ref/A.html b/html-test/ref/A.html index c6965abc..e4802966 100644 --- a/html-test/ref/A.html +++ b/html-test/ref/A.html @@ -54,11 +54,15 @@ >
                • other :: Int
                • :: Int
                • test2 :: Bool
                • :: Bool
                • data
                • reExport :: Int
                • :: Int

                  other :: Int :: Int #

                  test2 :: Bool :: Bool #

                  reExport :: Int :: Int #

                  x :: [Char] :: [Char] #

                • foo :: Int
                • :: Int

                  foo :: Int :: Int #

                  Bug310

                  Synopsis
                  • type family (a :: Nat) + (b :: Nat) :: Nat where ...

                  Documentation

                  type family (a :: Nat) (a :: Nat) + (b :: Nat) :: Nat (b :: Nat) :: Nat where ... infixl 6 #

                  Addition of type-level naturals.

                  Since: base-4.7.0.0

                • test1 :: Int
                • :: Int
                • test2 :: Int
                • :: Int

                  test1 :: Int :: Int #

                  test2 :: Int :: Int #

                • foo :: Int
                • :: Int

                  foo :: Int :: Int #

                • x :: Integer
                • :: Integer
                • compile :: String -> String
                • :: String -> String

                  x :: Integer :: Integer #

                  compile :: String -> String :: String -> String #

                  newtype WrappedArrow (a :: * -> * -> *) b c (a :: Type -> Type -> Type) b c #

                  Generic1 ( Generic1 (WrappedArrow a b :: * -> *) a b :: Type -> Type)

                  type Rep1 (WrappedArrow a b) :: k -> *

                  Rep1 (WrappedArrow a b) :: k -> Type #

                  from1 :: WrappedArrow a b a0 -> Rep1 ( a b a0 -> Rep1 (WrappedArrow a b) a0

                  a b) a0 #

                  to1 :: Rep1 ( :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0

                  a b a0 #

                  Arrow a => Functor ( Arrow a => Functor (WrappedArrow a b)

                  Since: base-2.1

                  WrappedArrow a b a0 -> WrappedArrow a b b0

                  a b b0 #

                  (<$)WrappedArrow a b b0 -> WrappedArrow a b a0

                  a b a0 #

                  Arrow a => Applicative ( Arrow a => Applicative (WrappedArrow a b)

                  Since: base-2.1

                  pure :: a0 -> WrappedArrow a b a0

                  a b a0 #

                  (<*>)WrappedArrow a b a0 -> WrappedArrow a b b0

                  a b b0 #

                  liftA2WrappedArrow a b b0 -> WrappedArrow a b c

                  a b c #

                  (*>)WrappedArrow a b b0 -> WrappedArrow a b b0

                  a b b0 #

                  (<*)WrappedArrow a b b0 -> WrappedArrow a b a0

                  a b a0 #

                  (ArrowZero a, ArrowPlus a) => Alternative ( (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b)

                  Since: base-2.1

                  empty :: WrappedArrow a b a0

                  a b a0 #

                  (<|>)WrappedArrow a b a0 -> WrappedArrow a b a0

                  a b a0 #

                  someWrappedArrow a b a0 -> WrappedArrow a b [a0]

                  a b [a0] #

                  manyWrappedArrow a b a0 -> WrappedArrow a b [a0]

                  a b [a0] #

                  Generic ( Generic (WrappedArrow a b c)

                  type Rep (WrappedArrow a b c) :: * -> *

                  Rep (WrappedArrow a b c) :: Type -> Type #

                  from :: WrappedArrow a b c -> Rep ( a b c -> Rep (WrappedArrow a b c) x

                  a b c) x #

                  to :: Rep ( :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c

                  a b c #

                  type Rep1 ( Rep1 (WrappedArrow a b :: * -> *) a b :: Type -> Type)

                  Since: base-4.7.0.0

                  type Rep1 ( Rep1 (WrappedArrow a b :: * -> *) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (a b))))
                  a b :: Type -> Type) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (a b))))
                  type Rep ( Rep (WrappedArrow a b c)

                  Since: base-4.7.0.0

                  type Rep ( Rep (WrappedArrow a b c) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a b c))))
                  a b c) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a b c))))Bug574
                  Safe HaskellNone

                  Bug574

                  Synopsis

                  Documentation

                  foo :: Int -> Int -> Int #

                  Somthing with a spliced type

                  \ No newline at end of file diff --git a/html-test/ref/Bug6.html b/html-test/ref/Bug6.html index 27f73d64..15842547 100644 --- a/html-test/ref/Bug6.html +++ b/html-test/ref/Bug6.html @@ -58,7 +58,9 @@ >A = A Int Int
                • dataB = B Int
                • Int
                • b :: B -> Int
                • -> Int
                • data
                • c1 :: Int
                • :: Int
                • c2 :: Int
                • :: Int}
                • D = D Int Int
                • Int Int
                • newtypeE = E Int
                • IntA Int IntB Int Intb :: B -> Int -> Int #

                  c1 :: Int :: Int
                  c2 :: Int :: Int
                  D Int Int Int IntE Int Int Functor (Either a) (Either a) #

                  fmap :: (a0 -> b) -> Either a a0 -> Either a b :: (a0 -> b) -> Either a a0 -> Either a b #

                  (--->) :: Foldable t0 => t0 t -> :: Foldable t0 => t0 t -> Typ -> Typ

                • foo :: Int
                • :: Int
                • bar :: Int
                • :: Int
                • baz :: Int
                • :: Int
                • one :: Int
                • :: Int
                • two :: Int
                • :: Int
                • three :: Int
                • :: Int

                  foo :: Int :: Int #

                  bar :: Int :: Int #

                  baz :: Int :: Int #

                  one :: Int :: Int #

                  two :: Int :: Int #

                  three :: Int :: Int #

                • foo :: Int
                • :: Int
                • bar :: Int
                • :: Int
                • baz :: Int
                • :: Int
                • one :: Int
                • :: Int
                • two :: Int
                • :: Int
                • three :: Int
                • :: Int

                  foo :: Int :: Int #

                  bar :: Int :: Int #

                  baz :: Int :: Int #

                  one :: Int :: Int #

                  two :: Int :: Int #

                  three :: Int :: Int #

                  A a (a -> Int) a (a -> Int)data Vec :: Nat -> * -> * :: Nat -> * -> * where
                  pattern MyRecCons :: Bool -> Int -> MyRec :: Bool -> Int -> MyRec #

                  pattern (:+) :: String -> a -> MyInfix a :: String -> a -> MyInfix a #

                  pattern BlubCons :: () => Show b => b -> Blub :: () => Show b => b -> Blub #

                  pattern MyGADTCons :: a -> Int -> MyGADT (Maybe String) :: a -> Int -> MyGADT (Maybe String) #

                • foo :: Int
                • :: Int
                • bar :: Int
                • :: Int

                  foo :: Int :: Int #

                  bar :: Int :: Int #

                • foo :: Int
                • :: Int

                  foo :: Int :: Int #

                • foo :: Integer
                • :: Integer

                  foo :: Integer :: Integer #

                  foo :: Int :: Int #

                  foo :: Int :: Int #

                  SomeNewType = SomeNewTypeConst String String
                • newtypeSomeOtherNewType = SomeOtherNewTypeConst String
                • StringSomeNewTypeConst String String

                  SomeOtherNewTypeConst String String

                • foo :: Int
                • :: Int

                  foo :: Int :: Int #

                • fooName :: String
                • :: String
                • fooValue :: Int
                • :: Int}fooName :: String :: String

                  some name

                  fooValue :: Int :: Int

                  type TypeSyn = String = String

                • type OtherTypeSyn = String
                • = String
                  type TypeSyn = String = String #

                  type OtherTypeSyn = String = String #

                • fib :: Integer -> Integer
                • :: Integer -> Integer

                  fib :: Integer -> Integer :: Integer -> Integer #

                  Fibonacci number of given IntegerInteger.

                  Examples:

                  :: Ord a=> Int-> Bool (b :: ()). d ~ ()
                • C2 :: Ord a => [a] -> :: Ord a => [a] -> H1 a a
                • C3 :: {..} -> H1 Int Int
                • IntInt
                • C4 :: {..} -> H1 Int a
                • Int a

                  hash :: Float -> Int :: Float -> Int #

                  Hash IntInt#

                  hash :: Int -> Int :: Int -> Int #

                  hash :: (a, b) -> Int :: (a, b) -> Int #

                  VisibleClass IntInt# Num Num VisibleDataVisibleData -> VisibleData#

                  VisibleData -> VisibleData #

                  VisibleData -> VisibleData #

                  VisibleData -> VisibleData #

                  VisibleData -> VisibleData #

                  VisibleData -> VisibleData #

                  fromInteger :: Integer -> :: Integer -> VisibleData #

                • foo :: Int
                • :: Int

                  foo :: Int :: Int #

                  foo :: (a <~~ Int) -> a0 -> a Int) -> a0 -> a <~~ a0 #<~~ (a <~~ a0)) -> Int -> a a0)) -> Int -> a <~~ (a <~~ Int) Int) #

                  foo :: f Int -> a -> f a :: f Int -> a -> f a #

                  foo' :: f (f a) -> Int -> f (f Int) :: f (f a) -> Int -> f (f Int) #

                  foo :: [Int] -> a -> [a] :: [Int] -> a -> [a] #

                  foo' :: [[a]] -> Int -> [[Int]] :: [[a]] -> Int -> [[Int]] #

                  Foo MaybeMaybe#

                  foo :: Maybe Int -> a -> Maybe a :: Maybe Int -> a -> Maybe a #

                  foo' :: Maybe (Maybe a) -> Int -> Maybe (Maybe Int) :: Maybe (Maybe a) -> Int -> Maybe (Maybe Int) #

                  Foo (Either a) (Either a)#

                  foo :: Either a Int -> a0 -> Either a a0 :: Either a Int -> a0 -> Either a a0 #

                  foo' :: Either a (Either a a0) -> Int -> Either a (Either a Int) :: Either a (Either a a0) -> Int -> Either a (Either a Int) #

                  (Eq a, (Eq a, Foo f) => Foo ((,) (f a)) ((,) (f a))#

                  foo :: (f a, Int) -> a0 -> (f a, a0) :: (f a, Int) -> a0 -> (f a, a0) #

                  foo' :: (f a, (f a, a0)) -> Int -> (f a, (f a, Int)) :: (f a, (f a, a0)) -> Int -> (f a, (f a, Int)) #

                  foo :: (a <~~ Int) -> a0 -> a Int) -> a0 -> a <~~ a0 #<~~ (a <~~ a0)) -> Int -> a a0)) -> Int -> a <~~ (a <~~ Int) Int) #

                  Foo ((,,) a a) ((,,) a a)#

                  foo :: (a, a, Int) -> a0 -> (a, a, a0) :: (a, a, Int) -> a0 -> (a, a, a0) #

                  foo' :: (a, a, (a, a, a0)) -> Int -> (a, a, (a, a, Int)) :: (a, a, (a, a, a0)) -> Int -> (a, a, (a, a, Int)) #

                  foo :: Quux a b Int -> a0 -> a b Int -> a0 -> Quux a b a0 #Quux a b (Quux a b a0) -> Int -> a b a0) -> Int -> Quux a b (Quux a b Int) a b Int) #

                  Foo ((->) a :: * -> *) ((->) a :: Type -> Type)#

                  foo :: (a -> Int) -> a0 -> a -> a0 :: (a -> Int) -> a0 -> a -> a0 #

                  foo' :: (a -> (a -> a0)) -> Int -> a -> (a -> Int) :: (a -> (a -> a0)) -> Int -> a -> (a -> Int) #

                  bar :: f a -> f Bool -> a :: f a -> f Bool -> a #

                  Bar Maybe Bool Maybe Bool #

                  bar :: Maybe Bool -> Maybe Bool -> Bool :: Maybe Bool -> Maybe Bool -> Bool #

                  bar' :: Maybe (Maybe Bool) -> Maybe (Maybe (Maybe b)) :: Maybe (Maybe Bool) -> Maybe (Maybe (Maybe b)) #

                  bar0 :: (Maybe Bool, Maybe Bool) -> (Maybe b, Maybe c) :: (Maybe Bool, Maybe Bool) -> (Maybe b, Maybe c) #

                  bar1 :: (Maybe Bool, Maybe Bool) -> (Maybe b, Maybe c) :: (Maybe Bool, Maybe Bool) -> (Maybe b, Maybe c) #

                  Bar Maybe [a]Maybe [a]#

                  bar :: Maybe [a] -> Maybe Bool -> [a] :: Maybe [a] -> Maybe Bool -> [a] #

                  bar' :: Maybe (Maybe [a]) -> Maybe (Maybe (Maybe b)) :: Maybe (Maybe [a]) -> Maybe (Maybe (Maybe b)) #

                  bar0 :: (Maybe [a], Maybe [a]) -> (Maybe b, Maybe c) :: (Maybe [a], Maybe [a]) -> (Maybe b, Maybe c) #

                  bar1 :: (Maybe [a], Maybe [a]) -> (Maybe b, Maybe c) :: (Maybe [a], Maybe [a]) -> (Maybe b, Maybe c) #

                  bar :: [(a, a)] -> [Bool] -> (a, a) :: [(a, a)] -> [Bool] -> (a, a) #

                  Foo f => Bar (Either a) (f a) (Either a) (f a) #

                  bar :: Either a (f a) -> Either a Bool -> f a :: Either a (f a) -> Either a Bool -> f a #

                  bar' :: Either a (Either a (f a)) -> Either a (Either a (Either a b)) :: Either a (Either a (f a)) -> Either a (Either a (Either a b)) #

                  bar0 :: (Either a (f a), Either a (f a)) -> (Either a b, Either a c) :: (Either a (f a), Either a (f a)) -> (Either a b, Either a c) #

                  bar1 :: (Either a (f a), Either a (f a)) -> (Either a b, Either a c) :: (Either a (f a), Either a (f a)) -> (Either a b, Either a c) #

                  Foo ((,,) a b) => ((,,) a b) => Bar ((,,) a b) (a, b, a) ((,,) a b) (a, b, a)#

                  bar :: (a, b, (a, b, a)) -> (a, b, Bool) -> (a, b, a) :: (a, b, (a, b, a)) -> (a, b, Bool) -> (a, b, a) #

                  Quux a b c) -> Quux a c Bool -> a c Bool -> Quux a b c #foo :: Quux a b Int -> a0 -> a b Int -> a0 -> Quux a b a0 #Quux a b (Quux a b a0) -> Int -> a b a0) -> Int -> Quux a b (Quux a b Int) a b Int) #

                  Quux a b c) -> Quux a c Bool -> a c Bool -> Quux a b c #dataThud Int ( Int (Quux a [a] c)data Thud Int ( Int (Quux a [a] c) Norf Int BoolIntBool#typePlugh Int c Bool :: * Int c Bool :: Type#

                  data Thud Int c :: * Int c :: Type #

                  norf :: Plugh Int c Bool -> Int -> (Int -> c) -> Bool Int c Bool -> Int -> (Int -> c) -> Bool#

                  typePlugh [a] c [b] :: * [a] c [b] :: Type#

                  data Thud [a] c :: * [a] c :: Type #

                • f :: Integer
                • :: Integer

                  f :: Integer :: Integer #

                  foo :: Int :: Int #

                • g :: Int
                • :: Int

                  g :: Int :: Int #

                  aClass :: AType -> Int -> Int #

                  aClass :: a -> Int :: a -> Int #

                  aClass :: AType -> Int -> Int#

                  IntaClass :: AType -> Int -> Int#

                  dataBlubType = Show x => = Show x => BlubCtor x
                • Blub :: () => forall x. Show x => x -> x. Show x => x -> BlubType
                • pattern PatWithExplicitSig :: Eq somex => somex -> :: Eq somex => somex -> FooType somex
                • :: Ord a
                  => Int

                  First argument

                  -> Bool

                  Third argument

                  :: forall (b :: ()). d ~ ()
                  C2 :: Ord a => [a] -> :: Ord a => [a] -> H1 a a:: { field :: Int :: Int

                  hello docs

                  } -> H1 Int Int Int Int
                  } -> H1 Int a Int a
                  GadtConstructorArgs
                  Safe HaskellSafe

                  GadtConstructorArgs

                  Documentation

                  data Boo where #

                  Constructors

                  Fot

                  Fields

                  Fob

                  Record GADT with docs

                  Fields

                  \ No newline at end of file diff --git a/html-test/ref/Hash.html b/html-test/ref/Hash.html index c4f04f2c..8fd04bb4 100644 --- a/html-test/ref/Hash.html +++ b/html-test/ref/Hash.html @@ -87,23 +87,37 @@ >
                • new :: (Eq key, :: (Eq key, Hash key) => Int -> IO ( key) => Int -> IO (HashTable key val)
                • insert :: (Eq key, :: (Eq key, Hash key) => key -> val -> IO ()
                • key) => key -> val -> IO ()
                • lookup :: Hash key => key -> IO (Maybe val)
                • key => key -> IO (Maybe val)
                • class
                • hash :: a -> Int
                • :: a -> Intkey should be an instance of EqEq.

                  new :: (Eq key, :: (Eq key, Hash key) => Int -> IO ( key) => Int -> IO (HashTable key val) #

                  insert :: (Eq key, :: (Eq key, Hash key) => key -> val -> IO () key) => key -> val -> IO () #

                  lookup :: Hash key => key -> IO (Maybe val) key => key -> IO (Maybe val) #

                  Looks up a key in the hash table, returns JustJust val if the key was found, or NothingNothing otherwise.

                  hash :: a -> Int :: a -> Int #

                  hashes the value of type a into an IntInt

                  Hash Float Float #
                  AType Int
                  IntegerStringString Show Show Expr

                  showsPrec :: Int -> :: Int -> Expr -> ShowS

                  -> ShowS#

                  show :: Expr -> String

                  -> String#

                  showList :: [Expr] -> ShowS

                  ] -> ShowS#

                  Show Show BinOp

                  showsPrec :: Int -> :: Int -> BinOp -> ShowS

                  -> ShowS#

                  show :: BinOp -> String

                  -> String#

                  showList :: [BinOp] -> ShowS

                  ] -> ShowS#

                  eval :: Expr -> Integer -> Integer#

                  expr :: QuasiQuoter :: QuasiQuoter #

                  parseExprExp :: String -> Q Exp :: String -> Q Exp #

                  val :: Integer :: Integer #

                  Functor ( Functor (SomeType f)SomeType f a -> SomeType f b

                  f b #

                  (<$)SomeType f b -> SomeType f a

                  f a #

                  Applicative f => Applicative ( Applicative f => Applicative (SomeType f)pure :: a -> SomeType f a

                  f a #

                  (<*>)SomeType f a -> SomeType f b

                  f b #

                  liftA2SomeType f b -> SomeType f c

                  f c #

                  (*>)SomeType f b -> SomeType f b

                  f b #

                  (<*)SomeType f b -> SomeType f a

                  f a #

                  decl :: Q [Dec] :: Q [Dec] #

                • = A Int (Maybe Float)
                • Int (MaybeFloat)
                • | BT a b, T Int Float)
                • IntFloat)
                • p :: Int
                • :: Int
                • qr, s :: Int
                • :: Int }
                • t :: T1 -> T2 Int Int -> Int Int -> T3 Bool Bool -> Bool Bool -> T4 Float Float -> Float Float -> T5 () ()
                • u, v :: Int
                • :: Int }
                • s1 :: Int
                • :: Int
                • s2 :: Int
                • :: Int
                • s3 :: Int
                • :: Int}
                • p :: R -> Int
                • -> Int
                • qu :: R -> Int
                • -> Int
                • class
                • a :: IO a
                • :: IO a
                • ba :: C a => IO a
                • a => IO a
                • f :: C a => a -> Int
                • a => a -> Int
                • g :: Int -> IO CInt
                • :: Int -> IO CInt
                • hidden :: Int -> Int
                • :: Int -> Int
                • module VisibleT () () -> T2 Int Int -> ( Int Int -> (T3 Bool Bool -> Bool Bool -> T4 Float Float) -> Float Float) -> T5 () () -> IO ()
                • () () -> IO ()
                • l :: (Int, Int, Float) -> Int
                • :: (Int, Int, Float) -> Int
                • mR -> N1 () -> IO Int
                • () -> IOInt
                • o :: Float -> IO Float
                • :: Float -> IOFloat
                • f' :: Int
                • :: Int
                • withType :: Int
                • :: Int
                • withoutType
                • Int (MaybeFloat)IntFloat)d :: T Float b Float b #

                  e :: (Float, Float) :: (Float, Float) #

                  D IntInt#d :: T Int b Int b #

                  e :: (Int, Int) :: (Int, Int) #

                  a :: C a => IO a a => IO a #

                  f :: C a => a -> Int a => a -> Int #

                  g :: Int -> IO CInt :: Int -> IO CInt #

                  hidden :: Int -> Int :: Int -> Int #

                  IntIntFloatFloat)-> IO ()
                  Show x => Show x => BlubCtor xBlub :: () => forall x. Show x => x -> x. Show x => x -> BlubType #pattern PatWithExplicitSig :: Eq somex => somex -> :: Eq somex => somex -> FooType somex #Cons :: Maybe h -> :: Maybe h -> Pattern t -> PatternRevCons :: Maybe h -> :: Maybe h -> RevPattern t -> RevPattern
                • fib :: Integer -> Integer
                • :: Integer -> Integer

                  fib :: Integer -> Integer :: Integer -> Integer #

                  Fibonacci number of given IntegerInteger.

                  fib n <= fib (n + 1)
                  QuantifiedConstraints
                  Safe HaskellSafe

                  QuantifiedConstraints

                  Documentation

                  class Foo a where #

                  Methods

                  fooed :: a #

                  needsParensAroundContext :: (forall x. Foo (f x)) => f Int #

                  \ No newline at end of file diff --git a/html-test/ref/QuasiExpr.html b/html-test/ref/QuasiExpr.html index 42b21f70..dfded323 100644 --- a/html-test/ref/QuasiExpr.html +++ b/html-test/ref/QuasiExpr.html @@ -58,7 +58,9 @@ >
                  IntExpr Integer
                  AntiIntExpr String
                  AntiExpr String
                  A Int (Maybe Float)

                  This comment describes the T a b, T Int Float)

                  This comment describes the p :: Int :: Int

                  This comment applies to the r, s :: Int :: Int

                  This comment applies to both t :: T1 -> T2 Int Int -> Int Int -> T3 Bool Bool -> Bool Bool -> T4 Float Float -> Float Float -> T5 () ()

                  u, v :: Int :: Int
                  s1 :: Int :: Int

                  The s2 :: Int :: Int

                  The s3 :: Int :: Int

                  The p :: R -> Int -> Int #

                  u :: R -> Int -> Int #

                  a :: IO a :: IO a #

                  D Float Float #
                  -> T2 Int Int

                  This argument has type 'T2 Int Int'

                  -> (T3 Bool Bool -> Bool Bool -> T4 Float Float)

                  This argument has type

                  -> IO ()

                  This is the result type

                  :: (Int, Int, Float)-> Int-> IOInt
                  :: (Int, Int, Float)

                  takes a triple

                  -> Int

                  returns an IntInt

                  -> IO Int

                  and the return value

                  :: Float-> IOFloat#X<> (a :: *) = (a :: Type) = XAssocDY :: * :: Type#

                  AssocT Y :: * :: Type #

                  #Y<> (a :: *) = a (a :: Type) = a#Y<> (a :: *) = a (a :: Type) = aX<> (a :: *) (a :: Type)#X<> (a :: *) = (a :: Type) = X#
                  :: Float

                  The input float

                  -> IO Float

                  The output float

                  f' :: Int :: Int #

                  withType :: Int :: Int #

                • f :: Integer
                • :: Integer

                  f :: Integer :: Integer #

                • forkTH :: Q Exp
                • :: Q Exp

                  forkTH :: Q Exp :: Q Exp #

                  ...given a raw Addr#Addr# to the string, and the length of the string.

                • f :: Int
                • :: Int

                  f :: Int :: Int #

                • foo :: Integer
                • :: Integer
                • bar :: Integer
                • :: Integer

                  foo :: Integer :: Integer #

                  bar :: Integer :: Integer #

                  AssocD X :: * :: Type #

                  AssocT X :: * :: Type #

                  #

                  External instance

                  Foo X :: *) :: Type)

                  Doc for: type instance Foo X = Y

                  X <> (a :: *) (a :: Type) #

                  Doc for: type instance Foo Y = X

                  Y <> (a :: *) (a :: Type) #

                  Doc for: type instance Foo Y = X

                  #

                  Doc for: type instance Foo X = Y

                  AssocD Y :: * :: Type #

                  AssocT Y :: * :: Type #

                  AssocD X :: * :: Type #

                  AssocT X :: * :: Type #

                  Y <> (a :: *) (a :: Type) #

                  Should be visible, but with a hidden right hand side

                  #

                  Should be visible, but with a hidden right hand side

                  #

                  External instance

                • x :: Int
                • :: Int

                  x :: Int :: Int #

                  Unicode2
                  Safe HaskellSafe

                  Unicode2

                  Synopsis

                  Documentation

                  ü :: () #

                  All of the following work with a unicode character ü:

                  • an italicized ü
                  • inline code ü
                  • a code block:
                  ü
                  \ No newline at end of file diff --git a/html-test/ref/Visible.html b/html-test/ref/Visible.html index 22c6be6c..308689e4 100644 --- a/html-test/ref/Visible.html +++ b/html-test/ref/Visible.html @@ -45,7 +45,11 @@ >

                  visible :: Int -> Int :: Int -> Int #

                  $(let i = [t| Int |] in [t| $i -> $i |]) +foo x y = x + y diff --git a/html-test/src/ConstructorArgs.hs b/html-test/src/ConstructorArgs.hs new file mode 100644 index 00000000..6b0da711 --- /dev/null +++ b/html-test/src/ConstructorArgs.hs @@ -0,0 +1,56 @@ +{-# LANGUAGE GADTs, PatternSynonyms #-} + +module ConstructorArgs (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where + +data Foo + = Rec -- ^ doc on a record + { x :: String -- ^ doc on the `String` field of `Rec` + , y :: String -- ^ doc on the `String` field of `Rec` + } + | Baz Int String -- ^ old prefix doc style + | Boa -- ^ doc on the `Boa` constrictor + !Int -- ^ doc on the `Int` field of `Boa` + !String -- ^ doc on the `String` field of `Boa` + | Int :| String -- ^ old infix doc style + | Int -- ^ doc on the `Int` field of the `:*` constructor + :* -- ^ doc on the `:*` constructor + String -- ^ doc on the `String` field of the `:*` constructor + +infixr 1 `Foo` +infixr 2 `Boa` +infixr 3 :* + +data Boo where + -- | Info about a 'Foo' + Foo :: Int -- ^ `Int` field of `Foo` + -> String -- ^ `String` field of `Foo` + -> Boo -- ^ Make a `Boo` + + -- | no argument docs GADT + Foa :: Int -> Boo + +infixr 4 `Boo` + +-- | Info about bundled 'Fo' +pattern Fo :: Int -- ^ an 'Int' + -> String -- ^ a 'String' + -> Boo -- ^ a 'Boo' +pattern Fo x y = Foo x y + +-- | Bundled and no argument docs +pattern Fo' :: Boo +pattern Fo' = Foo 1 "hi" + +infixr 5 `Fo` + +-- | Info about not-bundled 'Bo' +pattern Bo :: Int -- ^ an 'Int' + -> String -- ^ a 'String' + -> Boo -- ^ a 'Boo' pattern +pattern Bo x y = Foo x y + +-- | Not bunded and no argument docs +pattern Bo' :: Int -> String -> Boo +pattern Bo' x y = Foo x y + +infixr 6 `Bo` diff --git a/html-test/src/GadtConstructorArgs.hs b/html-test/src/GadtConstructorArgs.hs new file mode 100644 index 00000000..79ffb4d3 --- /dev/null +++ b/html-test/src/GadtConstructorArgs.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, PatternSynonyms #-} + +module GadtConstructorArgs (Boo(..)) where + +data Boo where + Fot :: { x :: Int -- ^ an 'x' + , y :: Int -- ^ a 'y' + } -> Boo + + -- | Record GADT with docs + Fob :: { w :: Int -- ^ a 'w' + , z :: Int -- ^ a 'z' + } -> Boo -- ^ a 'Boo' diff --git a/html-test/src/QuantifiedConstraints.hs b/html-test/src/QuantifiedConstraints.hs new file mode 100644 index 00000000..82dd81e5 --- /dev/null +++ b/html-test/src/QuantifiedConstraints.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE QuantifiedConstraints #-} +module QuantifiedConstraints where + +class Foo a where + fooed :: a + +needsParensAroundContext :: (forall x. Foo (f x)) => f Int +needsParensAroundContext = fooed + +needsNoParensAroundContext :: Foo (f Int) => f Int +needsNoParensAroundContext = fooed diff --git a/html-test/src/Unicode2.hs b/html-test/src/Unicode2.hs new file mode 100644 index 00000000..ca6b18ba --- /dev/null +++ b/html-test/src/Unicode2.hs @@ -0,0 +1,18 @@ +module Unicode2 where + +-- | All of the following work with a unicode character ü: +-- +-- * an italicized /ü/ +-- +-- * inline code @ü@ +-- +-- * a code block: +-- +-- > ü +-- +-- * a url +-- +-- * a link to 'ü' +-- +ü :: () +ü = () diff --git a/latex-test/ref/ConstructorArgs/ConstructorArgs.tex b/latex-test/ref/ConstructorArgs/ConstructorArgs.tex new file mode 100644 index 00000000..44304f47 --- /dev/null +++ b/latex-test/ref/ConstructorArgs/ConstructorArgs.tex @@ -0,0 +1,69 @@ +\haddockmoduleheading{ConstructorArgs} +\label{module:ConstructorArgs} +\haddockbeginheader +{\haddockverb\begin{verbatim} +module ConstructorArgs ( + Foo((:|), Rec, Baz, Boa, (:*), x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo, + pattern Bo' + ) where\end{verbatim}} +\haddockendheader + +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +data\ Foo +\end{tabular}]\haddockbegindoc +\enspace \emph{Constructors}\par +\haddockbeginconstrs +\haddockdecltt{=} & \haddockdecltt{Rec} & doc on a record \\ + & \haddocktt{\qquad \{} \haddockdecltt{x :: String} & doc on the \haddockid{String} field of \haddockid{Rec} \\ + & \haddocktt{\qquad ,} \haddockdecltt{y :: String} & doc on the \haddockid{String} field of \haddockid{Rec} \\ & \haddocktt{\qquad \}} \\ +\haddockdecltt{|} & \haddockdecltt{Baz Int String} & old prefix doc style \\ +\haddockdecltt{|} & \haddockdecltt{Boa} & doc on the \haddockid{Boa} constrictor \\ + & \qquad \haddockdecltt{!Int} & doc on the \haddockid{Int} field of \haddockid{Boa} \\ + & \qquad \haddockdecltt{!String} & doc on the \haddockid{String} field of \haddockid{Boa} \\ +\haddockdecltt{|} & \haddockdecltt{Int :| String} & old infix doc style \\ +\haddockdecltt{|} & \haddockdecltt{(:*)} & doc on the \haddockid{:*} constructor \\ + & \qquad \haddockdecltt{Int} & doc on the \haddockid{Int} field of the \haddockid{:*} constructor \\ + & \qquad \haddockdecltt{String} & doc on the \haddockid{String} field of the \haddockid{:*} constructor \\ +\end{tabulary}\par +\end{haddockdesc} +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +data\ Boo\ where +\end{tabular}]\haddockbegindoc +\enspace \emph{Constructors}\par +\haddockbeginconstrs +& \haddockdecltt{Foo} & Info about a \haddockid{Foo} \\ + & \qquad \haddockdecltt{::} \enspace \haddockdecltt{Int} & \haddockid{Int} field of \haddockid{Foo} \\ + & \qquad \haddockdecltt{->} \enspace \haddockdecltt{String} & \haddockid{String} field of \haddockid{Foo} \\ + & \qquad \haddockdecltt{->} \enspace \haddockdecltt{Boo} & Make a \haddockid{Boo} \\ +& \haddockdecltt{Foa :: Int -> Boo} & no argument docs GADT \\ +\end{tabulary}\par +\enspace \emph{Bundled Patterns}\par +\haddockbeginconstrs +& \haddockdecltt{pattern Fo} & Info about bundled \haddockid{Fo} \\ + & \qquad \haddockdecltt{::} \enspace \haddockdecltt{Int} & an \haddockid{Int} \\ + & \qquad \haddockdecltt{->} \enspace \haddockdecltt{String} & a \haddockid{String} \\ + & \qquad \haddockdecltt{->} \enspace \haddockdecltt{Boo} & a \haddockid{Boo} \\ +& \haddockdecltt{pattern Fo' :: Boo} & Bundled and no argument docs \\ +\end{tabulary}\par +\end{haddockdesc} +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +pattern\ Bo +\end{tabular}]\haddockbegindoc +\haddockbeginargs +\haddockdecltt{::} & \haddockdecltt{Int} & an \haddockid{Int} \\ +\haddockdecltt{->} & \haddockdecltt{String} & a \haddockid{String} \\ +\haddockdecltt{->} & \haddockdecltt{Boo} & a \haddockid{Boo} pattern \\ +\end{tabulary}\par +Info about not-bundled \haddockid{Bo}\par + +\end{haddockdesc} +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +pattern\ Bo'\ ::\ Int\ ->\ String\ ->\ Boo +\end{tabular}]\haddockbegindoc +Not bunded and no argument docs\par + +\end{haddockdesc} \ No newline at end of file diff --git a/latex-test/ref/ConstructorArgs/haddock.sty b/latex-test/ref/ConstructorArgs/haddock.sty new file mode 100644 index 00000000..6e031a98 --- /dev/null +++ b/latex-test/ref/ConstructorArgs/haddock.sty @@ -0,0 +1,57 @@ +% Default Haddock style definitions. To use your own style, invoke +% Haddock with the option --latex-style=mystyle. + +\usepackage{tabulary} % see below + +% make hyperlinks in the PDF, and add an expandabale index +\usepackage[pdftex,bookmarks=true]{hyperref} + +\newenvironment{haddocktitle} + {\begin{center}\bgroup\large\bfseries} + {\egroup\end{center}} +\newenvironment{haddockprologue}{\vspace{1in}}{} + +\newcommand{\haddockmoduleheading}[1]{\chapter{\texttt{#1}}} + +\newcommand{\haddockbeginheader}{\hrulefill} +\newcommand{\haddockendheader}{\noindent\hrulefill} + +% a little gap before the ``Methods'' header +\newcommand{\haddockpremethods}{\vspace{2ex}} + +% inserted before \\begin{verbatim} +\newcommand{\haddockverb}{\small} + +% an identifier: add an index entry +\newcommand{\haddockid}[1]{\haddocktt{#1}\index{#1@\texttt{#1}}} + +% The tabulary environment lets us have a column that takes up ``the +% rest of the space''. Unfortunately it doesn't allow +% the \end{tabulary} to be in the expansion of a macro, it must appear +% literally in the document text, so Haddock inserts +% the \end{tabulary} itself. +\newcommand{\haddockbeginconstrs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} +\newcommand{\haddockbeginargs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} + +\newcommand{\haddocktt}[1]{{\small \texttt{#1}}} +\newcommand{\haddockdecltt}[1]{{\small\bfseries \texttt{#1}}} + +\makeatletter +\newenvironment{haddockdesc} + {\list{}{\labelwidth\z@ \itemindent-\leftmargin + \let\makelabel\haddocklabel}} + {\endlist} +\newcommand*\haddocklabel[1]{\hspace\labelsep\haddockdecltt{#1}} +\makeatother + +% after a declaration, start a new line for the documentation. +% Otherwise, the documentation starts right after the declaration, +% because we're using the list environment and the declaration is the +% ``label''. I tried making this newline part of the label, but +% couldn't get that to work reliably (the space seemed to stretch +% sometimes). +\newcommand{\haddockbegindoc}{\hfill\\[1ex]} + +% spacing between paragraphs and no \parindent looks better +\parskip=10pt plus2pt minus2pt +\setlength{\parindent}{0cm} diff --git a/latex-test/ref/ConstructorArgs/main.tex b/latex-test/ref/ConstructorArgs/main.tex new file mode 100644 index 00000000..80f639c5 --- /dev/null +++ b/latex-test/ref/ConstructorArgs/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{ConstructorArgs} +\end{document} \ No newline at end of file diff --git a/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex b/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex new file mode 100644 index 00000000..7aaf5512 --- /dev/null +++ b/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex @@ -0,0 +1,25 @@ +\haddockmoduleheading{GadtConstructorArgs} +\label{module:GadtConstructorArgs} +\haddockbeginheader +{\haddockverb\begin{verbatim} +module GadtConstructorArgs ( + Boo(Fot, Fob, x, y, w, z) + ) where\end{verbatim}} +\haddockendheader + +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +data\ Boo\ where +\end{tabular}]\haddockbegindoc +\enspace \emph{Constructors}\par +\haddockbeginconstrs +& \haddockdecltt{Fot} & \\ + & \qquad \haddockdecltt{:: \{} \enspace \haddockdecltt{x :: Int} & an \haddockid{x} \\ + & \qquad \haddockdecltt{\ \ \ \ ,} \enspace \haddockdecltt{y :: Int} & a \haddockid{y} \\ + & \qquad \haddockdecltt{\ \ \ \ \} ->} \enspace \haddockdecltt{Boo} & \\ +& \haddockdecltt{Fob} & Record GADT with docs \\ + & \qquad \haddockdecltt{:: \{} \enspace \haddockdecltt{w :: Int} & a \haddockid{w} \\ + & \qquad \haddockdecltt{\ \ \ \ ,} \enspace \haddockdecltt{z :: Int} & a \haddockid{z} \\ + & \qquad \haddockdecltt{\ \ \ \ \} ->} \enspace \haddockdecltt{Boo} & a \haddockid{Boo} \\ +\end{tabulary}\par +\end{haddockdesc} \ No newline at end of file diff --git a/latex-test/ref/GadtConstructorArgs/haddock.sty b/latex-test/ref/GadtConstructorArgs/haddock.sty new file mode 100644 index 00000000..6e031a98 --- /dev/null +++ b/latex-test/ref/GadtConstructorArgs/haddock.sty @@ -0,0 +1,57 @@ +% Default Haddock style definitions. To use your own style, invoke +% Haddock with the option --latex-style=mystyle. + +\usepackage{tabulary} % see below + +% make hyperlinks in the PDF, and add an expandabale index +\usepackage[pdftex,bookmarks=true]{hyperref} + +\newenvironment{haddocktitle} + {\begin{center}\bgroup\large\bfseries} + {\egroup\end{center}} +\newenvironment{haddockprologue}{\vspace{1in}}{} + +\newcommand{\haddockmoduleheading}[1]{\chapter{\texttt{#1}}} + +\newcommand{\haddockbeginheader}{\hrulefill} +\newcommand{\haddockendheader}{\noindent\hrulefill} + +% a little gap before the ``Methods'' header +\newcommand{\haddockpremethods}{\vspace{2ex}} + +% inserted before \\begin{verbatim} +\newcommand{\haddockverb}{\small} + +% an identifier: add an index entry +\newcommand{\haddockid}[1]{\haddocktt{#1}\index{#1@\texttt{#1}}} + +% The tabulary environment lets us have a column that takes up ``the +% rest of the space''. Unfortunately it doesn't allow +% the \end{tabulary} to be in the expansion of a macro, it must appear +% literally in the document text, so Haddock inserts +% the \end{tabulary} itself. +\newcommand{\haddockbeginconstrs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} +\newcommand{\haddockbeginargs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} + +\newcommand{\haddocktt}[1]{{\small \texttt{#1}}} +\newcommand{\haddockdecltt}[1]{{\small\bfseries \texttt{#1}}} + +\makeatletter +\newenvironment{haddockdesc} + {\list{}{\labelwidth\z@ \itemindent-\leftmargin + \let\makelabel\haddocklabel}} + {\endlist} +\newcommand*\haddocklabel[1]{\hspace\labelsep\haddockdecltt{#1}} +\makeatother + +% after a declaration, start a new line for the documentation. +% Otherwise, the documentation starts right after the declaration, +% because we're using the list environment and the declaration is the +% ``label''. I tried making this newline part of the label, but +% couldn't get that to work reliably (the space seemed to stretch +% sometimes). +\newcommand{\haddockbegindoc}{\hfill\\[1ex]} + +% spacing between paragraphs and no \parindent looks better +\parskip=10pt plus2pt minus2pt +\setlength{\parindent}{0cm} diff --git a/latex-test/ref/GadtConstructorArgs/main.tex b/latex-test/ref/GadtConstructorArgs/main.tex new file mode 100644 index 00000000..dc1a1aa3 --- /dev/null +++ b/latex-test/ref/GadtConstructorArgs/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{GadtConstructorArgs} +\end{document} \ No newline at end of file diff --git a/latex-test/src/ConstructorArgs/ConstructorArgs.hs b/latex-test/src/ConstructorArgs/ConstructorArgs.hs new file mode 100644 index 00000000..6b0da711 --- /dev/null +++ b/latex-test/src/ConstructorArgs/ConstructorArgs.hs @@ -0,0 +1,56 @@ +{-# LANGUAGE GADTs, PatternSynonyms #-} + +module ConstructorArgs (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where + +data Foo + = Rec -- ^ doc on a record + { x :: String -- ^ doc on the `String` field of `Rec` + , y :: String -- ^ doc on the `String` field of `Rec` + } + | Baz Int String -- ^ old prefix doc style + | Boa -- ^ doc on the `Boa` constrictor + !Int -- ^ doc on the `Int` field of `Boa` + !String -- ^ doc on the `String` field of `Boa` + | Int :| String -- ^ old infix doc style + | Int -- ^ doc on the `Int` field of the `:*` constructor + :* -- ^ doc on the `:*` constructor + String -- ^ doc on the `String` field of the `:*` constructor + +infixr 1 `Foo` +infixr 2 `Boa` +infixr 3 :* + +data Boo where + -- | Info about a 'Foo' + Foo :: Int -- ^ `Int` field of `Foo` + -> String -- ^ `String` field of `Foo` + -> Boo -- ^ Make a `Boo` + + -- | no argument docs GADT + Foa :: Int -> Boo + +infixr 4 `Boo` + +-- | Info about bundled 'Fo' +pattern Fo :: Int -- ^ an 'Int' + -> String -- ^ a 'String' + -> Boo -- ^ a 'Boo' +pattern Fo x y = Foo x y + +-- | Bundled and no argument docs +pattern Fo' :: Boo +pattern Fo' = Foo 1 "hi" + +infixr 5 `Fo` + +-- | Info about not-bundled 'Bo' +pattern Bo :: Int -- ^ an 'Int' + -> String -- ^ a 'String' + -> Boo -- ^ a 'Boo' pattern +pattern Bo x y = Foo x y + +-- | Not bunded and no argument docs +pattern Bo' :: Int -> String -> Boo +pattern Bo' x y = Foo x y + +infixr 6 `Bo` diff --git a/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs b/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs new file mode 100644 index 00000000..79ffb4d3 --- /dev/null +++ b/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, PatternSynonyms #-} + +module GadtConstructorArgs (Boo(..)) where + +data Boo where + Fot :: { x :: Int -- ^ an 'x' + , y :: Int -- ^ a 'y' + } -> Boo + + -- | Record GADT with docs + Fob :: { w :: Int -- ^ a 'w' + , z :: Int -- ^ a 'z' + } -> Boo -- ^ a 'Boo' -- cgit v1.2.3 From e3b86a49b57f9b127d9c98e47e61fb15f58478e7 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Fri, 20 Jul 2018 16:05:47 +0200 Subject: Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. --- haddock-api/haddock-api.cabal | 4 ++-- haddock.cabal | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index 6a7a932b..e1a52824 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -42,7 +42,7 @@ library -- this package typically supports only single major versions build-depends: base ^>= 4.12.0 , Cabal ^>= 2.3.0 - , ghc ^>= 8.5 + , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 @@ -167,7 +167,7 @@ test-suite spec Haddock.Backends.Hyperlinker.Types build-depends: Cabal ^>= 2.3 - , ghc ^>= 8.5 + , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 diff --git a/haddock.cabal b/haddock.cabal index af606894..29d3d114 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -78,7 +78,7 @@ executable haddock xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, ghc-boot, - ghc == 8.5.*, + ghc == 8.6.*, bytestring, parsec, text, -- cgit v1.2.3 From d504a2864a4e1982e142cf88c023e7caeea3b76f Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Fri, 22 Jun 2018 21:37:22 +0200 Subject: Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes #854. --- haddock-api/src/Haddock/Interface/LexParseRn.hs | 53 ++++++++++++++++--------- 1 file changed, 35 insertions(+), 18 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 731f2a35..e83708d0 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -1,5 +1,6 @@ {-# OPTIONS_GHC -Wwarn #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ViewPatterns #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Interface.LexParseRn @@ -18,7 +19,11 @@ module Haddock.Interface.LexParseRn , processModuleHeader ) where +import Avail +import Control.Arrow +import Control.Monad import Data.List +import Data.Ord import Documentation.Haddock.Doc (metaDocConcat) import DynFlags (languageExtensions) import qualified GHC.LanguageExtensions as LangExt @@ -94,11 +99,9 @@ rename dflags gre = rn -- Generate the choices for the possible kind of thing this -- is. let choices = dataTcOccs x - -- Try to look up all the names in the GlobalRdrEnv that match - -- the names. - let names = concatMap (\c -> map gre_name (lookupGRE_RdrName c gre)) choices - case names of + -- Lookup any GlobalRdrElts that match the choices. + case concatMap (\c -> lookupGRE_RdrName c gre) choices of -- We found no names in the env so we start guessing. [] -> case choices of @@ -117,12 +120,10 @@ rename dflags gre = rn -- There is only one name in the environment that matches so -- use it. - [a] -> pure (DocIdentifier a) + [a] -> pure (DocIdentifier (gre_name a)) - -- But when there are multiple names available, default to - -- type constructors: somewhat awfully GHC returns the - -- values in the list positionally. - a:b:_ -> ambiguous dflags x (if isTyConName a then a else b) names + -- There are multiple names available. + gres -> ambiguous dflags x gres DocWarning doc -> DocWarning <$> rn doc DocEmphasis doc -> DocEmphasis <$> rn doc @@ -167,16 +168,32 @@ outOfScope dflags x = pure (monospaced a) monospaced a = DocMonospaced (DocString (showPpr dflags a)) --- | Warn about an ambiguous identifier. -ambiguous :: DynFlags -> RdrName -> Name -> [Name] -> ErrMsgM (Doc Name) -ambiguous dflags x dflt names = do - tell [msg] +-- | Handle ambiguous identifiers. +-- +-- Prefers local names primarily and type constructors or class names secondarily. +-- +-- Emits a warning if the 'GlobalRdrElts's don't belong to the same type or class. +ambiguous :: DynFlags + -> RdrName + -> [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" ++ + concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map gre_name gres) ++ + " You may be able to disambiguate the identifier by qualifying it or\n" ++ + " by hiding some imports.\n" ++ + " Defaulting to " ++ x_str ++ " 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) where - msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++ - concatMap (\n -> " * " ++ defnLoc n ++ "\n") names ++ - " You may be able to disambiguate the identifier by qualifying it or\n" ++ - " by hiding some imports.\n" ++ - " Defaulting to " ++ x_str ++ " defined " ++ defnLoc dflt + isLocalName (nameSrcLoc -> RealSrcLoc {}) = True + isLocalName _ = False x_str = '\'' : showPpr dflags x ++ "'" defnLoc = showSDoc dflags . pprNameDefnLoc -- cgit v1.2.3 From 73707ed58d879cc04cb644c5dab88c39ca1465b7 Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Sat, 23 Jun 2018 16:45:31 +0200 Subject: outOfScope: Recommend qualifying the identifier --- haddock-api/src/Haddock/Interface/LexParseRn.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index e83708d0..87face7c 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -164,7 +164,9 @@ outOfScope dflags x = Exact name -> warnAndMonospace name -- Shouldn't happen since x is out of scope where warnAndMonospace a = do - tell ["Warning: '" ++ showPpr dflags a ++ "' is out of scope."] + tell ["Warning: '" ++ 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)) -- cgit v1.2.3 From 532b209d127e4cecdbf7e9e3dcf4f653a5605b5a Mon Sep 17 00:00:00 2001 From: Masahiro Sakai Date: Sat, 21 Jul 2018 00:06:42 +0900 Subject: Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. --- doc/markup.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/markup.rst b/doc/markup.rst index 590bee00..e22c25e7 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -762,7 +762,7 @@ Special Characters ~~~~~~~~~~~~~~~~~~ The following characters have special meanings in documentation -comments: ``\\``, ``/``, ``'``, ``\```, ``"``, ``@``, ``<``, ``$``. To insert a +comments: ``\\``, ``/``, ``'``, ``\```, ``"``, ``@``, ``<``, ``$``, ``#``. To insert a literal occurrence of one of these special characters, precede it with a backslash (``\\``). -- cgit v1.2.3 From 1868443b01232d57ec11dfc831ac0a6915a2b337 Mon Sep 17 00:00:00 2001 From: Yuji Yamamoto Date: Mon, 23 Jul 2018 15:16:01 +0900 Subject: Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: : commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 --- haddock-api/src/Haddock/Interface.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index a66745ea..7c7f0e75 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -81,6 +81,7 @@ processModules processModules verbosity modules flags extIfaces = do #if defined(mingw32_HOST_OS) -- Avoid internal error: : hPutChar: invalid argument (invalid character)' non UTF-8 Windows + liftIO $ hSetEncoding stdout $ mkLocaleEncoding TransliterateCodingFailure liftIO $ hSetEncoding stderr $ mkLocaleEncoding TransliterateCodingFailure #endif -- cgit v1.2.3 From 9765c10a27013b5c9168ee507d1f3b34cb4be26f Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Sun, 15 Jul 2018 19:26:54 +0200 Subject: Match XFieldOcc rename in GHC Trac #15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) --- haddock-api/src/Haddock/Types.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index ea74043d..6da45a3b 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -696,7 +696,7 @@ type instance XUserTyVar DocNameI = NoExt type instance XKindedTyVar DocNameI = NoExt type instance XXTyVarBndr DocNameI = NoExt -type instance XFieldOcc DocNameI = DocName +type instance XCFieldOcc DocNameI = DocName type instance XXFieldOcc DocNameI = NoExt type instance XFixitySig DocNameI = NoExt -- cgit v1.2.3 From 1c4076328cfdd3aadbbbd494a240e25bd7309b0c Mon Sep 17 00:00:00 2001 From: Alexander Biehl Date: Mon, 6 Aug 2018 13:04:02 +0200 Subject: Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion --- haddock-api/src/Haddock.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 00eb50f6..1651866a 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -48,6 +48,7 @@ import Control.Exception import Data.Maybe import Data.IORef import Data.Map (Map) +import Data.Version (makeVersion) import qualified Data.Map as Map import System.IO import System.Exit @@ -362,9 +363,13 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do -- might want to fix that if/when these two get some work on them when (Flag_Hoogle `elem` flags) $ do case pkgNameVer of - (Just (PackageName pkgNameFS), Just pkgVer) -> - let pkgNameStr | unpackFS pkgNameFS == "main" && title /= [] = title - | otherwise = unpackFS pkgNameFS + (Just (PackageName pkgNameFS), mpkgVer) -> + let + pkgNameStr | unpackFS pkgNameFS == "main" && title /= [] = title + | otherwise = unpackFS pkgNameFS + + pkgVer = + fromMaybe (makeVersion []) mpkgVer in ppHoogle dflags' pkgNameStr pkgVer title (fmap _doc prologue) visibleIfaces odir _ -> putStrLn . unlines $ -- cgit v1.2.3 From 9712d8899d452292913a260058a6dd3346e8d39b Mon Sep 17 00:00:00 2001 From: Noel Bourke Date: Tue, 21 Aug 2018 08:34:18 +0100 Subject: Remove unnecessary backslashes from docs (#908) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. --- doc/markup.rst | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/doc/markup.rst b/doc/markup.rst index e22c25e7..edbd45b2 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -762,14 +762,14 @@ Special Characters ~~~~~~~~~~~~~~~~~~ The following characters have special meanings in documentation -comments: ``\\``, ``/``, ``'``, ``\```, ``"``, ``@``, ``<``, ``$``, ``#``. To insert a +comments: ``\``, ``/``, ``'``, `````, ``"``, ``@``, ``<``, ``$``, ``#``. To insert a literal occurrence of one of these special characters, precede it with a -backslash (``\\``). +backslash (``\``). Additionally, the character ``>`` has a special meaning at the beginning of a line, and the following characters have special meanings at the beginning of a paragraph: ``*``, ``-``. These characters can also be -escaped using ``\\``. +escaped using ``\``. Furthermore, the character sequence ``>>>`` has a special meaning at the beginning of a line. To escape it, just prefix the characters in the -- cgit v1.2.3 From e6aa8fb47b9477cc5ef5e46097524fe83e080f6d Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Tue, 21 Aug 2018 08:34:50 +0100 Subject: Load plugins when starting a GHC session (#905) Fixes #900 --- haddock-api/src/Haddock.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 00eb50f6..86a65901 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -75,6 +75,7 @@ import Packages import Panic (handleGhcException) import Module import FastString +import qualified DynamicLoading -------------------------------------------------------------------------------- -- * Exception handling @@ -437,7 +438,10 @@ withGhc' libDir flags ghcActs = runGhc (Just libDir) $ do -- that may need to be re-linked: Haddock doesn't do any -- dynamic or static linking at all! _ <- setSessionDynFlags dynflags'' - ghcActs dynflags'' + hscenv <- GHC.getSession + dynflags''' <- liftIO (DynamicLoading.initializePlugins hscenv dynflags'') + _ <- setSessionDynFlags dynflags''' + ghcActs dynflags''' where -- ignore sublists of flags that start with "+RTS" and end in "-RTS" -- cgit v1.2.3 From 40eb5aabed0ae52982a690be311177b2dea2a0bb Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Mon, 23 Jul 2018 13:23:35 -0700 Subject: Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing #469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) --- haddock-api/src/Haddock/Interface.hs | 59 +++++++++++++--------- .../src/Haddock/Interface/AttachInstances.hs | 11 ++-- 2 files changed, 42 insertions(+), 28 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index a66745ea..c330c5fe 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, OverloadedStrings #-} +{-# LANGUAGE CPP, OverloadedStrings, BangPatterns #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Interface @@ -51,6 +51,7 @@ import System.Directory import System.FilePath import Text.Printf +import Module (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet) import Digraph import DynFlags hiding (verbosity) import Exception @@ -59,7 +60,9 @@ import HscTypes import FastString (unpackFS) import MonadUtils (liftIO) import TcRnTypes (tcg_rdr_env) -import RdrName (plusGlobalRdrEnv) +import Name (nameIsFromExternalPackage, nameOccName) +import OccName (isTcOcc) +import RdrName (unQualOK, gre_name, globalRdrEnvElts) import ErrUtils (withTiming) #if defined(mingw32_HOST_OS) @@ -87,7 +90,7 @@ processModules verbosity modules flags extIfaces = do out verbosity verbose "Creating interfaces..." let instIfaceMap = Map.fromList [ (instMod iface, iface) | ext <- extIfaces , iface <- ifInstalledIfaces ext ] - interfaces <- createIfaces0 verbosity modules flags instIfaceMap + (interfaces, ms) <- createIfaces0 verbosity modules flags instIfaceMap let exportedNames = Set.unions $ map (Set.fromList . ifaceExports) $ @@ -96,7 +99,7 @@ processModules verbosity modules flags extIfaces = do out verbosity verbose "Attaching instances..." interfaces' <- {-# SCC attachInstances #-} withTiming getDynFlags "attachInstances" (const ()) $ do - attachInstances (exportedNames, mods) interfaces instIfaceMap + attachInstances (exportedNames, mods) interfaces instIfaceMap ms out verbosity verbose "Building cross-linking environment..." -- Combine the link envs of the external packages into one @@ -120,7 +123,7 @@ processModules verbosity modules flags extIfaces = do -------------------------------------------------------------------------------- -createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc [Interface] +createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet) createIfaces0 verbosity modules flags instIfaceMap = -- Output dir needs to be set before calling depanal since depanal uses it to -- compute output file names that are stored in the DynFlags of the @@ -150,43 +153,51 @@ createIfaces0 verbosity modules flags instIfaceMap = depanal [] False -createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc [Interface] +createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc ([Interface], ModuleSet) createIfaces verbosity flags instIfaceMap mods = do let sortedMods = flattenSCCs $ topSortModuleGraph False mods Nothing out verbosity normal "Haddock coverage:" - (ifaces, _) <- foldM f ([], Map.empty) sortedMods - return (reverse ifaces) + (ifaces, _, !ms) <- foldM f ([], Map.empty, emptyModuleSet) sortedMods + return (reverse ifaces, ms) where - f (ifaces, ifaceMap) modSummary = do + f (ifaces, ifaceMap, !ms) modSummary = do x <- {-# SCC processModule #-} withTiming getDynFlags "processModule" (const ()) $ do processModule verbosity modSummary flags ifaceMap instIfaceMap return $ case x of - Just iface -> (iface:ifaces, Map.insert (ifaceMod iface) iface ifaceMap) - Nothing -> (ifaces, ifaceMap) -- Boot modules don't generate ifaces. + Just (iface, ms') -> ( iface:ifaces + , Map.insert (ifaceMod iface) iface ifaceMap + , unionModuleSet ms ms' ) + Nothing -> ( ifaces + , ifaceMap + , ms ) -- Boot modules don't generate ifaces. -processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe Interface) +processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe (Interface, ModuleSet)) processModule verbosity modsum flags modMap instIfaceMap = do out verbosity verbose $ "Checking module " ++ moduleString (ms_mod modsum) ++ "..." tm <- {-# SCC "parse/typecheck/load" #-} loadModule =<< typecheckModule =<< parseModule modsum - -- We need to modify the interactive context's environment so that when - -- Haddock later looks for instances, it also looks in the modules it - -- encountered while typechecking. - -- - -- See https://github.com/haskell/haddock/issues/469. - hsc_env@HscEnv{ hsc_IC = old_IC } <- getSession - let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm - setSession hsc_env{ hsc_IC = old_IC { - ic_rn_gbl_env = ic_rn_gbl_env old_IC `plusGlobalRdrEnv` new_rdr_env - } } - if not $ isBootSummary modsum then do out verbosity verbose "Creating interface..." (interface, msgs) <- {-# SCC createIterface #-} withTiming getDynFlags "createInterface" (const ()) $ do runWriterGhc $ createInterface tm flags modMap instIfaceMap + + -- We need to keep track of which modules were somehow in scope so that when + -- Haddock later looks for instances, it also looks in these modules too. + -- + -- See https://github.com/haskell/haddock/issues/469. + hsc_env <- getSession + let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm + this_pkg = thisPackage (hsc_dflags hsc_env) + !mods = mkModuleSet [ nameModule name + | gre <- globalRdrEnvElts new_rdr_env + , let name = gre_name gre + , nameIsFromExternalPackage this_pkg name + , isTcOcc (nameOccName name) -- Types and classes only + , unQualOK gre ] -- In scope unqualified + liftIO $ mapM_ putStrLn (nub msgs) dflags <- getDynFlags let (haddockable, haddocked) = ifaceHaddockCoverage interface @@ -220,7 +231,7 @@ processModule verbosity modsum flags modMap instIfaceMap = do unless header $ out verbosity normal " Module header" mapM_ (out verbosity normal . (" " ++)) undocumentedExports interface' <- liftIO $ evaluate interface - return (Just interface') + return (Just (interface', mods)) else return Nothing diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index bf50ded3..2d72d117 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, MagicHash #-} +{-# LANGUAGE CPP, MagicHash, BangPatterns #-} {-# LANGUAGE TypeFamilies #-} ----------------------------------------------------------------------------- -- | @@ -34,6 +34,7 @@ import FamInstEnv import FastString import GHC import InstEnv +import Module ( ModuleSet, moduleSetElts ) import MonadUtils (liftIO) import Name import NameEnv @@ -51,11 +52,13 @@ type Modules = Set.Set Module type ExportInfo = (ExportedNames, Modules) -- Also attaches fixities -attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> Ghc [Interface] -attachInstances expInfo ifaces instIfaceMap = do - (_msgs, mb_index) <- getNameToInstancesIndex (map ifaceMod ifaces) +attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> ModuleSet -> Ghc [Interface] +attachInstances expInfo ifaces instIfaceMap mods = do + (_msgs, mb_index) <- getNameToInstancesIndex (map ifaceMod ifaces) mods' mapM (attach $ fromMaybe emptyNameEnv mb_index) ifaces where + mods' = Just (moduleSetElts mods) + -- TODO: take an IfaceMap as input ifaceMap = Map.fromList [ (ifaceMod i, i) | i <- ifaces ] -- cgit v1.2.3 From 3902a807acf4bccf5cd01d2115bed10d57316661 Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Tue, 21 Aug 2018 08:34:50 +0100 Subject: Load plugins when starting a GHC session (#905) Fixes #900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) --- haddock-api/src/Haddock.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 00eb50f6..86a65901 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -75,6 +75,7 @@ import Packages import Panic (handleGhcException) import Module import FastString +import qualified DynamicLoading -------------------------------------------------------------------------------- -- * Exception handling @@ -437,7 +438,10 @@ withGhc' libDir flags ghcActs = runGhc (Just libDir) $ do -- that may need to be re-linked: Haddock doesn't do any -- dynamic or static linking at all! _ <- setSessionDynFlags dynflags'' - ghcActs dynflags'' + hscenv <- GHC.getSession + dynflags''' <- liftIO (DynamicLoading.initializePlugins hscenv dynflags'') + _ <- setSessionDynFlags dynflags''' + ghcActs dynflags''' where -- ignore sublists of flags that start with "+RTS" and end in "-RTS" -- cgit v1.2.3 From 9c5f68605aee048a061ea7b4074b59a0a0371c4f Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 22 Sep 2018 08:32:16 -0700 Subject: Update Travis --- .travis.yml | 96 +++++++++++++++++++++++++++++++++++++------------------------ 1 file changed, 59 insertions(+), 37 deletions(-) diff --git a/.travis.yml b/.travis.yml index 290b0e0e..cc75b682 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,8 +1,8 @@ # This Travis job script has been generated by a script via # -# make_travis_yml_2.hs 'haddock.cabal' +# runghc make_travis_yml_2.hs 'haddock.cabal' # -# For more information, see https://github.com/hvr/multi-ghc-travis +# For more information, see https://github.com/haskell-CI/haskell-ci # language: c sudo: false @@ -24,54 +24,76 @@ before_cache: - rm -fv $HOME/.cabal/packages/hackage.haskell.org/01-index.tar - rm -fv $HOME/.cabal/packages/hackage.haskell.org/01-index.tar.idx + - rm -rfv $HOME/.cabal/packages/head.hackage + matrix: include: - compiler: "ghc-8.6.1" # env: TEST=--disable-tests BENCH=--disable-benchmarks addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.6.1], sources: [hvr-ghc]}} - allow_failures: - - compiler: "ghc-head" - before_install: - - HC=${CC} - - unset CC - - PATH=/opt/ghc/bin:/opt/ghc-ppa-tools/bin:$PATH - - PKGNAME='haddock' + - HC=${CC} + - HCPKG=${HC/ghc/ghc-pkg} + - unset CC + - ROOTDIR=$(pwd) + - mkdir -p $HOME/.local/bin + - "PATH=/opt/ghc/bin:/opt/ghc-ppa-tools/bin:$HOME/local/bin:$PATH" + - HCNUMVER=$(( $(${HC} --numeric-version|sed -E 's/([0-9]+)\.([0-9]+)\.([0-9]+).*/\1 * 10000 + \2 * 100 + \3/') )) + - echo $HCNUMVER install: - - cabal --version - - echo "$(${HC} --version) [$(${HC} --print-project-git-commit-id 2> /dev/null || echo '?')]" - - BENCH=${BENCH---enable-benchmarks} - - TEST=${TEST---enable-tests} - - travis_retry cabal update -v - - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config - - rm -fv cabal.project.local - - rm -f cabal.project.freeze - - travis_retry cabal new-build -w ${HC} ${TEST} ${BENCH} --dep -j2 --allow-newer --constraint 'setup.Cabal installed' all - - travis_retry cabal new-build -w ${HC} --disable-tests --disable-benchmarks --dep -j2 --allow-newer --constraint 'setup.Cabal installed' all + - cabal --version + - echo "$(${HC} --version) [$(${HC} --print-project-git-commit-id 2> /dev/null || echo '?')]" + - BENCH=${BENCH---enable-benchmarks} + - TEST=${TEST---enable-tests} + - HADDOCK=${HADDOCK-true} + - UNCONSTRAINED=${UNCONSTRAINED-true} + - NOINSTALLEDCONSTRAINTS=${NOINSTALLEDCONSTRAINTS-false} + - GHCHEAD=${GHCHEAD-false} + - travis_retry cabal update -v + - "sed -i.bak 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config" + - rm -fv cabal.project cabal.project.local + - grep -Ev -- '^\s*--' ${HOME}/.cabal/config | grep -Ev '^\s*$' + - "printf 'packages: \".\"\\n' > cabal.project" + - touch cabal.project.local + - "if ! $NOINSTALLEDCONSTRAINTS; then for pkg in $($HCPKG list --simple-output); do echo $pkg | grep -vw -- haddock | sed 's/^/constraints: /' | sed 's/-[^-]*$/ installed/' >> cabal.project.local; done; fi" + - cat cabal.project || true + - cat cabal.project.local || true + - if [ -f "./configure.ac" ]; then + (cd "." && autoreconf -i); + fi + - rm -f cabal.project.freeze + - cabal new-build -w ${HC} ${TEST} ${BENCH} --project-file="cabal.project" --dep -j2 all + - cabal new-build -w ${HC} --disable-tests --disable-benchmarks --project-file="cabal.project" --dep -j2 all + - rm -rf .ghc.environment.* "."/dist + - DISTDIR=$(mktemp -d /tmp/dist-test.XXXX) # Here starts the actual work to be performed for the package under test; # any command which exits with a non-zero exit code causes the build to fail. script: - - if [ -f configure.ac ]; then autoreconf -i; fi - - rm -rf dist/ - - cabal sdist # test that a source-distribution can be generated - - cd dist/ - - SRCTAR=(${PKGNAME}-*.tar.gz) - - SRC_BASENAME="${SRCTAR/%.tar.gz}" - - tar -xvf "./$SRC_BASENAME.tar.gz" - - cd "$SRC_BASENAME/" -## from here on, CWD is inside the extracted source-tarball - - rm -fv cabal.project.local - # this builds all libraries and executables (without tests/benchmarks) - - rm -f cabal.project.freeze - - cabal new-build -w ${HC} --disable-tests --disable-benchmarks --allow-newer --constraint 'setup.Cabal installed' all - # this builds all libraries and executables (including tests/benchmarks) - # - rm -rf ./dist-newstyle + # test that source-distributions can be generated + - (cd "." && cabal sdist) + - mv "."/dist/haddock-*.tar.gz ${DISTDIR}/ + - cd ${DISTDIR} || false + - find . -maxdepth 1 -name '*.tar.gz' -exec tar -xvf '{}' \; + - "printf 'packages: haddock-*/*.cabal\\n' > cabal.project" + - touch cabal.project.local + - "if ! $NOINSTALLEDCONSTRAINTS; then for pkg in $($HCPKG list --simple-output); do echo $pkg | grep -vw -- haddock | sed 's/^/constraints: /' | sed 's/-[^-]*$/ installed/' >> cabal.project.local; done; fi" + - cat cabal.project || true + - cat cabal.project.local || true + # this builds all libraries and executables (without tests/benchmarks) + - cabal new-build -w ${HC} --disable-tests --disable-benchmarks all + + # build & run tests, build benchmarks + - cabal new-build -w ${HC} ${TEST} ${BENCH} all + - if [ "x$TEST" = "x--enable-tests" ]; then cabal new-test -w ${HC} ${TEST} ${BENCH} all; fi + + # cabal check + - (cd haddock-* && cabal check) - # build & run tests - - cabal new-build -w ${HC} ${TEST} ${BENCH} --allow-newer --constraint 'setup.Cabal installed' all - - if [ "x$TEST" = "x--enable-tests" ]; then cabal new-test -w ${HC} ${TEST} --allow-newer --constraint 'setup.Cabal installed' all; fi + # Build without installed constraints for packages in global-db + - if $UNCONSTRAINED; then rm -f cabal.project.local; echo cabal new-build -w ${HC} --disable-tests --disable-benchmarks all; else echo "Not building without installed constraints"; fi +# REGENDATA ["haddock.cabal"] # EOF -- cgit v1.2.3 From 20623767951d24e96985d817f798f7fddb1f5c60 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 22 Sep 2018 09:33:39 -0700 Subject: Accept failing tests Also silence orphan warnings. --- haddock-test/src/Test/Haddock/Xhtml.hs | 3 +-- hoogle-test/ref/Bug722/test.txt | 2 +- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/haddock-test/src/Test/Haddock/Xhtml.hs b/haddock-test/src/Test/Haddock/Xhtml.hs index 69361f7c..8bfc973f 100644 --- a/haddock-test/src/Test/Haddock/Xhtml.hs +++ b/haddock-test/src/Test/Haddock/Xhtml.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE StandaloneDeriving #-} - +{-# OPTIONS_GHC -fno-warn-orphans #-} module Test.Haddock.Xhtml ( Xml(..) @@ -22,7 +22,6 @@ newtype Xml = Xml } deriving Eq --- TODO: Find a way to avoid warning about orphan instances. deriving instance Eq Element deriving instance Eq Content deriving instance Eq CData diff --git a/hoogle-test/ref/Bug722/test.txt b/hoogle-test/ref/Bug722/test.txt index 96f3747b..2f44ed8f 100644 --- a/hoogle-test/ref/Bug722/test.txt +++ b/hoogle-test/ref/Bug722/test.txt @@ -8,7 +8,7 @@ module Bug722 class Foo a (!@#) :: Foo a => a -> a -> a infixl 4 !@# -type family &* :: * -> * -> * +type family (&*) :: * -> * -> * infixr 3 &* data a :-& b (:^&) :: a -> b -> (:-&) a b -- cgit v1.2.3 From fb1db8f48ec97bdb26cac129c582913870e3d1bf Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 22 Sep 2018 09:41:23 -0700 Subject: Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README --- CHANGES.md | 12 ++++++++---- README.md | 6 +++--- haddock-api/haddock-api.cabal | 12 ++++++------ haddock-library/CHANGES.md | 4 ++++ haddock-library/haddock-library.cabal | 4 ++-- haddock.cabal | 10 +++++----- 6 files changed, 28 insertions(+), 20 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index d9ddab54..ee19ae3d 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -1,13 +1,17 @@ -## TBD / GHC-8.5+ +## Changes in version 2.21.0 * Overhaul handling of data declarations in XHTML and LaTeX. Adds support for documenting individual arguments of constructors/patterns (#709) -## Changes in version 2.20.0 + * Actually list all fixities for `--hoogle` (#871) + + * Fix broken instance source links (#869) -TODO + * Avoiding line breaks due to ling line in the output of `--hoogle` (#868) -## Changes in version 2.19.1 + * Capture docs on type family instances (#867) + +## Changes in version 2.20.0 * Show where instances are defined (#748) diff --git a/README.md b/README.md index 51642aab..38354996 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -# Haddock, a Haskell Documentation Tool [![Build Status](https://travis-ci.org/haskell/haddock.svg?branch=master)](https://travis-ci.org/haskell/haddock) +# Haddock, a Haskell Documentation Tool [![Build Status](https://travis-ci.org/haskell/haddock.svg?branch=ghc-8.6)](https://travis-ci.org/haskell/haddock) ## About haddock @@ -57,9 +57,9 @@ and then proceed using your favourite build tool. #### Using [`cabal new-build`](http://cabal.readthedocs.io/en/latest/nix-local-build-overview.html) ```bash -cabal new-build -w ghc-8.4.1 +cabal new-build -w ghc-8.6.1 # build & run the test suite -cabal new-test -w ghc-8.4.1 all +cabal new-test -w ghc-8.6.1 all ``` #### Using Cabal sandboxes diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index e1a52824..fa14eb50 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -1,13 +1,13 @@ cabal-version: 2.0 name: haddock-api -version: 2.20.0 +version: 2.21.0 synopsis: A documentation-generation tool for Haskell libraries description: Haddock is a documentation-generation tool for Haskell libraries license: BSD3 license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ bug-reports: https://github.com/haskell/haddock/issues copyright: (c) Simon Marlow, David Waern @@ -41,10 +41,10 @@ library -- this package typically supports only single major versions build-depends: base ^>= 4.12.0 - , Cabal ^>= 2.3.0 + , Cabal ^>= 2.4.0 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.6.0 + , haddock-library ^>= 1.7.0 , xhtml ^>= 3000.2.2 -- Versions for the dependencies below are transitively pinned by @@ -166,10 +166,10 @@ test-suite spec Haddock.Backends.Hyperlinker.Parser Haddock.Backends.Hyperlinker.Types - build-depends: Cabal ^>= 2.3 + build-depends: Cabal ^>= 2.4 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.6.0 + , haddock-library ^>= 1.7.0 , xhtml ^>= 3000.2.2 , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 diff --git a/haddock-library/CHANGES.md b/haddock-library/CHANGES.md index e41b8087..ec30a4d3 100644 --- a/haddock-library/CHANGES.md +++ b/haddock-library/CHANGES.md @@ -1,3 +1,7 @@ +## Changes in version 1.7.0 + + * Replace `attoparsec` with `parsec` (#799) + ## Changes in version 1.6.0 * `MetaDoc` stores package name for since annotations diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 1fc3f772..820a36ad 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -1,6 +1,6 @@ cabal-version: 2.0 name: haddock-library -version: 1.6.0 +version: 1.7.0 synopsis: Library exposing some functionality of Haddock. description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it @@ -10,7 +10,7 @@ description: Haddock is a documentation-generation tool for Haskell itself, see the ‘haddock’ package. license: BSD3 license-files: LICENSE -maintainer: Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ bug-reports: https://github.com/haskell/haddock/issues category: Documentation diff --git a/haddock.cabal b/haddock.cabal index 29d3d114..1c84562d 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -1,6 +1,6 @@ cabal-version: 2.0 name: haddock -version: 2.20.0 +version: 2.21.0 synopsis: A documentation-generation tool for Haskell libraries description: This is Haddock, a tool for automatically generating documentation @@ -23,17 +23,17 @@ description: without any documentation annotations, Haddock can generate useful documentation from your source code. . - <> + <> license: BSD3 license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ bug-reports: https://github.com/haskell/haddock/issues copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==8.4.* +tested-with: GHC==8.6.* extra-source-files: CHANGES.md @@ -142,7 +142,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.20.0 + build-depends: haddock-api == 2.21.0 test-suite html-test type: exitcode-stdio-1.0 -- cgit v1.2.3 From 246905efb043ca1aec041defe77b2cfa2cbcda92 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 22 Sep 2018 10:53:31 -0700 Subject: Turn haddock-library into a minor release Fix some version bounds in haddock-library too. --- haddock-api/haddock-api.cabal | 4 ++-- haddock-library/CHANGES.md | 2 +- haddock-library/haddock-library.cabal | 7 ++++--- 3 files changed, 7 insertions(+), 6 deletions(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index fa14eb50..384b5794 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -44,7 +44,7 @@ library , Cabal ^>= 2.4.0 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.7.0 + , haddock-library ^>= 1.6.1 , xhtml ^>= 3000.2.2 -- Versions for the dependencies below are transitively pinned by @@ -169,7 +169,7 @@ test-suite spec build-depends: Cabal ^>= 2.4 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.7.0 + , haddock-library ^>= 1.6.1 , xhtml ^>= 3000.2.2 , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 diff --git a/haddock-library/CHANGES.md b/haddock-library/CHANGES.md index ec30a4d3..c62edd85 100644 --- a/haddock-library/CHANGES.md +++ b/haddock-library/CHANGES.md @@ -1,4 +1,4 @@ -## Changes in version 1.7.0 +## Changes in version 1.6.1 * Replace `attoparsec` with `parsec` (#799) diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 820a36ad..195d409e 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -1,6 +1,6 @@ cabal-version: 2.0 name: haddock-library -version: 1.7.0 +version: 1.6.1 synopsis: Library exposing some functionality of Haddock. description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it @@ -71,7 +71,7 @@ test-suite spec Documentation.Haddock.Utf8Spec build-depends: - base >= 4.5 && < 4.12 + base >= 4.5 && < 4.13 , base-compat >= 0.9.3 && < 0.11 , bytestring >= 0.9.2.1 && < 0.11 , containers >= 0.4.2.1 && < 0.7 @@ -91,8 +91,9 @@ test-suite fixtures main-is: Fixtures.hs ghc-options: -Wall -O0 hs-source-dirs: fixtures + buildable: False build-depends: - base >= 4.5 && < 4.12 + base >= 4.5 && < 4.13 , base-compat >= 0.9.3 && < 0.11 , directory ^>= 1.3.0.2 , filepath ^>= 1.4.1.2 -- cgit v1.2.3 From 7873f4c1011c5ab61ab050399a129d48b54b3491 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 22 Sep 2018 11:42:54 -0700 Subject: keep cabal.project file --- .travis.yml | 13 ++----------- 1 file changed, 2 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index cc75b682..681399b9 100644 --- a/.travis.yml +++ b/.travis.yml @@ -53,9 +53,8 @@ install: - GHCHEAD=${GHCHEAD-false} - travis_retry cabal update -v - "sed -i.bak 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config" - - rm -fv cabal.project cabal.project.local + - rm -fv cabal.project.local - grep -Ev -- '^\s*--' ${HOME}/.cabal/config | grep -Ev '^\s*$' - - "printf 'packages: \".\"\\n' > cabal.project" - touch cabal.project.local - "if ! $NOINSTALLEDCONSTRAINTS; then for pkg in $($HCPKG list --simple-output); do echo $pkg | grep -vw -- haddock | sed 's/^/constraints: /' | sed 's/-[^-]*$/ installed/' >> cabal.project.local; done; fi" - cat cabal.project || true @@ -72,14 +71,6 @@ install: # Here starts the actual work to be performed for the package under test; # any command which exits with a non-zero exit code causes the build to fail. script: - # test that source-distributions can be generated - - (cd "." && cabal sdist) - - mv "."/dist/haddock-*.tar.gz ${DISTDIR}/ - - cd ${DISTDIR} || false - - find . -maxdepth 1 -name '*.tar.gz' -exec tar -xvf '{}' \; - - "printf 'packages: haddock-*/*.cabal\\n' > cabal.project" - - touch cabal.project.local - - "if ! $NOINSTALLEDCONSTRAINTS; then for pkg in $($HCPKG list --simple-output); do echo $pkg | grep -vw -- haddock | sed 's/^/constraints: /' | sed 's/-[^-]*$/ installed/' >> cabal.project.local; done; fi" - cat cabal.project || true - cat cabal.project.local || true # this builds all libraries and executables (without tests/benchmarks) @@ -90,7 +81,7 @@ script: - if [ "x$TEST" = "x--enable-tests" ]; then cabal new-test -w ${HC} ${TEST} ${BENCH} all; fi # cabal check - - (cd haddock-* && cabal check) + - cabal check # Build without installed constraints for packages in global-db - if $UNCONSTRAINED; then rm -f cabal.project.local; echo cabal new-build -w ${HC} --disable-tests --disable-benchmarks all; else echo "Not building without installed constraints"; fi -- cgit v1.2.3 From d6b47bbb8bfb88fcf0900fa33376131b5d8e1e6b Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Tue, 16 Oct 2018 09:36:30 -0700 Subject: Build on 7.4 and 7.8 --- haddock-library/src/Documentation/Haddock/Parser/Monad.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs index 585c76bb..a5664aa8 100644 --- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs +++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs @@ -17,6 +17,7 @@ import Data.String ( IsString(..) ) import Data.Bits ( Bits(..) ) import Data.Char ( ord ) import Data.List ( foldl' ) +import Control.Applicative as App import Documentation.Haddock.Types ( Version ) @@ -52,7 +53,7 @@ peekChar' = Parsec.lookAhead Parsec.anyChar -- | Parses the given string. Returns the parsed string. string :: Text -> Parser Text -string t = Parsec.string (T.unpack t) *> pure t +string t = Parsec.string (T.unpack t) *> App.pure t -- | Scan the input text, accumulating characters as long as the scanning -- function returns true. -- cgit v1.2.3 From b90465ac987600d09d0f9b9b5afee077925bda06 Mon Sep 17 00:00:00 2001 From: Herbert Valerio Riedel Date: Tue, 16 Oct 2018 18:45:52 +0200 Subject: Minor tweak to package description --- haddock-library/haddock-library.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 195d409e..74c928b2 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -6,8 +6,8 @@ description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it without pulling in the GHC dependency. Please note that the API is likely to change so specify upper bounds in your - project if you can't release often. For interacting with Haddock - itself, see the ‘haddock’ package. + project. For interacting with Haddock + itself, see the [haddock package](https://hackage.haskell.org/package/haddock). license: BSD3 license-files: LICENSE maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk -- cgit v1.2.3 From 44169f4b1907e34fdf8ff84cf8b7509b1dfcaf55 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Tue, 16 Oct 2018 10:54:21 -0700 Subject: Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). --- haddock-api/haddock-api.cabal | 4 ++-- haddock-library/CHANGES.md | 4 ++++ haddock-library/haddock-library.cabal | 6 +++--- 3 files changed, 9 insertions(+), 5 deletions(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index 384b5794..fa14eb50 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -44,7 +44,7 @@ library , Cabal ^>= 2.4.0 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.6.1 + , haddock-library ^>= 1.7.0 , xhtml ^>= 3000.2.2 -- Versions for the dependencies below are transitively pinned by @@ -169,7 +169,7 @@ test-suite spec build-depends: Cabal ^>= 2.4 , ghc ^>= 8.6 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.6.1 + , haddock-library ^>= 1.7.0 , xhtml ^>= 3000.2.2 , hspec >= 2.4.4 && < 2.6 , QuickCheck ^>= 2.11 diff --git a/haddock-library/CHANGES.md b/haddock-library/CHANGES.md index c62edd85..0175b6af 100644 --- a/haddock-library/CHANGES.md +++ b/haddock-library/CHANGES.md @@ -1,3 +1,7 @@ +## Changes in version 1.7.0 + + * Make `Documentation.Haddock.Parser.Monad` an internal module + ## Changes in version 1.6.1 * Replace `attoparsec` with `parsec` (#799) diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 74c928b2..0b4405b9 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -1,6 +1,6 @@ cabal-version: 2.0 name: haddock-library -version: 1.6.1 +version: 1.7.0 synopsis: Library exposing some functionality of Haddock. description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it @@ -35,14 +35,14 @@ library Documentation.Haddock.Doc Documentation.Haddock.Markup Documentation.Haddock.Parser - Documentation.Haddock.Parser.Monad Documentation.Haddock.Types Documentation.Haddock.Utf8 other-modules: Documentation.Haddock.Parser.Util + Documentation.Haddock.Parser.Monad - ghc-options: -funbox-strict-fields -Wall -fwarn-tabs -O2 + ghc-options: -funbox-strict-fields -Wall -fwarn-tabs if impl(ghc >= 8.0) ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances -- cgit v1.2.3