From 60e10eb876899165e9644013508361bf72048bdb Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Tue, 14 Nov 2017 09:21:30 -0500 Subject: Fix #548 by rendering datatype kinds more carefully (#702) --- html-test/ref/Bug548.html | 600 ++++++++++++++++++++++++++++++++++++++++++++++ html-test/src/Bug548.hs | 3 + 2 files changed, 603 insertions(+) create mode 100644 html-test/ref/Bug548.html create mode 100644 html-test/src/Bug548.hs (limited to 'html-test') diff --git a/html-test/ref/Bug548.html b/html-test/ref/Bug548.html new file mode 100644 index 00000000..1ae91878 --- /dev/null +++ b/html-test/ref/Bug548.html @@ -0,0 +1,600 @@ +Bug548

Safe HaskellSafe

Bug548

Documentation

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

Constructors

WrapArrow

Fields

Instances
Generic1 * (WrappedArrow a b)
Instance details

Associated Types

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

Methods

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

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

Arrow a => Functor (WrappedArrow a b)

Since: 2.1

Instance details

Methods

fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 #

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

Arrow a => Applicative (WrappedArrow a b)

Since: 2.1

Instance details

Methods

pure :: a0 -> WrappedArrow a b a0 #

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

liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c #

(*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 #

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

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

Since: 2.1

Instance details

Methods

empty :: WrappedArrow a b a0 #

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

some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

Generic (WrappedArrow a b c)
Instance details

Associated Types

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

Methods

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

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

type Rep1 * (WrappedArrow a b)
Instance details
type Rep1 * (WrappedArrow a b) = D1 * (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 * (MetaCons "WrapArrow" PrefixI True) (S1 * (MetaSel (Just Symbol "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * (a b))))
type Rep (WrappedArrow a b c)
Instance details
type Rep (WrappedArrow a b c) = D1 * (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 * (MetaCons "WrapArrow" PrefixI True) (S1 * (MetaSel (Just Symbol "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (a b c))))
\ No newline at end of file diff --git a/html-test/src/Bug548.hs b/html-test/src/Bug548.hs new file mode 100644 index 00000000..652d3d32 --- /dev/null +++ b/html-test/src/Bug548.hs @@ -0,0 +1,3 @@ +module Bug548 (WrappedArrow(..)) where + +import Control.Applicative -- cgit v1.2.3 From cabe219d10492e376fcfbfa514ae8a722d5e21e2 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Thu, 14 Dec 2017 01:32:53 -0800 Subject: Clickable anchors for headings (#716) See #579. This just adds an tag around the heading, pointing to the heading itself. --- haddock-api/src/Haddock/Backends/Xhtml.hs | 3 +- html-test/ref/Bug387.html | 16 ++++--- html-test/ref/BugExportHeadings.html | 36 ++++++++++------ html-test/ref/DeprecatedReExport.html | 12 ++++-- html-test/ref/Hash.html | 30 +++++++------ html-test/ref/Test.html | 72 ++++++++++++++++++++----------- 6 files changed, 110 insertions(+), 59 deletions(-) (limited to 'html-test') diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs index 55175163..01c08f7a 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml.hs @@ -697,7 +697,8 @@ processDeclOneLiner True = Just processDeclOneLiner False = Just . divTopDecl . declElem groupHeading :: Int -> String -> Html -> Html -groupHeading lev id0 = groupTag lev ! [identifier (groupId id0)] +groupHeading lev id0 = linkedAnchor grpId . groupTag lev ! [identifier grpId] + where grpId = groupId id0 groupTag :: Int -> Html -> Html groupTag lev diff --git a/html-test/ref/Bug387.html b/html-test/ref/Bug387.html index 23faa420..e6228cad 100644 --- a/html-test/ref/Bug387.html +++ b/html-test/ref/Bug387.html @@ -73,10 +73,12 @@ >

Two

Two

Three

Three

Re-exported from an other package

Re-exported from an other package

Not yet working, see

Operations on HashTables

Operations on HashTables

The Hash class

The Hash class

Type declarations

Data types

Type declarations

Data types

Records

Records

test that we can export record selectors on their own:

Class declarations

Class declarations

method

Function types

Function types

Auxiliary stuff

Auxiliary stuff

This is some documentation that is attached to a name ($aux1) @@ -1916,8 +1928,10 @@ test2 each line must begin with > (which isn't significant unless it is at the beginning of the line).

A hidden module

A hidden module

A visible module

A visible module

Existential / Universal types

Existential / Universal types

Type signatures with argument docs

Type signatures with argument docs

A section

A subsection

A section

A subsection

a literal line
Date: Sun, 17 Dec 2017 11:40:03 +0100 Subject: Treat escaped \] better in definition lists (#717) This fixes #546. --- .../src/Documentation/Haddock/Parser.hs | 15 +- html-test/ref/Bug546.html | 273 +++++++++++++++++++++ html-test/src/Bug546.hs | 55 +++++ 3 files changed, 342 insertions(+), 1 deletion(-) create mode 100644 html-test/ref/Bug546.html create mode 100644 html-test/src/Bug546.hs (limited to 'html-test') diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index 8dc2a801..dd1044cb 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -338,7 +338,7 @@ definitionList :: BS.ByteString -> Parser (DocH mod Identifier) definitionList indent = DocDefList <$> p where p = do - label <- "[" *> (parseStringBS <$> takeWhile1 (notInClass "]\n")) <* ("]" <* optional ":") + label <- "[" *> (parseStringBS <$> scan False accept) <* ("]" <* optional ":") c <- takeLine (cs, items) <- more indent p let contents = parseString . dropNLs . unlines $ c : cs @@ -346,6 +346,19 @@ definitionList indent = DocDefList <$> p Left x -> [(label, contents `docAppend` x)] Right i -> (label, contents) : i + -- handle '\]' escapes + accept True ']' = Just False + + -- stop on ']' or '\n' + accept _ ']' = Nothing + accept _ '\n' = Nothing + + -- starting an escape sequence + accept _ '\\' = Just True + + -- anything else + accept _ _ = Just False + -- | Drops all trailing newlines. dropNLs :: String -> String dropNLs = reverse . dropWhile (== '\n') . reverse diff --git a/html-test/ref/Bug546.html b/html-test/ref/Bug546.html new file mode 100644 index 00000000..1ed6657f --- /dev/null +++ b/html-test/ref/Bug546.html @@ -0,0 +1,273 @@ +Bug546
Safe HaskellSafe

Bug546

Synopsis

Documentation

x :: Integer #

Test:

[code with square \ brackets]
lorem ipsum

compile :: String -> String #

[..]
Matches any of the enclosed characters. Ranges of characters can + be specified by separating the endpoints with a '-'. '-' or + ']' can be matched by including them as the first character(s) + in the list. Never matches path separators: [/] matches + nothing at all. Named character classes can also be matched: + [:x:] within [] specifies the class named x, which matches + certain predefined characters. See below for a full list.
[^..] or [!..]
Like [..], but matches any character not listed. + Note that [^-x] is not the inverse of [-x], but + the range [^-x].
<m-n>
Matches any integer in the range m to n, inclusive. The range may + be open-ended by leaving out either number: "<->", for + instance, matches any integer.
**/
Matches any number of characters, including path separators, + excluding the empty string.

Supported character classes:

[:alnum:]
Equivalent to "0-9A-Za-z".
[:alpha:]
Equivalent to "A-Za-z".
[:blank:]
Equivalent to "\t ".
[:cntrl:]
Equivalent to "\0-\x1f\x7f".
[:digit:]
Equivalent to "0-9".
[:graph:]
Equivalent to "!-~".
[:lower:]
Equivalent to "a-z".
[:print:]
Equivalent to " -~".
[:punct:]
Equivalent to "!-/:-@[-`{-~".
[:space:]
Equivalent to "\t-\r ".
[:upper:]
Equivalent to "A-Z".
[:xdigit:]
Equivalent to "0-9A-Fa-f".
\ No newline at end of file diff --git a/html-test/src/Bug546.hs b/html-test/src/Bug546.hs new file mode 100644 index 00000000..4493b1d9 --- /dev/null +++ b/html-test/src/Bug546.hs @@ -0,0 +1,55 @@ +module Bug546 where + +-- |Test: +-- +-- [@[code with square \\ brackets\]@] lorem ipsum +x = 1 + +-- | +-- +-- [@[..\]@] Matches any of the enclosed characters. Ranges of characters can +-- be specified by separating the endpoints with a @\'-'@. @\'-'@ or +-- @']'@ can be matched by including them as the first character(s) +-- in the list. Never matches path separators: @[\/]@ matches +-- nothing at all. Named character classes can also be matched: +-- @[:x:]@ within @[]@ specifies the class named @x@, which matches +-- certain predefined characters. See below for a full list. +-- +-- [@[^..\]@ or @[!..\]@] Like @[..]@, but matches any character /not/ listed. +-- Note that @[^-x]@ is not the inverse of @[-x]@, but +-- the range @[^-x]@. +-- +-- [@\@] Matches any integer in the range m to n, inclusive. The range may +-- be open-ended by leaving out either number: @\"\<->\"@, for +-- instance, matches any integer. +-- +-- [@**/@] Matches any number of characters, including path separators, +-- excluding the empty string. +-- +-- Supported character classes: +-- +-- [@[:alnum:\]@] Equivalent to @\"0-9A-Za-z\"@. +-- +-- [@[:alpha:\]@] Equivalent to @\"A-Za-z\"@. +-- +-- [@[:blank:\]@] Equivalent to @\"\\t \"@. +-- +-- [@[:cntrl:\]@] Equivalent to @\"\\0-\\x1f\\x7f\"@. +-- +-- [@[:digit:\]@] Equivalent to @\"0-9\"@. +-- +-- [@[:graph:\]@] Equivalent to @\"!-~\"@. +-- +-- [@[:lower:\]@] Equivalent to @\"a-z\"@. +-- +-- [@[:print:\]@] Equivalent to @\" -~\"@. +-- +-- [@[:punct:\]@] Equivalent to @\"!-\/:-\@[-`{-~\"@. +-- +-- [@[:space:\]@] Equivalent to @\"\\t-\\r \"@. +-- +-- [@[:upper:\]@] Equivalent to @\"A-Z\"@. +-- +-- [@[:xdigit:\]@] Equivalent to @\"0-9A-Fa-f\"@. +compile :: String -> String +compile = id \ No newline at end of file -- cgit v1.2.3 From 088b1993fb6c6ed014a95e93d7c07f68218c7777 Mon Sep 17 00:00:00 2001 From: Oleg Grenrus Date: Tue, 26 Dec 2017 17:13:14 +0200 Subject: Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example --- CHANGES.md | 2 + doc/markup.rst | 20 ++ .../resources/html/Classic.theme/xhaddock.css | 14 ++ .../resources/html/Ocean.std-theme/ocean.css | 15 ++ haddock-api/src/Haddock/Backends/Hoogle.hs | 3 +- haddock-api/src/Haddock/Backends/LaTeX.hs | 5 +- .../src/Haddock/Backends/Xhtml/DocMarkup.hs | 19 +- haddock-api/src/Haddock/Interface/LexParseRn.hs | 1 + haddock-api/src/Haddock/InterfaceFile.hs | 32 +++ haddock-api/src/Haddock/Types.hs | 9 + haddock-library/fixtures/Fixtures.hs | 9 + .../fixtures/examples/table-simple.input | 7 + .../fixtures/examples/table-simple.parsed | 52 +++++ haddock-library/fixtures/examples/table1.input | 12 ++ haddock-library/fixtures/examples/table1.parsed | 81 +++++++ haddock-library/fixtures/examples/table2.input | 7 + haddock-library/fixtures/examples/table2.parsed | 46 ++++ haddock-library/fixtures/examples/table3.input | 7 + haddock-library/fixtures/examples/table3.parsed | 50 +++++ haddock-library/fixtures/examples/table4.input | 17 ++ haddock-library/fixtures/examples/table4.parsed | 26 +++ haddock-library/fixtures/examples/table5.input | 8 + haddock-library/fixtures/examples/table5.parsed | 53 +++++ haddock-library/haddock-library.cabal | 3 + .../src/Documentation/Haddock/Markup.hs | 4 +- .../src/Documentation/Haddock/Parser.hs | 196 ++++++++++++++++- haddock-library/src/Documentation/Haddock/Types.hs | 20 ++ html-test/ref/Table.html | 238 +++++++++++++++++++++ html-test/src/Table.hs | 47 ++++ 29 files changed, 996 insertions(+), 7 deletions(-) create mode 100644 haddock-library/fixtures/examples/table-simple.input create mode 100644 haddock-library/fixtures/examples/table-simple.parsed create mode 100644 haddock-library/fixtures/examples/table1.input create mode 100644 haddock-library/fixtures/examples/table1.parsed create mode 100644 haddock-library/fixtures/examples/table2.input create mode 100644 haddock-library/fixtures/examples/table2.parsed create mode 100644 haddock-library/fixtures/examples/table3.input create mode 100644 haddock-library/fixtures/examples/table3.parsed create mode 100644 haddock-library/fixtures/examples/table4.input create mode 100644 haddock-library/fixtures/examples/table4.parsed create mode 100644 haddock-library/fixtures/examples/table5.input create mode 100644 haddock-library/fixtures/examples/table5.parsed create mode 100644 html-test/ref/Table.html create mode 100644 html-test/src/Table.hs (limited to 'html-test') diff --git a/CHANGES.md b/CHANGES.md index b4d69ce4..7127df79 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -2,6 +2,8 @@ * to be released + * Haddock now supports tables in documentation inspired by reSTs grid tables + * A --reexport flag, which can be used to add extra modules to the top-level module tree diff --git a/doc/markup.rst b/doc/markup.rst index d0b9392d..acabaa28 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -1078,6 +1078,26 @@ If the output format supports it, the mathematics will be rendered inside the documentation. For example, the HTML backend will display the mathematics via `MathJax `__. +Grid Tables +~~~~~~~~~~~ + +Inspired by reSTs grid tables Haddock supports a complete table representation via a grid-like "ASCII art". Grid tables are described with a visual grid made up of the characters "-", "=", "|", and "+". The hyphen ("-") is used for horizontal lines (row separators). The equals sign ("=") may be used to separate optional header rows from the table body. The vertical bar ("|") is used for vertical lines (column separators). The plus sign ("+") is used for intersections of horizontal and vertical lines. :: + + -- | This is a grid table: + -- + -- +------------------------+------------+----------+----------+ + -- | Header row, column 1 | Header 2 | Header 3 | Header 4 | + -- | (header rows optional) | | | | + -- +========================+============+==========+==========+ + -- | body row 1, column 1 | column 2 | column 3 | column 4 | + -- +------------------------+------------+----------+----------+ + -- | body row 2 | Cells may span columns. | + -- +------------------------+------------+---------------------+ + -- | body row 3 | Cells may | \[ | + -- +------------------------+ span rows. | f(n) = \sum_{i=1} | + -- | body row 4 | | \] | + -- +------------------------+------------+---------------------+ + Anchors ~~~~~~~ diff --git a/haddock-api/resources/html/Classic.theme/xhaddock.css b/haddock-api/resources/html/Classic.theme/xhaddock.css index 1bf668e9..b8164815 100644 --- a/haddock-api/resources/html/Classic.theme/xhaddock.css +++ b/haddock-api/resources/html/Classic.theme/xhaddock.css @@ -392,6 +392,20 @@ td.rdoc p { } +.doc table { + border-collapse: collapse; + border-spacing: 0px; +} + +.doc th, +.doc td { + padding: 5px; + border: 1px solid #ddd; +} + +.doc th { + background-color: #f0f0f0; +} #footer { background-color: #000099; diff --git a/haddock-api/resources/html/Ocean.std-theme/ocean.css b/haddock-api/resources/html/Ocean.std-theme/ocean.css index 0852dea5..ba6af9ca 100644 --- a/haddock-api/resources/html/Ocean.std-theme/ocean.css +++ b/haddock-api/resources/html/Ocean.std-theme/ocean.css @@ -443,6 +443,21 @@ div#style-menu-holder { margin-top: 0.8em; } +.doc table { + border-collapse: collapse; + border-spacing: 0px; +} + +.doc th, +.doc td { + padding: 5px; + border: 1px solid #ddd; +} + +.doc th { + background-color: #f0f0f0; +} + .clearfix:after { clear: both; content: " "; diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index f1d8ddb2..fc71d4b5 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -328,7 +328,8 @@ markupTag dflags = Markup { markupAName = const $ str "", markupProperty = box TagPre . str, markupExample = box TagPre . str . unlines . map exampleToString, - markupHeader = \(Header l h) -> box (TagInline $ "h" ++ show l) h + markupHeader = \(Header l h) -> box (TagInline $ "h" ++ show l) h, + markupTable = \(Table _ _) -> str "TODO: table" } diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index d79e0e6c..3ac3b405 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -1140,7 +1140,8 @@ parLatexMarkup ppId = Markup { markupAName = \_ _ -> empty, markupProperty = \p _ -> quote $ verb $ text p, markupExample = \e _ -> quote $ verb $ text $ unlines $ map exampleToString e, - markupHeader = \(Header l h) p -> header l (h p) + markupHeader = \(Header l h) p -> header l (h p), + markupTable = \(Table h b) p -> table h b p } where header 1 d = text "\\section*" <> braces d @@ -1149,6 +1150,8 @@ parLatexMarkup ppId = Markup { | l > 0 && l <= 6 = text "\\subsubsection*" <> braces d header l _ = error $ "impossible header level in LaTeX generation: " ++ show l + table _ _ _ = text "{TODO: Table}" + fixString Plain s = latexFilter s fixString Verb s = s fixString Mono s = latexMonoFilter s diff --git a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs index e63667b0..2990e1e4 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs @@ -73,7 +73,8 @@ parHtmlMarkup qual insertAnchors ppId = Markup { markupMathDisplay = \mathjax -> toHtml ("\\[" ++ mathjax ++ "\\]"), markupProperty = pre . toHtml, markupExample = examplesToHtml, - markupHeader = \(Header l t) -> makeHeader l t + markupHeader = \(Header l t) -> makeHeader l t, + markupTable = \(Table h r) -> makeTable h r } where makeHeader :: Int -> Html -> Html @@ -85,6 +86,22 @@ parHtmlMarkup qual insertAnchors ppId = Markup { makeHeader 6 mkup = h6 mkup makeHeader l _ = error $ "Somehow got a header level `" ++ show l ++ "' in DocMarkup!" + makeTable :: [TableRow Html] -> [TableRow Html] -> Html + makeTable hs bs = table (concatHtml (hs' ++ bs')) + where + hs' | null hs = [] + | otherwise = [thead (concatHtml (map (makeTableRow th) hs))] + + bs' = [tbody (concatHtml (map (makeTableRow td) bs))] + + makeTableRow :: (Html -> Html) -> TableRow Html -> Html + makeTableRow thr (TableRow cs) = tr (concatHtml (map (makeTableCell thr) cs)) + + makeTableCell :: (Html -> Html) -> TableCell Html -> Html + makeTableCell thr (TableCell i j c) = thr c ! (i' ++ j') + where + i' = if i == 1 then [] else [ colspan i ] + j' = if j == 1 then [] else [ rowspan j ] examplesToHtml l = pre (concatHtml $ map exampleToHtml l) ! [theclass "screen"] diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 75b2f223..311301ee 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -144,6 +144,7 @@ rename dflags gre = rn DocEmpty -> pure (DocEmpty) DocString str -> pure (DocString str) DocHeader (Header l t) -> DocHeader . Header l <$> rn t + DocTable t -> DocTable <$> traverse rn t -- | Wrap an identifier that's out of scope (i.e. wasn't found in -- 'GlobalReaderEnv' during 'rename') in an appropriate doc. Currently diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 76bcb4ae..bbd8d04e 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -459,6 +459,32 @@ instance Binary a => Binary (Header a) where t <- get bh return (Header l t) +instance Binary a => Binary (Table a) where + put_ bh (Table h b) = do + put_ bh h + put_ bh b + get bh = do + h <- get bh + b <- get bh + return (Table h b) + +instance Binary a => Binary (TableRow a) where + put_ bh (TableRow cs) = put_ bh cs + get bh = do + cs <- get bh + return (TableRow cs) + +instance Binary a => Binary (TableCell a) where + put_ bh (TableCell i j c) = do + put_ bh i + put_ bh j + put_ bh c + get bh = do + i <- get bh + j <- get bh + c <- get bh + return (TableCell i j c) + instance Binary Meta where put_ bh Meta { _version = v } = put_ bh v get bh = (\v -> Meta { _version = v }) <$> get bh @@ -542,6 +568,9 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where put_ bh (DocMathDisplay x) = do putByte bh 22 put_ bh x + put_ bh (DocTable x) = do + putByte bh 23 + put_ bh x get bh = do h <- getByte bh @@ -615,6 +644,9 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where 22 -> do x <- get bh return (DocMathDisplay x) + 23 -> do + x <- get bh + return (DocTable x) _ -> error "invalid binary data found in the interface file" diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index b4cdc343..725606b2 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -454,6 +454,7 @@ instance (NFData a, NFData mod) DocProperty a -> a `deepseq` () DocExamples a -> a `deepseq` () DocHeader a -> a `deepseq` () + DocTable a -> a `deepseq` () #if !MIN_VERSION_ghc(8,0,2) -- These were added to GHC itself in 8.0.2 @@ -474,6 +475,14 @@ instance NFData Picture where instance NFData Example where rnf (Example a b) = a `deepseq` b `deepseq` () +instance NFData id => NFData (Table id) where + rnf (Table h b) = h `deepseq` b `deepseq` () + +instance NFData id => NFData (TableRow id) where + rnf (TableRow cs) = cs `deepseq` () + +instance NFData id => NFData (TableCell id) where + rnf (TableCell i j c) = i `deepseq` j `deepseq` c `deepseq` () exampleToString :: Example -> String exampleToString (Example expression result) = diff --git a/haddock-library/fixtures/Fixtures.hs b/haddock-library/fixtures/Fixtures.hs index 3707e0a8..f75ff664 100644 --- a/haddock-library/fixtures/Fixtures.hs +++ b/haddock-library/fixtures/Fixtures.hs @@ -151,3 +151,12 @@ instance ToExpr Picture deriving instance Generic Example instance ToExpr Example + +deriving instance Generic (Table id) +instance ToExpr id => ToExpr (Table id) + +deriving instance Generic (TableRow id) +instance ToExpr id => ToExpr (TableRow id) + +deriving instance Generic (TableCell id) +instance ToExpr id => ToExpr (TableCell id) diff --git a/haddock-library/fixtures/examples/table-simple.input b/haddock-library/fixtures/examples/table-simple.input new file mode 100644 index 00000000..d9c49f87 --- /dev/null +++ b/haddock-library/fixtures/examples/table-simple.input @@ -0,0 +1,7 @@ ++------+--------------+------------------------------------------+ +| code | message | description | ++======+==============+==========================================+ +| 200 | @OK@ | operation successful | ++------+--------------+------------------------------------------+ +| 204 | @No Content@ | operation successful, no body returned | ++------+--------------+------------------------------------------+ diff --git a/haddock-library/fixtures/examples/table-simple.parsed b/haddock-library/fixtures/examples/table-simple.parsed new file mode 100644 index 00000000..b5e62453 --- /dev/null +++ b/haddock-library/fixtures/examples/table-simple.parsed @@ -0,0 +1,52 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " 200 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMonospaced (DocString "OK")) + (DocString " ")), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " operation successful ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " 204 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMonospaced (DocString "No Content")) + (DocString " ")), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " operation successful, no body returned ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " code ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " message ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " description ", + tableCellRowspan = 1}]]} diff --git a/haddock-library/fixtures/examples/table1.input b/haddock-library/fixtures/examples/table1.input new file mode 100644 index 00000000..a007020c --- /dev/null +++ b/haddock-library/fixtures/examples/table1.input @@ -0,0 +1,12 @@ ++------------------------+------------+----------+----------+ +| Header row, column 1 | Header 2 | Header 3 | Header 4 | +| (header rows optional) | | | | ++========================+============+==========+==========+ +| body row 1, column 1 | column 2 | column 3 | column 4 | ++------------------------+------------+----------+----------+ +| body row 2 | Cells may span columns. | ++------------------------+------------+---------------------+ +| body row 3 | Cells may | \[ | ++------------------------+ span rows. | f(n) = \sum_{i=1} | +| body row 4 | | \] | ++------------------------+------------+---------------------+ diff --git a/haddock-library/fixtures/examples/table1.parsed b/haddock-library/fixtures/examples/table1.parsed new file mode 100644 index 00000000..2fa58fd8 --- /dev/null +++ b/haddock-library/fixtures/examples/table1.parsed @@ -0,0 +1,81 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 1, column 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocString " Cells may span columns. ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" Cells may \n", + " span rows. \n", + " "]), + tableCellRowspan = 2}, + TableCell + {tableCellColspan = 2, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMathDisplay + (concat + [" \n", + " f(n) = \\sum_{i=1} \n", + " "])) + (DocString " ")), + tableCellRowspan = 2}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 4 ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" Header row, column 1 \n", + " (header rows optional) "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 2 \n", " "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 3 \n", " "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 4 \n", " "]), + tableCellRowspan = 1}]]} diff --git a/haddock-library/fixtures/examples/table2.input b/haddock-library/fixtures/examples/table2.input new file mode 100644 index 00000000..aa5d0862 --- /dev/null +++ b/haddock-library/fixtures/examples/table2.input @@ -0,0 +1,7 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++--------------+----------+-----------+-----------+ +| row 2 | | ++--------------+----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table2.parsed b/haddock-library/fixtures/examples/table2.parsed new file mode 100644 index 00000000..e3dbf0b4 --- /dev/null +++ b/haddock-library/fixtures/examples/table2.parsed @@ -0,0 +1,46 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocString " ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = []} diff --git a/haddock-library/fixtures/examples/table3.input b/haddock-library/fixtures/examples/table3.input new file mode 100644 index 00000000..a6ca84ca --- /dev/null +++ b/haddock-library/fixtures/examples/table3.input @@ -0,0 +1,7 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++--------------+----------+-----------+-----------+ +| row 2 | Use the command ``ls | more``. | ++--------------+----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table3.parsed b/haddock-library/fixtures/examples/table3.parsed new file mode 100644 index 00000000..cabff9cb --- /dev/null +++ b/haddock-library/fixtures/examples/table3.parsed @@ -0,0 +1,50 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 2, + tableCellContents = DocString " Use the command ``ls ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " more``. ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = []} diff --git a/haddock-library/fixtures/examples/table4.input b/haddock-library/fixtures/examples/table4.input new file mode 100644 index 00000000..2c5611c8 --- /dev/null +++ b/haddock-library/fixtures/examples/table4.input @@ -0,0 +1,17 @@ +Single outer cell: + ++-------------+ +| outer | +| | ++-------+ | +| inner | | ++-------+-----+ + +Broken (only inner cell is rendered): + ++-------+-----+ +| inner | | ++-------+ | +| | +| outer | ++-------------+ diff --git a/haddock-library/fixtures/examples/table4.parsed b/haddock-library/fixtures/examples/table4.parsed new file mode 100644 index 00000000..cfdd6f0f --- /dev/null +++ b/haddock-library/fixtures/examples/table4.parsed @@ -0,0 +1,26 @@ +DocAppend + (DocParagraph (DocString "Single outer cell:")) + (DocAppend + (DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" outer \n", + " \n", + "-------+ \n", + " inner | "]), + tableCellRowspan = 1}]], + tableHeaderRows = []}) + (DocAppend + (DocParagraph (DocString "Broken (only inner cell is rendered):")) + (DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " inner ", + tableCellRowspan = 1}]], + tableHeaderRows = []}))) diff --git a/haddock-library/fixtures/examples/table5.input b/haddock-library/fixtures/examples/table5.input new file mode 100644 index 00000000..7cf26512 --- /dev/null +++ b/haddock-library/fixtures/examples/table5.input @@ -0,0 +1,8 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++==============+==========+===========+===========+ +| row 2 | Use the command @ls | more@. | +| | | +| +----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table5.parsed b/haddock-library/fixtures/examples/table5.parsed new file mode 100644 index 00000000..9a547ad3 --- /dev/null +++ b/haddock-library/fixtures/examples/table5.parsed @@ -0,0 +1,53 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" row 2 \n", + " \n", + " \n", + " row 3 "]), + tableCellRowspan = 2}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocAppend + (DocString " Use the command ") + (DocAppend + (DocMonospaced (DocString "ls | more")) + (DocString + (concat + [". \n", + " "]))), + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}]]} diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 2707a928..62df724b 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -18,12 +18,14 @@ build-type: Simple cabal-version: >= 2.0 extra-source-files: CHANGES.md + library default-language: Haskell2010 build-depends: base >= 4.5 && < 4.12 , bytestring >= 0.9.2.1 && < 0.11 + , containers >= 0.4.2.1 && < 0.6 , transformers >= 0.3.0 && < 0.6 -- internal sub-lib @@ -108,6 +110,7 @@ test-suite spec build-depends: base-compat ^>= 0.9.3 + , containers >= 0.4.2.1 && < 0.6 , transformers >= 0.3.0 && < 0.6 , hspec ^>= 2.4.4 , QuickCheck ^>= 2.10 diff --git a/haddock-library/src/Documentation/Haddock/Markup.hs b/haddock-library/src/Documentation/Haddock/Markup.hs index 1bf6c084..da8edcd4 100644 --- a/haddock-library/src/Documentation/Haddock/Markup.hs +++ b/haddock-library/src/Documentation/Haddock/Markup.hs @@ -30,6 +30,7 @@ markup m (DocMathDisplay mathjax) = markupMathDisplay m mathjax markup m (DocProperty p) = markupProperty m p markup m (DocExamples e) = markupExample m e markup m (DocHeader (Header l t)) = markupHeader m (Header l (markup m t)) +markup m (DocTable (Table h b)) = markupTable m (Table (map (fmap (markup m)) h) (map (fmap (markup m)) b)) markupPair :: DocMarkupH mod id a -> (DocH mod id, DocH mod id) -> (a, a) markupPair m (a,b) = (markup m a, markup m b) @@ -59,5 +60,6 @@ idMarkup = Markup { markupMathDisplay = DocMathDisplay, markupProperty = DocProperty, markupExample = DocExamples, - markupHeader = DocHeader + markupHeader = DocHeader, + markupTable = DocTable } diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index 4ea87db7..a1349c95 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -24,15 +24,17 @@ import Control.Arrow (first) import Control.Monad import qualified Data.ByteString.Char8 as BS import Data.Char (chr, isAsciiUpper) -import Data.List (stripPrefix, intercalate, unfoldr) -import Data.Maybe (fromMaybe) +import Data.List (stripPrefix, intercalate, unfoldr, elemIndex) +import Data.Maybe (fromMaybe, mapMaybe) import Data.Monoid +import qualified Data.Set as Set import Documentation.Haddock.Doc import Documentation.Haddock.Parser.Monad hiding (take, endOfLine) import Documentation.Haddock.Parser.Util import Documentation.Haddock.Types import Documentation.Haddock.Utf8 import Prelude hiding (takeWhile) +import qualified Prelude as P -- $setup -- >>> :set -XOverloadedStrings @@ -79,6 +81,7 @@ overIdentifier f d = g d g (DocProperty x) = DocProperty x g (DocExamples x) = DocExamples x g (DocHeader (Header l x)) = DocHeader . Header l $ g x + g (DocTable (Table h b)) = DocTable (Table (map (fmap g) h) (map (fmap g) b)) parse :: Parser a -> BS.ByteString -> (ParserState, a) parse p = either err id . parseOnly (p <* endOfInput) @@ -251,7 +254,7 @@ markdownImage = fromHyperlink <$> ("!" *> linkParser) -- | Paragraph parser, called by 'parseParas'. paragraph :: Parser (DocH mod Identifier) -paragraph = examples <|> do +paragraph = examples <|> table <|> do indent <- takeIndent choice [ since @@ -266,6 +269,193 @@ paragraph = examples <|> do , docParagraph <$> textParagraph ] +-- | Provides support for grid tables. +-- +-- Tables are composed by an optional header and body. The header is composed by +-- a single row. The body is composed by a non-empty list of rows. +-- +-- Example table with header: +-- +-- > +----------+----------+ +-- > | /32bit/ | 64bit | +-- > +==========+==========+ +-- > | 0x0000 | @0x0000@ | +-- > +----------+----------+ +-- +-- Algorithms loosely follows ideas in +-- http://docutils.sourceforge.net/docutils/parsers/rst/tableparser.py +-- +table :: Parser (DocH mod Identifier) +table = do + -- first we parse the first row, which determines the width of the table + firstRow <- parseFirstRow + let len = BS.length firstRow + + -- then we parse all consequtive rows starting and ending with + or |, + -- of the width `len`. + restRows <- many (parseRestRows len) + + -- Now we gathered the table block, the next step is to split the block + -- into cells. + DocTable <$> tableStepTwo len (firstRow : restRows) + where + parseFirstRow :: Parser BS.ByteString + parseFirstRow = do + skipHorizontalSpace + -- upper-left corner is + + c <- char '+' + cs <- many1 (char '-' <|> char '+') + + -- upper right corner is + too + guard (last cs == '+') + + -- trailing space + skipHorizontalSpace + _ <- char '\n' + + return (BS.cons c $ BS.pack cs) + + parseRestRows :: Int -> Parser BS.ByteString + parseRestRows l = do + skipHorizontalSpace + + c <- char '|' <|> char '+' + bs <- scan (l - 2) predicate + c2 <- char '|' <|> char '+' + + -- trailing space + skipHorizontalSpace + _ <- char '\n' + + return (BS.cons c (BS.snoc bs c2)) + where + predicate n c + | n <= 0 = Nothing + | c == '\n' = Nothing + | otherwise = Just (n - 1) + +-- Second step searchs for row of '+' and '=' characters, records it's index +-- and changes to '=' to '-'. +tableStepTwo + :: Int -- ^ width + -> [BS.ByteString] -- ^ rows + -> Parser (Table (DocH mod Identifier)) +tableStepTwo width = go 0 [] where + go _ left [] = tableStepThree width (reverse left) Nothing + go n left (r : rs) + | BS.all (`elem` ['+', '=']) r = + tableStepThree width (reverse left ++ r' : rs) (Just n) + | otherwise = + go (n + 1) (r : left) rs + where + r' = BS.map (\c -> if c == '=' then '-' else c) r + +-- Third step recognises cells in the table area, returning a list of TC, cells. +tableStepThree + :: Int -- ^ width + -> [BS.ByteString] -- ^ rows + -> Maybe Int -- ^ index of header separator + -> Parser (Table (DocH mod Identifier)) +tableStepThree width rs hdrIndex = do + cells <- loop (Set.singleton (0, 0)) + tableStepFour rs hdrIndex cells + where + height = length rs + + loop :: Set.Set (Int, Int) -> Parser [TC] + loop queue = case Set.minView queue of + Nothing -> return [] + Just ((y, x), queue') + | y + 1 >= height || x + 1 >= width -> loop queue' + | otherwise -> case scanRight x y of + Nothing -> loop queue' + Just (x2, y2) -> do + let tc = TC y x y2 x2 + fmap (tc :) $ loop $ queue' `Set.union` Set.fromList + [(y, x2), (y2, x), (y2, x2)] + + -- scan right looking for +, then try scan down + -- + -- do we need to record + saw on the way left and down? + scanRight :: Int -> Int -> Maybe (Int, Int) + scanRight x y = go (x + 1) where + bs = rs !! y + go x' | x' >= width = fail "overflow right " + | BS.index bs x' == '+' = scanDown x y x' <|> go (x' + 1) + | BS.index bs x' == '-' = go (x' + 1) + | otherwise = fail $ "not a border (right) " ++ show (x,y,x') + + -- scan down looking for + + scanDown :: Int -> Int -> Int -> Maybe (Int, Int) + scanDown x y x2 = go (y + 1) where + go y' | y' >= height = fail "overflow down" + | BS.index (rs !! y') x2 == '+' = scanLeft x y x2 y' <|> go (y' + 1) + | BS.index (rs !! y') x2 == '|' = go (y' + 1) + | otherwise = fail $ "not a border (down) " ++ show (x,y,x2,y') + + -- check that at y2 x..x2 characters are '+' or '-' + scanLeft :: Int -> Int -> Int -> Int -> Maybe (Int, Int) + scanLeft x y x2 y2 + | all (\x' -> BS.index bs x' `elem` ['+', '-']) [x..x2] = scanUp x y x2 y2 + | otherwise = fail $ "not a border (left) " ++ show (x,y,x2,y2) + where + bs = rs !! y2 + + -- check that at y2 x..x2 characters are '+' or '-' + scanUp :: Int -> Int -> Int -> Int -> Maybe (Int, Int) + scanUp x y x2 y2 + | all (\y' -> BS.index (rs !! y') x `elem` ['+', '|']) [y..y2] = return (x2, y2) + | otherwise = fail $ "not a border (up) " ++ show (x,y,x2,y2) + +-- | table cell: top left bottom right +data TC = TC !Int !Int !Int !Int + deriving Show + +tcXS :: TC -> [Int] +tcXS (TC _ x _ x2) = [x, x2] + +tcYS :: TC -> [Int] +tcYS (TC y _ y2 _) = [y, y2] + +-- | Fourth step. Given the locations of cells, forms 'Table' structure. +tableStepFour :: [BS.ByteString] -> Maybe Int -> [TC] -> Parser (Table (DocH mod Identifier)) +tableStepFour rs hdrIndex cells = case hdrIndex of + Nothing -> return $ Table [] rowsDoc + Just i -> case elemIndex i yTabStops of + Nothing -> return $ Table [] rowsDoc + Just i' -> return $ uncurry Table $ splitAt i' rowsDoc + where + xTabStops = sortNub $ concatMap tcXS cells + yTabStops = sortNub $ concatMap tcYS cells + + sortNub :: Ord a => [a] -> [a] + sortNub = Set.toList . Set.fromList + + init' :: [a] -> [a] + init' [] = [] + init' [_] = [] + init' (x : xs) = x : init' xs + + rowsDoc = (fmap . fmap) parseStringBS rows + + rows = map makeRow (init' yTabStops) + where + makeRow y = TableRow $ mapMaybe (makeCell y) cells + makeCell y (TC y' x y2 x2) + | y /= y' = Nothing + | otherwise = Just $ TableCell xts yts (extract (x + 1) (y + 1) (x2 - 1) (y2 - 1)) + where + xts = length $ P.takeWhile (< x2) $ dropWhile (< x) xTabStops + yts = length $ P.takeWhile (< y2) $ dropWhile (< y) yTabStops + + -- extract cell contents given boundaries + extract :: Int -> Int -> Int -> Int -> BS.ByteString + extract x y x2 y2 = BS.intercalate "\n" + [ BS.take (x2 - x + 1) $ BS.drop x $ rs !! y' + | y' <- [y .. y2] + ] + +-- | Parse \@since annotations. since :: Parser (DocH mod a) since = ("@since " *> version <* skipHorizontalSpace <* endOfLine) >>= setSince >> return DocEmpty where diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs index 1e76c631..96653864 100644 --- a/haddock-library/src/Documentation/Haddock/Types.hs +++ b/haddock-library/src/Documentation/Haddock/Types.hs @@ -81,6 +81,21 @@ data Example = Example , exampleResult :: [String] } deriving (Eq, Show) +data TableCell id = TableCell + { tableCellColspan :: Int + , tableCellRowspan :: Int + , tableCellContents :: id + } deriving (Eq, Show, Functor, Foldable, Traversable) + +newtype TableRow id = TableRow + { tableRowCells :: [TableCell id] + } deriving (Eq, Show, Functor, Foldable, Traversable) + +data Table id = Table + { tableHeaderRows :: [TableRow id] + , tableBodyRows :: [TableRow id] + } deriving (Eq, Show, Functor, Foldable, Traversable) + data DocH mod id = DocEmpty | DocAppend (DocH mod id) (DocH mod id) @@ -105,6 +120,7 @@ data DocH mod id | DocProperty String | DocExamples [Example] | DocHeader (Header (DocH mod id)) + | DocTable (Table (DocH mod id)) deriving (Eq, Show, Functor, Foldable, Traversable) #if MIN_VERSION_base(4,8,0) @@ -132,6 +148,7 @@ instance Bifunctor DocH where bimap _ _ (DocProperty s) = DocProperty s bimap _ _ (DocExamples examples) = DocExamples examples bimap f g (DocHeader (Header level title)) = DocHeader (Header level (bimap f g title)) + bimap f g (DocTable (Table header body)) = DocTable (Table (map (fmap (bimap f g)) header) (map (fmap (bimap f g)) body)) #endif #if MIN_VERSION_base(4,10,0) @@ -149,6 +166,7 @@ instance Bifoldable DocH where bifoldr f g z (DocDefList docs) = foldr (\(l, r) acc -> bifoldr f g (bifoldr f g acc l) r) z docs bifoldr f g z (DocCodeBlock doc) = bifoldr f g z doc bifoldr f g z (DocHeader (Header _ title)) = bifoldr f g z title + bifoldr f g z (DocTable (Table header body)) = foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) (foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) z body) header bifoldr _ _ z _ = z instance Bitraversable DocH where @@ -175,6 +193,7 @@ instance Bitraversable DocH where bitraverse _ _ (DocProperty s) = pure (DocProperty s) bitraverse _ _ (DocExamples examples) = pure (DocExamples examples) bitraverse f g (DocHeader (Header level title)) = (DocHeader . Header level) <$> bitraverse f g title + bitraverse f g (DocTable (Table header body)) = (\h b -> DocTable (Table h b)) <$> traverse (traverse (bitraverse f g)) header <*> traverse (traverse (bitraverse f g)) body #endif -- | 'DocMarkupH' is a set of instructions for marking up documentation. @@ -209,4 +228,5 @@ data DocMarkupH mod id a = Markup , markupProperty :: String -> a , markupExample :: [Example] -> a , markupHeader :: Header a -> a + , markupTable :: Table a -> a } diff --git a/html-test/ref/Table.html b/html-test/ref/Table.html new file mode 100644 index 00000000..959f18b2 --- /dev/null +++ b/html-test/ref/Table.html @@ -0,0 +1,238 @@ +Table
Safe HaskellSafe

Table

Description

This tests the table markup

Synopsis

Documentation

tableWithHeader :: a -> a #

Table with header.

code message description
200 OK operation successful
204 No Content operation successful, no body returned

tableWithoutHeader :: a -> a #

Table without header.

200 OK operation successful
204 No Content operation successful, no body returned
404 Not Found resource not found

fancyTable :: a -> a #

Fancy table.

Header row, column 1 + (header rows optional) Header 2 + Header 3 + Header 4 +
body row 1, column 1 column 2 column 3 column 4
tableWithHeader Cells may span columns.
body row 3 Cells may + span rows. + \[ + f(n) = \sum_{i=1} + \]
body row 4
\ No newline at end of file diff --git a/html-test/src/Table.hs b/html-test/src/Table.hs new file mode 100644 index 00000000..2cf0c662 --- /dev/null +++ b/html-test/src/Table.hs @@ -0,0 +1,47 @@ +-- | This tests the table markup +module Table + ( tableWithHeader + , tableWithoutHeader + , fancyTable + ) where + +-- | Table with header. +-- +-- +------+--------------+------------------------------------------+ +-- | code | message | description | +-- +======+==============+==========================================+ +-- | 200 | @OK@ | operation successful | +-- +------+--------------+------------------------------------------+ +-- | 204 | @No Content@ | operation successful, no body returned | +-- +------+--------------+------------------------------------------+ +tableWithHeader :: a -> a +tableWithHeader a = a + +-- | Table without header. +-- +-- +------+--------------+------------------------------------------+ +-- | 200 | @OK@ | operation successful | +-- +------+--------------+------------------------------------------+ +-- | 204 | @No Content@ | operation successful, no body returned | +-- +------+--------------+------------------------------------------+ +-- | 404 | @Not Found@ | resource not found | +-- +------+--------------+------------------------------------------+ +tableWithoutHeader :: a -> a +tableWithoutHeader a = a + +-- | Fancy table. +-- +-- +------------------------+------------+----------+----------+ +-- | Header row, column 1 | Header 2 | Header 3 | Header 4 | +-- | (header rows optional) | | | | +-- +========================+============+==========+==========+ +-- | body row 1, column 1 | column 2 | column 3 | column 4 | +-- +------------------------+------------+----------+----------+ +-- | 'tableWithHeader' | Cells may span columns. | +-- +------------------------+------------+---------------------+ +-- | body row 3 | Cells may | \[ | +-- +------------------------+ span rows. | f(n) = \sum_{i=1} | +-- | body row 4 | | \] | +-- +------------------------+------------+---------------------+ +fancyTable :: a -> a +fancyTable x = x -- cgit v1.2.3 From 6ed6c110c874a746b002aca148192c3cbc819d7f Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Fri, 5 Jan 2018 09:59:59 -0800 Subject: Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for #679 and #710 --- haddock-api/src/Haddock/Interface/Specialize.hs | 20 +-- html-test/ref/Bug679.html | 196 ++++++++++++++++++++++++ html-test/src/Bug679.hs | 24 +++ 3 files changed, 230 insertions(+), 10 deletions(-) create mode 100644 html-test/ref/Bug679.html create mode 100644 html-test/src/Bug679.hs (limited to 'html-test') diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index 6d2888d3..bb27f10c 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -31,23 +31,23 @@ import qualified Data.Set as Set specialize :: forall name a. (Ord (IdP name), DataId name, NamedThing (IdP name)) => Data a => [(IdP name, HsType name)] -> a -> a -specialize specs = go +specialize specs = go spec_map0 where - go :: forall x. Data x => x -> x - go = everywhereButType @name $ mkT $ sugar . strip_kind_sig . specialize_ty_var + go :: forall x. Data x => Map name (HsType name) -> x -> x + go spec_map = everywhereButType @name $ mkT $ sugar . strip_kind_sig . specialize_ty_var spec_map strip_kind_sig :: HsType name -> HsType name strip_kind_sig (HsKindSig (L _ t) _) = t strip_kind_sig typ = typ - specialize_ty_var :: HsType name -> HsType name - specialize_ty_var (HsTyVar _ (L _ name')) + specialize_ty_var :: Map name (HsType name) -> HsType name -> HsType name + specialize_ty_var spec_map (HsTyVar _ (L _ name')) | Just t <- Map.lookup name' spec_map = t - specialize_ty_var typ = typ - -- This is a tricky recursive definition that is guaranteed to terminate - -- because a type binder cannot be instantiated with a type that depends - -- on that binder. i.e. @a -> Maybe a@ is invalid - spec_map = Map.fromList [ (n, go t) | (n, t) <- specs] + specialize_ty_var _ typ = typ + + -- This is a tricky recursive definition. By adding in the specializations + -- one by one, we should avoid infinite loops. + spec_map0 = foldr (\(n,t) acc -> Map.insert n (go acc t) acc) mempty specs -- | Instantiate given binders with corresponding types. diff --git a/html-test/ref/Bug679.html b/html-test/ref/Bug679.html new file mode 100644 index 00000000..ddec7a12 --- /dev/null +++ b/html-test/ref/Bug679.html @@ -0,0 +1,196 @@ +Bug679
Safe HaskellNone

Bug679

Documentation

data Bar a #

Constructors

Bar
Instances
Foo (Bar a) #
Instance details

Methods

foo :: Bar a -> Bar a #

class Foo a where #

Minimal complete definition

foo

Methods

foo :: a -> a #

Instances
Foo (Bar a) #
Instance details

Methods

foo :: Bar a -> Bar a #

\ No newline at end of file diff --git a/html-test/src/Bug679.hs b/html-test/src/Bug679.hs new file mode 100644 index 00000000..dba194c4 --- /dev/null +++ b/html-test/src/Bug679.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE TemplateHaskell #-} + +module Bug679 where + +import Language.Haskell.TH + +data Bar a = Bar + +$(do + a <- newName "a" + + let classN = mkName "Foo" + let methodN = mkName "foo" + + methodTy <- [t| $(varT a) -> $(varT a) |] + let cla = ClassD [] classN [PlainTV a] [] [SigD methodN methodTy] + + -- Note that we are /reusing/ the same type variable 'a' as in the class + instanceHead <- [t| $(conT classN) (Bar $(varT a)) |] + idCall <- [e| id |] + let ins = InstanceD Nothing [] instanceHead [FunD methodN [Clause [] (NormalB idCall) []]] + + pure [cla,ins]) + -- cgit v1.2.3 From 69b98a99ce4de93ea0e6082bd11edb3baaf2fa6e Mon Sep 17 00:00:00 2001 From: Alexander Biehl Date: Fri, 2 Mar 2018 15:43:21 +0100 Subject: Make testsuite work with haddock-1.19.0 release (#766) --- html-test/Main.hs | 15 + html-test/ref/A.html | 12 +- html-test/ref/Bug1.html | 2 +- html-test/ref/Bug2.html | 2 +- html-test/ref/Bug253.html | 2 +- html-test/ref/Bug26.html | 4 +- html-test/ref/Bug280.html | 2 +- html-test/ref/Bug294.html | 154 +++++- html-test/ref/Bug298.html | 8 +- html-test/ref/Bug3.html | 4 +- html-test/ref/Bug310.html | 16 +- html-test/ref/Bug387.html | 8 +- html-test/ref/Bug4.html | 4 +- html-test/ref/Bug546.html | 12 +- html-test/ref/Bug548.html | 244 +++++----- html-test/ref/Bug6.html | 78 ++-- html-test/ref/Bug613.html | 26 +- html-test/ref/Bug647.html | 2 +- html-test/ref/Bug679.html | 18 +- html-test/ref/Bug7.html | 12 +- html-test/ref/Bug8.html | 16 +- html-test/ref/Bug85.html | 16 +- html-test/ref/BugDeprecated.html | 24 +- html-test/ref/BugExportHeadings.html | 24 +- html-test/ref/Bugs.html | 2 +- html-test/ref/BundledPatterns.html | 64 +-- html-test/ref/BundledPatterns2.html | 98 ++-- html-test/ref/ConstructorPatternExport.html | 18 +- html-test/ref/DeprecatedClass.html | 4 +- html-test/ref/DeprecatedFunction.html | 10 +- html-test/ref/DeprecatedFunction2.html | 4 +- html-test/ref/DeprecatedFunction3.html | 4 +- html-test/ref/DeprecatedModule.html | 2 +- html-test/ref/DeprecatedModule2.html | 2 +- html-test/ref/DeprecatedNewtype.html | 8 +- html-test/ref/DeprecatedReExport.html | 6 +- html-test/ref/DeprecatedRecord.html | 8 +- html-test/ref/DeprecatedTypeFamily.html | 16 +- html-test/ref/DeprecatedTypeSynonym.html | 8 +- html-test/ref/Examples.html | 10 +- html-test/ref/FunArgs.html | 8 +- html-test/ref/GADTRecords.html | 34 +- html-test/ref/Hash.html | 80 ++-- html-test/ref/HiddenInstances.html | 50 +- html-test/ref/HiddenInstancesB.html | 8 +- html-test/ref/Hyperlinks.html | 4 +- html-test/ref/ImplicitParams.html | 14 +- html-test/ref/Instances.html | 566 +++++++++++------------ html-test/ref/Math.html | 4 +- html-test/ref/Minimal.html | 24 +- html-test/ref/ModuleWithWarning.html | 2 +- html-test/ref/NoLayout.html | 6 +- html-test/ref/Operators.html | 40 +- html-test/ref/OrphanInstances.html | 18 +- html-test/ref/OrphanInstancesClass.html | 52 ++- html-test/ref/OrphanInstancesType.html | 50 +- html-test/ref/PatternSyns.html | 72 +-- html-test/ref/PromotedTypes.html | 40 +- html-test/ref/Properties.html | 10 +- html-test/ref/QuasiExpr.html | 54 +-- html-test/ref/QuasiQuote.html | 2 +- html-test/ref/SpuriousSuperclassConstraints.html | 48 +- html-test/ref/Table.html | 2 +- html-test/ref/Test.html | 424 ++++++++++------- html-test/ref/Threaded.html | 4 +- html-test/ref/Ticket112.html | 2 +- html-test/ref/Ticket61.html | 2 +- html-test/ref/Ticket75.html | 6 +- html-test/ref/TitledPicture.html | 12 +- html-test/ref/TypeFamilies.html | 544 +++++++++------------- html-test/ref/TypeFamilies2.html | 50 +- html-test/ref/TypeOperators.html | 14 +- html-test/ref/Unicode.html | 4 +- html-test/ref/Visible.html | 4 +- 74 files changed, 1687 insertions(+), 1536 deletions(-) (limited to 'html-test') diff --git a/html-test/Main.hs b/html-test/Main.hs index 67dbeec6..d65a5087 100755 --- a/html-test/Main.hs +++ b/html-test/Main.hs @@ -47,7 +47,22 @@ stripIfRequired mdl = preserveLinksModules :: [String] preserveLinksModules = ["Bug253"] +ingoredTests :: [FilePath] +ingoredTests = + [ + -- Currently some declarations are exported twice + -- we need a reliable way to deduplicate here. + -- Happens since PR #688. + "B" + + -- ignore-exports flag broke with PR #688. We use + -- the Avails calculated by GHC now. Probably + -- requires a change to GHC to "ignore" a modules + -- export list reliably. + , "IgnoreExports" + ] checkIgnore :: FilePath -> Bool +checkIgnore file | takeBaseName file `elem` ingoredTests = True checkIgnore file@(c:_) | takeExtension file == ".html" && isUpper c = False checkIgnore _ = True diff --git a/html-test/ref/A.html b/html-test/ref/A.html index 1fbfb371..e4802966 100644 --- a/html-test/ref/A.html +++ b/html-test/ref/A.html @@ -54,13 +54,13 @@ >
  • other :: :: Int
  • test2 :: :: Bool
  • reExport :: :: Int
  • other :: :: Int #

    test2 :: :: Bool #

    reExport :: :: Int #

    We should have different anchors for constructors and types/classes. This hyperlink should point to the type constructor by default: T.

    x :: :: A #This link should generate #v anchor: fakeFakeFake

    Minimal complete definition

    c_f

    C ()

    x :: [ :: [Char] # data DP A

    data TP TP A

    problemField :: TO :: TO A -> -> A #

    problemField' :: DO :: DO A -> -> A #

    gadtField :: ({..} -> GADT :: ({..} -> GADT A) -> ) -> A #

    data family TP t :: * #

    Instances
    data TP A #
    Instance details
    data TP A = ProblemCtor A

    data family DP t :: t :: * # data DP A

    data family TO' t :: * #

    Instances
    data TO' a #
    Instance details
    data TO' a = PolyCtor
  • test1 :: :: Int
  • test2 :: :: Int
  • test1 :: :: Int #

    test2 :: :: Int #

  • foo :: :: Int
  • foo :: :: Int #

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

    compile :: :: String -> -> String #newtype WrappedArrow (a :: (a :: * -> -> * -> -> *) b c # Generic1 * ( (WrappedArrow a b) a b :: * -> *)

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

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

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

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

    fmap :: (a0 -> b0) -> :: (a0 -> b0) -> WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b b0 #

    (<$) :: a0 -> :: a0 -> WrappedArrow a b b0 -> a b b0 -> WrappedArrow a b a0 # Arrow a => a => Applicative ( (WrappedArrow a b)

    pure :: a0 -> :: a0 -> WrappedArrow a b a0 #

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

    liftA2 :: (a0 -> b0 -> c) -> :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b b0 -> a b b0 -> WrappedArrow a b c #

    (*>) :: :: WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b b0 -> a b b0 -> WrappedArrow a b b0 #

    (<*) :: :: WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b b0 -> a b b0 -> WrappedArrow a b a0 # ( (ArrowZero a, a, ArrowPlus a) => a) => Alternative ( (WrappedArrow a b)

    empty :: :: WrappedArrow a b a0 #

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

    some :: :: WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b [a0] #

    many :: :: WrappedArrow a b a0 -> a b a0 -> WrappedArrow a b [a0] # Generic ( (WrappedArrow a b c)

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

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

    to :: :: Rep ( (WrappedArrow a b c) x -> a b c) x -> WrappedArrow a b c # type Rep1 * ( (WrappedArrow a b) a b :: * -> *)

    type Rep ( (WrappedArrow a b c)A = A Int
  • B = B {}
  • Int
  • b :: B -> Int
  • data
  • c1 :: :: Int
  • c2 :: :: Int
  • D = D Int Int
  • E = E Int
  • A IntB Int

    Fields

    b :: B -> Int #

    datac1 :: :: Int

    c2 :: :: Int
    D Int IntE Int

    Minimal complete definition

    fmap

    Functor ( (Either a)

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

    fmap :: (a1 -> b) -> :: (a1 -> b) -> ThreeVars a0 a a1 -> a0 a a1 -> ThreeVars a0 a b # Functor ( (ThreeVars a0 a)

    fmap :: (a1 -> b) -> :: (a1 -> b) -> ThreeVars a0 a a1 -> a0 a a1 -> ThreeVars a0 a b #

    Minimal complete definition

    f

    Foo ( (Bar a)

    foo :: :: Bar a -> a -> Bar a #

    Minimal complete definition

    foo

    Foo ( (Bar a)

    foo :: :: Bar a -> a -> Bar a # Bar Foo Foo Bar Foo Foo Type ( (Typ, [, [Typ])TFree ( (Typ, [, [Typ])

    (-->) :: p1 -> p2 -> :: p1 -> p2 -> Typ infix 9

    (--->) :: :: Foldable t0 => t0 t -> t0 => t0 t -> Typ -> -> Typ infix 9data Foo :: ( :: (* -> -> *) -> ) -> * -> -> * whereBar :: f x -> :: f x -> Foo f (f x)data Baz :: :: * whereBaz' :: :: BazQuux :: :: Qux

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

    bar :: :: Int #

    baz :: :: Int #

    one :: :: Int #

    two :: :: Int #

    three :: :: Int #

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

    bar :: :: Int #

    baz :: :: Int #

    one :: :: Int #

    two :: :: Int #

    three :: :: Int #A a (a -> a (a -> Int)data Vec :: :: Nat -> -> * -> -> * where

  • Nil :: :: Vec 0 a
  • pattern (:>) :: a -> :: a -> Vec n a -> n a -> Vec (n (n + 1) a
  • data RTree :: :: Nat -> -> * -> -> * wherepattern LR :: a -> :: a -> RTree 0 a
  • pattern BR :: :: RTree d a -> d a -> RTree d a -> d a -> RTree (d (d + 1) a
  • data Vec :: :: Nat -> -> * -> -> * whereLists with their length encoded in their type
  • Vector elements have an subscript starting from 0 and ending at length - 1Nil :: :: Vec 0 apattern (:>) :: a -> :: a -> Vec n a -> n a -> Vec (n (n + 1) a infixr 5data RTree :: :: Nat -> -> * -> -> * wherepattern LR :: a -> :: a -> RTree 0 apattern BR :: :: RTree d a -> d a -> RTree d a -> d a -> RTree (d (d + 1) adata Vec :: :: Nat -> -> * -> -> * wherepattern Empty :: (:>) :: a -> Vec 0 a
  • n a -> Vec (n + 1) a
  • pattern (:>) :: a -> Vec n a -> Empty :: Vec (n + 1) a
  • 0 a
  • data RTree :: :: Nat -> -> * -> -> * wherepattern LR :: a -> :: a -> RTree 0 a
  • pattern BR :: :: RTree d a -> d a -> RTree d a -> d a -> RTree (d (d + 1) a
  • data Vec :: :: Nat -> -> * -> -> * whereLists with their length encoded in their type
  • Vector elements have an subscript starting from 0 and ending at length - 1Bundled Patterns

    pattern Empty :: Vec 0 a
    pattern (:>) :: a -> :: a -> Vec n a -> n a -> Vec (n (n + 1) a infixr 5
    pattern Empty :: Vec 0 a
    data RTree :: :: Nat -> -> * -> -> * wherepattern LR :: a -> :: a -> RTree 0 apattern BR :: :: RTree d a -> d a -> RTree d a -> d a -> RTree (d (d + 1) apattern FooCons :: :: String -> a -> Foo a #pattern MyRecCons :: :: Bool -> -> Int -> MyRec #pattern (:+) :: :: String -> a -> MyInfix a #pattern BlubCons :: () => :: () => Show b => b -> Blub #MyGADTCons :: () => forall a. a. Eq a => a -> a => a -> Int -> MyGADT ( -> MyGADT (Maybe String) #

    Minimal complete definition

    foo

    Minimal complete definition

    bar

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

    Deprecated: use bar instead

    bar :: :: Int #

  • foo :: :: Int
  • foo :: :: Int #

  • foo :: :: Integer
  • foo :: :: Integer #

    foo :: :: Int #

    foo :: :: Int #SomeNewType = SomeNewTypeConst String

  • SomeOtherNewType = SomeOtherNewTypeConst String
  • SomeNewTypeConst StringSomeOtherNewTypeConst String
  • foo :: :: Int
  • foo :: :: Int #

    Deprecated: use bar instead

  • fooName :: :: String
  • fooValue :: :: Int
  • fooName :: :: String
    fooValue :: :: Int
    data family SomeTypeFamily k :: k :: * -> -> *
  • data family SomeOtherTypeFamily k :: k :: * -> -> *
  • data family SomeTypeFamily k :: k :: * -> -> * #data family SomeOtherTypeFamily k :: k :: * -> -> * #type TypeSyn = = String
  • type OtherTypeSyn = = String
  • type TypeSyn = = String #type OtherTypeSyn = = String #
  • fib :: :: Integer -> -> Integer
  • fib :: :: Integer -> -> Integer #

    Fibonacci number of given Integer.

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

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

    class Foo f => Bar

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

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

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

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

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

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

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

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

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

    bar :: [(a, a)] -> [ :: [(a, a)] -> [Bool] -> (a, a) # Foo f => f => Bar ( (Either a) (f a)

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

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

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

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

    bar :: (a, b, (a, b, a)) -> (a, b, :: (a, b, (a, b, a)) -> (a, b, Bool) -> (a, b, a) # Bar ( (Quux a c) ( a c) (Quux a b c)

    bar :: :: Quux a c ( a c (Quux a b c) -> a b c) -> Quux a c a c Bool -> -> Quux a b c #

    bar' :: :: Quux a c ( a c (Quux a c ( a c (Quux a b c)) -> a b c)) -> Quux a c ( a c (Quux a c ( a c (Quux a c b0)) #

    bar0 :: ( :: (Quux a c ( a c (Quux a b c), a b c), Quux a c ( a c (Quux a b c)) -> ( a b c)) -> (Quux a c b0, a c b0, Quux a c c0) #

    bar1 :: ( :: (Quux a c ( a c (Quux a b c), a b c), Quux a c ( a c (Quux a b c)) -> ( a b c)) -> (Quux a c b0, a c b0, Quux a c c0) # Baz [c] Baz (a -> b) Baz (a, b, c) Baz ( (Quux a b c)

    baz :: :: Quux a b c -> (forall a0. a0 -> a0) -> (b0, forall c0. c0 -> c0. c0 -> Quux a b c) -> (b0, c1) #baz' :: b0 -> (forall b1. b1 -> b1. b1 -> Quux a b c) -> (forall b2. b2 -> b2. b2 -> Quux a b c) -> [(b0, a b c) -> [(b0, Quux a b c)] #forall b1. (forall b2. b2 -> b2. b2 -> Quux a b c) -> c0) -> forall Baz (a, [b], b, a) Foo ( (Quux a b)

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

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

    bar :: :: Quux a c ( a c (Quux a b c) -> a b c) -> Quux a c a c Bool -> -> Quux a b c #

    bar' :: :: Quux a c ( a c (Quux a c ( a c (Quux a b c)) -> a b c)) -> Quux a c ( a c (Quux a c ( a c (Quux a c b0)) #

    bar0 :: ( :: (Quux a c ( a c (Quux a b c), a b c), Quux a c ( a c (Quux a b c)) -> ( a b c)) -> (Quux a c b0, a c b0, Quux a c c0) #

    bar1 :: ( :: (Quux a c ( a c (Quux a b c), a b c), Quux a c ( a c (Quux a b c)) -> ( a b c)) -> (Quux a c b0, a c b0, Quux a c c0) # Baz ( (Quux a b c)

    baz :: :: Quux a b c -> (forall a0. a0 -> a0) -> (b0, forall c0. c0 -> c0. c0 -> Quux a b c) -> (b0, c1) #baz' :: b0 -> (forall b1. b1 -> b1. b1 -> Quux a b c) -> (forall b2. b2 -> b2. b2 -> Quux a b c) -> [(b0, a b c) -> [(b0, Quux a b c)] #forall b1. (forall b2. b2 -> b2. b2 -> Quux a b c) -> c0) -> forall data Thud Int ( (Quux a [a] c)

    data Thud Int ( (Quux a [a] c)

    norf :: :: Plugh a c b -> a -> (a -> c) -> b # Norf Int Bool

    type Plugh Int c c Bool :: :: * #

    data Thud Int c :: c :: * #

    norf :: :: Plugh Int c c Bool -> -> Int -> ( -> (Int -> c) -> -> c) -> Bool # Norf [a] [b]

    type Plugh [a] c [b] :: [a] c [b] :: * #

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

    norf :: :: Plugh [a] c [b] -> [a] -> ([a] -> c) -> [b] #

  • f :: :: Integer
  • f :: :: Integer #

    Minimal complete definition

    foo, , bar | | bar, , bat | | foo, , bat | | fooBarBat

    Minimal complete definition

    x, , y

    Minimal complete definition

    aaa, , bbb

    Minimal complete definition

    ccc, ddd

    foo :: :: Int #

  • g :: :: Int
  • g :: :: Int #

    the function g

    Foo
  • (:<->) :: a -> b -> a :: a -> b -> a <-> b
  • type a <>< b :: b :: *
  • type (>-<) a b = a a b = a <-> b
  • :: :: Ord a
    => => Int
    -> -> Bool:: forall (b :: ()). d ~ (b :: ()). d ~ ()
  • C1 :: :: H1 a b
  • C2 :: :: Ord a => [a] -> a => [a] -> H1 a a
  • C3 :: {..} -> :: {..} -> H1 Int Int
  • C4 :: {..} -> :: {..} -> H1 Int a
  • C1 :: :: H1 a bC2 :: :: Ord a => [a] -> a => [a] -> H1 a aC3 :: {..} -> :: {..} -> H1 Int Intfield :: :: Int
    C4 :: {..} -> :: {..} -> H1 Int a
  • new :: ( :: (Eq key, key, Hash key) => key) => Int -> -> IO ( (HashTable key val)
  • insert :: ( :: (Eq key, key, Hash key) => key -> val -> key) => key -> val -> IO ()
  • lookup :: :: Hash key => key -> key => key -> IO ( (Maybe val)
  • key should be an instance of Eq.

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

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

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

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

    Minimal complete definition

    hash

    hash :: a -> :: a -> Int #hashes the value of type a into an Int

    Hash Float

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

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

    hash :: (a, b) -> :: (a, b) -> Int # VisibleClass Int VisibleClass VisibleData Num VisibleData

    (+) :: :: VisibleData -> -> VisibleData -> -> VisibleData #

    (-) :: :: VisibleData -> -> VisibleData -> -> VisibleData #

    (*) :: :: VisibleData -> -> VisibleData -> -> VisibleData #

    negate :: :: VisibleData -> -> VisibleData #

    abs :: :: VisibleData -> -> VisibleData #

    signum :: :: VisibleData -> -> VisibleData #

    fromInteger :: :: Integer -> -> VisibleData # VisibleClass VisibleData Foo Bar Foo Bar

  • foo :: :: Int
  • foo :: :: Int #

    c :: (?x :: :: (?x :: X) => ) => X #

    d :: (?x :: :: (?x :: X, ?y :: , ?y :: X) => () => (X, , X) #

    f :: ((?x :: :: ((?x :: X) => a) -> a # Foo ( ((<~~) a)

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

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

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

    foo' :: f (f a) -> :: f (f a) -> Int -> f (f -> f (f Int) # Foo []

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

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

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

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

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

    foo' :: :: Either a ( a (Either a a0) -> a a0) -> Int -> -> Either a ( a (Either a a Int) # ( (Eq a, a, Foo f) => f) => Foo ( ((,) (f a))

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

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

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

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

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

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

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

    foo' :: :: Quux a b ( a b (Quux a b a0) -> a b a0) -> Int -> -> Quux a b ( a b (Quux a b a b Int) # Foo ((->) LiftedRep LiftedRep a) ((->) a :: * -> *) #

    Foo `Bar` Foo infixl 3
    Foo :- Foo infixr 5(:<->) :: a -> b -> a :: a -> b -> a <-> b infixr 6

    Minimal complete definition

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

    type a <>< b :: b :: * infixl 2type (>-<) a b = a a b = a <-> b infixl 6
    Synopsis

      Documentation

      Orphan instances

      AClass AType

      aClass :: :: AType -> -> Int #

      Minimal complete definition

      aClass

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

      Instances
      AClass AType #

      This is an orphan instance.

      Instance details

      Methods

      aClass :: AType -> Int #

      AType Int
      Instances
      AClass AType #

      This is an orphan instance.

      Instance details

      Methods

      aClass :: AType -> Int #

      Foo :: forall x. x -> x. x -> FooType x
    • Bar :: forall x. x -> x. x -> FooType ( (FooType x)
    • (:<->) :: forall x x1. x -> x1 -> ( x x1. x -> x1 -> (FooType x, x, FooType ( (FooType x1))
    • data BlubType = = Show x => BlubCtorBlub :: () => forall x. x. Show x => x -> x => x -> BlubType
    • data (a :: (a :: *) ><E :: forall k a (b :: k). (><) k a b
    • k a (b :: k). a >< b
    • pattern PatWithExplicitSig :: :: Eq somex => somex -> somex => somex -> FooType somex
    • Foo :: forall x. x -> x. x -> FooType x #

      Pattern synonym for Foo x

      Bar :: forall x. x -> x. x -> FooType ( (FooType x) #

      Pattern synonym for Bar x

      (:<->) :: forall x x1. x -> x1 -> ( x x1. x -> x1 -> (FooType x, x, FooType ( (FooType x1)) #

      Pattern synonym for (:<->)

      This module illustrates & tests most of the features of Haddock. Testing references from the description: T, f, g, visible.

    • = A Int ( (Maybe Float)
    • | B ( (T a b, a b, T Int Float)
    • p :: :: Int
    • r, s :: :: Int
    • t :: T1 -> :: T1 -> T2 Int Int -> -> T3 Bool Bool -> -> T4 Float Float -> -> T5 () ()
    • u, v :: :: Int
    • s1 :: :: Int
    • s2 :: :: Int
    • s3 :: :: Int
    • }
    • p :: R -> Int
    • q :: R -> forall a. a -> a
    • u :: R -> Int
    • class D a => C
    • a :: :: C a => a => IO a
    • f :: :: C a => a -> a => a -> Int
    • g :: :: Int -> -> IO CInt
    • hidden :: :: Int -> -> Int
    • Ex a
    • Show x => BlubCtorBlub :: () => forall x. x. Show x => x -> x => x -> BlubType #

      Pattern synonym for Blub x

      data (a :: (a :: *) ><

      Doc for (><)

      E :: forall k a (b :: k). (><) k a b k a (b :: k). a >< b #

      Pattern for Empty

      pattern PatWithExplicitSig :: :: Eq somex => somex -> somex => somex -> FooType somex #
      ((RevList a) :>data Pattern :: [ :: [*] -> ] -> * whereNil :: :: Pattern '[]Cons :: :: Maybe h -> h -> Pattern t -> t -> Pattern (h ': t)data RevPattern :: :: RevList * -> -> * whereRevNil :: :: RevPattern RNilRevCons :: :: Maybe h -> h -> RevPattern t -> t -> RevPattern (t (t :> h)data Tuple :: ( :: (*, , *) -> ) -> * whereTuple :: a -> b -> :: a -> b -> Tuple '(a, b)
    • fib :: :: Integer -> -> Integer
    • fib :: :: Integer -> -> Integer #

      Fibonacci number of given Integer.

      IntExpr IntegerAntiIntExpr StringBinopExpr BinOp Expr ExprAntiExpr String Show Expr

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

      show :: :: Expr -> -> String #

      showList :: [ :: [Expr] -> ] -> ShowS # Show BinOp

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

      show :: :: BinOp -> -> String #

      showList :: [ :: [BinOp] -> ] -> ShowS #

      eval :: :: Expr -> -> Integer #

      parseExprExp :: :: String -> Q Exp #

      val :: :: Integer #data SomeType (f :: (f :: * -> -> *) a # Functor ( (SomeType f)

      fmap :: (a -> b) -> :: (a -> b) -> SomeType f a -> f a -> SomeType f b #

      (<$) :: a -> :: a -> SomeType f b -> f b -> SomeType f a # Applicative f => f => Applicative ( (SomeType f)

      pure :: a -> :: a -> SomeType f a #

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

      liftA2 :: (a -> b -> c) -> :: (a -> b -> c) -> SomeType f a -> f a -> SomeType f b -> f b -> SomeType f c #

      (*>) :: :: SomeType f a -> f a -> SomeType f b -> f b -> SomeType f b #

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

      tableWithHeader A Int ( (Maybe Float)

      This comment describes the A constructor

      B ( (T a b, a b, T Int Float)

      This comment describes the B constructor

      documents A3

      documents B3

      This is the doc for A4

      This is the doc for B4

      This is the doc for C4

      this is the n3 field

      The N7 constructor

      This is the documentation for the R record, which has four fields, p, q, r, and s.

      This is the C1 record constructor, with the following fields:

      p :: :: Int

      This comment applies to the p field

      This comment applies to the q field

      r, s :: :: Int

      This comment applies to both r and s

      This is the C2 record constructor, also with some fields:

      t :: T1 -> :: T1 -> T2 Int Int -> -> T3 Bool Bool -> -> T4 Float Float -> -> T5 () ()
      u, v :: :: Int

      This is the C3 record constructor

      s1 :: :: Int

      The s1 record selector

      s2 :: :: Int

      The s2 record selector

      s3 :: :: Int

      The s3 record selector

      test that we can export record selectors on their own:

      p :: R -> Int #

      This comment applies to the p field

      q :: R -> forall a. a -> a #

      This comment applies to the q field

      u :: R -> Int #

      Class declarations

      class D a => CThis comment applies to the previous declaration (the C class)

      Minimal complete definition

      a, , b

      a :: :: IO a #

      this is a description of the a method

      this is a description of the b method

      Minimal complete definition

      d, , e

      d :: :: T a b # D Float

      d :: :: T Float b #

      e :: ( :: (Float, , Float) # D Int

      d :: :: T Int b #

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

      Minimal complete definition

      ff

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

      this is a description of the a method

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

      In a comment string we can refer to identifiers in scope with single quotes like this: T, and we can refer to modules by @@ -1801,7 +1877,7 @@ using double quotes:

           This is a block of code, which can include other markup: R
      @@ -1821,9 +1897,9 @@ using double quotes: 

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

      hidden :: :: Int -> -> Int #
      C b => Ex1
      C a => Ex3
      :: :: T () ()

      This argument has type T

      -> -> T2 Int Int
      -> (-> (T3 Bool Bool -> -> T4 Float Float)
      -> -> T5 () ()
      -> -> IO ()
      :: (:: (Int, , Int, , Float)
      -> -> Int

      returns an Int

      Instance details

      Defined in Bug7

      Instance details

      Defined in Hash

      Methods

      Instance details

      Defined in Hash

      Methods

      Instance details

      Defined in Hash

      Methods

      Instance details

      Defined in HiddenInstances

      Instance details

      Defined in HiddenInstances

      Instance details

      Defined in HiddenInstances

      Methods

      Instance details

      Defined in HiddenInstances

      Instance details

      Defined in HiddenInstancesA

      Instance details

      Defined in HiddenInstancesA

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      Methods

      Instance details

      Defined in Instances

      data
      Instance details

      Defined in Instances

      Associated Types

      Instance details

      Defined in Instances

      Associated Types

      Instance details

      Methods

      Instance details

      Defined in OrphanInstances

      Methods

      Instance details

      Defined in OrphanInstances

      Methods

      Instance details

      Defined in QuasiExpr

      Methods

      Instance details

      Defined in QuasiExpr

      Methods

      Instance details

      Defined in SpuriousSuperclassConstraints

      Methods

      Instance details

      Defined in SpuriousSuperclassConstraints

      Methods

      Instance details

      Defined in Test

      Methods

      Instance details

      Defined in Test

      Methods

      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies

      Associated Types

      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      Associated Types

      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      data
      Instance details

      Defined in TypeFamilies

      Associated Types

      Instance details

      Defined in TypeFamilies

      Associated Types

      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies

      Instance details

      Defined in TypeFamilies2

      data
      Instance details

      Defined in TypeFamilies2

      type
      Instance details

      Defined in TypeFamilies2

      type
      Instance details

      Defined in TypeFamilies

      type
      Instance details

      Defined in TypeFamilies2

      data
      Instance details

      Defined in TypeFamilies

      data Date: Tue, 3 Apr 2018 16:35:50 +0200 Subject: Travis: Build with ghc-8.4.2 (#793) --- .travis.yml | 4 ++-- haddock-api/haddock-api.cabal | 2 +- html-test/ref/Bug310.html | 4 ++-- html-test/ref/Bug548.html | 8 ++++---- 4 files changed, 9 insertions(+), 9 deletions(-) (limited to 'html-test') diff --git a/.travis.yml b/.travis.yml index 4afc18f4..39135739 100644 --- a/.travis.yml +++ b/.travis.yml @@ -26,9 +26,9 @@ before_cache: matrix: include: - - compiler: "ghc-8.4.1" + - compiler: "ghc-8.4.2" # env: TEST=--disable-tests BENCH=--disable-benchmarks - addons: {apt: {packages: [ghc-ppa-tools,cabal-install-head,ghc-8.4.1], sources: [hvr-ghc]}} + 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]}} diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index f5803e09..acb4d9e4 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -169,7 +169,7 @@ test-suite spec build-depends: Cabal ^>= 2.0.0 , ghc ^>= 8.4 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.5.0 + , haddock-library ^>= 1.6.0 , xhtml ^>= 3000.2.2 , hspec ^>= 2.4.4 , QuickCheck ^>= 2.11 diff --git a/html-test/ref/Bug310.html b/html-test/ref/Bug310.html index e8ce24f8..47da5387 100644 --- a/html-test/ref/Bug310.html +++ b/html-test/ref/Bug310.html @@ -89,7 +89,7 @@ >Addition of type-level naturals.

      Since: 4.7.0.0Since: base-4.7.0.0

      \ No newline at end of file +> diff --git a/html-test/ref/Bug548.html b/html-test/ref/Bug548.html index 29216433..b32f8c8c 100644 --- a/html-test/ref/Bug548.html +++ b/html-test/ref/Bug548.html @@ -183,7 +183,7 @@ >
      \ No newline at end of file +> -- cgit v1.2.3 From 622c45d56e0ccb11e3b8b0832654cb30c8369ba8 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(-) (limited to 'html-test') diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index d4f6db0e..819c9aa6 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -523,9 +523,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 @@ -585,12 +585,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: Wed, 13 Jun 2018 23:49:52 +0200 Subject: html-test: Accept output --- html-test/ref/A.html | 24 +- html-test/ref/Bug280.html | 4 +- html-test/ref/Bug294.html | 16 +- html-test/ref/Bug3.html | 8 +- html-test/ref/Bug310.html | 46 +-- html-test/ref/Bug387.html | 16 +- html-test/ref/Bug4.html | 8 +- html-test/ref/Bug546.html | 20 +- html-test/ref/Bug548.html | 256 +++------------ html-test/ref/Bug6.html | 60 +--- html-test/ref/Bug613.html | 10 +- html-test/ref/Bug8.html | 4 +- html-test/ref/Bug85.html | 14 +- html-test/ref/BugDeprecated.html | 48 +-- html-test/ref/BugExportHeadings.html | 48 +-- html-test/ref/Bugs.html | 4 +- html-test/ref/BundledPatterns.html | 36 +- html-test/ref/BundledPatterns2.html | 36 +- html-test/ref/ConstructorPatternExport.html | 30 +- 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/DeprecatedTypeFamily.html | 24 +- html-test/ref/DeprecatedTypeSynonym.html | 16 +- html-test/ref/Examples.html | 16 +- html-test/ref/FunArgs.html | 16 +- html-test/ref/GADTRecords.html | 54 ++- 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/Operators.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 | 32 +- html-test/ref/PromotedTypes.html | 28 +- html-test/ref/Properties.html | 16 +- html-test/ref/QuasiExpr.html | 80 +---- html-test/ref/QuasiQuote.html | 4 +- html-test/ref/SpuriousSuperclassConstraints.html | 44 +-- 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 | 120 +++---- html-test/ref/Unicode.html | 8 +- html-test/ref/Visible.html | 6 +- 59 files changed, 460 insertions(+), 1722 deletions(-) (limited to 'html-test') diff --git a/html-test/ref/A.html b/html-test/ref/A.html index e4802966..c6965abc 100644 --- a/html-test/ref/A.html +++ b/html-test/ref/A.html @@ -54,15 +54,11 @@ >
                    • other :: Int
                    • :: Int
                    • test2 :: Bool
                    • :: Bool
                    • data
                    • reExport :: Int
                    • :: Int

                      other :: Int :: Int #

                      test2 :: Bool :: Bool #

                      reExport :: Int :: Int #

                      gadtField :: ({..} -> GADT :: GADT A) -> -> A #data family TP t :: * t :: * #

                      data family DP t :: * t :: * #

                      data family TO' t :: * t :: * #

                    • 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

                      +> \ No newline at end of file diff --git a/html-test/ref/Bug387.html b/html-test/ref/Bug387.html index ba2f5c91..da1b1ee5 100644 --- a/html-test/ref/Bug387.html +++ b/html-test/ref/Bug387.html @@ -60,15 +60,11 @@ >
                    • 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 #

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

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

                      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) Arrow a => Applicative ( Arrow a => Applicative (WrappedArrow a b) (ArrowZero a, ArrowPlus a) => Alternative ( (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) Generic ( Generic (WrappedArrow a b c)

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

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

                      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

                      typeRep1 ( Rep1 (WrappedArrow a b :: * -> *) a b :: * -> *)
                      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 :: * -> *) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (a b))))typeRep ( Rep (WrappedArrow a b c)
                      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)))) +> \ No newline at end of file diff --git a/html-test/ref/Bug6.html b/html-test/ref/Bug6.html index 15842547..27f73d64 100644 --- a/html-test/ref/Bug6.html +++ b/html-test/ref/Bug6.html @@ -58,9 +58,7 @@ >A = AInt 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
                    • Int Int Intb :: B -> Int -> Int #

                      c1 :: Int :: Int
                      c2 :: Int :: Int
                      Int Int IntFunctor (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 -> Typdata Foo :: (* -> *) -> * -> * :: (* -> *) -> * -> * where #data Baz :: * :: * where #

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

                      foo :: Int :: Int #

                      a (a -> Int)dataVec :: Nat -> * -> * :: Nat -> * -> * where

                      foo :: Int :: Int #

                    • foo :: Integer
                    • :: Integer

                      foo :: Integer :: Integer #

                      foo :: Int :: Int #

                      SomeNewType = SomeNewTypeConst String String
                    • newtypeSomeOtherNewType = SomeOtherNewTypeConst String
                    • String
                      String String
                      :: :: R
                      -> -> N1 ()
                      -> -> IO Intdata Bat* X
                      :: :: Float
                      -> -> IO Float

                      f' :: :: Int #

                      a function with a prime can be referred to as f' @@ -2283,7 +2359,7 @@ is at the beginning of the line).

                      withType :: :: Int #

                    • f :: :: Integer
                    • f :: :: Integer #

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

                      Minimal complete definition

                      f

                    • f :: :: Int
                    • f :: :: Int #

                      type (<>) * Y a = a
                      <> (a :: *) = atype(<>)* X a<> (a :: *)#
                      type (<>) * X a = <> (a :: *) = X
                      (><) X XX >< XXX data Bar W
                      data Bar W = BarX type Foo W type Foo W type Foo X data Bar W
                      data Bar W = BarX data Bar Y

                      biO :: (g :: (g `O` f) a #

                      x :: (a :: (a :-: a) a) <=> (a (a `Op` a) => a #

                      y :: (a :: (a <=> a, (a a, (a `Op` a) a) <=> a) => a #

                    • x :: :: Int
                    • x :: :: Int #

                      visible :: :: Int -> -> Int # Date: Mon, 5 Feb 2018 18:14:32 -0800 Subject: Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes #458. --- haddock-library/haddock-library.cabal | 2 +- .../src/Documentation/Haddock/Parser.hs | 34 ++++----- .../src/Documentation/Haddock/Parser/Monad.hs | 25 ++++++- html-test/ref/Bug458.html | 80 ++++++++++++++++++++++ html-test/src/Bug458.hs | 6 ++ 5 files changed, 122 insertions(+), 25 deletions(-) create mode 100644 html-test/ref/Bug458.html create mode 100644 html-test/src/Bug458.hs (limited to 'html-test') diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 3d069f07..d7935747 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -64,13 +64,13 @@ library attoparsec exposed-modules: Data.Attoparsec.ByteString Data.Attoparsec.ByteString.Char8 + Data.Attoparsec.Combinator other-modules: Data.Attoparsec Data.Attoparsec.ByteString.Buffer Data.Attoparsec.ByteString.FastSet Data.Attoparsec.ByteString.Internal - Data.Attoparsec.Combinator Data.Attoparsec.Internal Data.Attoparsec.Internal.Fhthagn Data.Attoparsec.Internal.Types diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index a1349c95..82515ab4 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -23,7 +23,7 @@ import Control.Applicative import Control.Arrow (first) import Control.Monad import qualified Data.ByteString.Char8 as BS -import Data.Char (chr, isAsciiUpper) +import Data.Char (chr, isUpper, isAlpha, isAlphaNum) import Data.List (stripPrefix, intercalate, unfoldr, elemIndex) import Data.Maybe (fromMaybe, mapMaybe) import Data.Monoid @@ -35,6 +35,7 @@ import Documentation.Haddock.Types import Documentation.Haddock.Utf8 import Prelude hiding (takeWhile) import qualified Prelude as P +import Text.Read.Lex (isSymbolChar) -- $setup -- >>> :set -XOverloadedStrings @@ -205,20 +206,19 @@ monospace :: Parser (DocH mod Identifier) monospace = DocMonospaced . parseStringBS <$> ("@" *> takeWhile1_ (/= '@') <* "@") --- | Module names: we try our reasonable best to only allow valid --- Haskell module names, with caveat about not matching on technically --- valid unicode symbols. +-- | Module names. +-- +-- Note that we allow '#' and '\' to support anchors (old style anchors are of +-- the form "SomeModule\#anchor"). moduleName :: Parser (DocH mod a) moduleName = DocModule <$> (char '"' *> modid <* char '"') where modid = intercalate "." <$> conid `sepBy1` "." conid = (:) - <$> satisfy isAsciiUpper - -- NOTE: According to Haskell 2010 we should actually only - -- accept {small | large | digit | ' } here. But as we can't - -- match on unicode characters, this is currently not possible. - -- Note that we allow ‘#’ to suport anchors. - <*> (decodeUtf8 <$> takeWhile (notInClass " .&[{}(=*)+]!|@/;,^?\"\n")) + <$> satisfyUnicode (\c -> isAlpha c && isUpper c) + <*> many (satisfyUnicode conChar <|> char '\\' <|> char '#') + + conChar c = isAlphaNum c || c == '_' -- | Picture parser, surrounded by \<\< and \>\>. It's possible to specify -- a title for the picture. @@ -760,26 +760,16 @@ autoUrl = mkLink <$> url parseValid :: Parser String parseValid = p some where - idChar = - satisfy (\c -> isAlpha_ascii c - || isDigit c - -- N.B. '-' is placed first otherwise attoparsec thinks - -- it belongs to a character class - || inClass "-_.!#$%&*+/<=>?@\\|~:^" c) + idChar = satisfyUnicode (\c -> isAlphaNum c || isSymbolChar c || c == '_') p p' = do - vs' <- p' $ utf8String "⋆" <|> return <$> idChar - let vs = concat vs' + vs <- p' idChar c <- peekChar' case c of '`' -> return vs '\'' -> (\x -> vs ++ "'" ++ x) <$> ("'" *> p many') <|> return vs _ -> fail "outofvalid" --- | Parses UTF8 strings from ByteString streams. -utf8String :: String -> Parser String -utf8String x = decodeUtf8 <$> string (encodeUtf8 x) - -- | Parses identifiers with help of 'parseValid'. Asks GHC for -- 'String' from the string it deems valid. identifier :: Parser (DocH mod Identifier) diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs index 3f7d60f8..3430ef8a 100644 --- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs +++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, BangPatterns #-} module Documentation.Haddock.Parser.Monad ( module Documentation.Haddock.Parser.Monad , Attoparsec.isDigit @@ -31,9 +31,10 @@ module Documentation.Haddock.Parser.Monad ( import Control.Applicative import Control.Monad import Data.String -import Data.ByteString (ByteString) +import Data.ByteString (ByteString, length) import qualified Data.ByteString.Lazy as LB import qualified Data.Attoparsec.ByteString.Char8 as Attoparsec +import qualified Data.Attoparsec.Combinator as Attoparsec import Control.Monad.Trans.State import qualified Control.Monad.Trans.Class as Trans import Data.Word @@ -41,6 +42,7 @@ import Data.Bits import Data.Tuple import Documentation.Haddock.Types (Version) +import Documentation.Haddock.Utf8 (encodeUtf8, decodeUtf8) newtype ParserState = ParserState { parserStateSince :: Maybe Version @@ -73,6 +75,25 @@ char = lift . Attoparsec.char char8 :: Char -> Parser Word8 char8 = lift . Attoparsec.char8 +-- | Peek a unicode character and return the number of bytes that it took up +peekUnicode :: Parser (Char, Int) +peekUnicode = lift $ Attoparsec.lookAhead $ do + + -- attoparsec's take fails on shorter inputs rather than truncate + bs <- Attoparsec.choice (map Attoparsec.take [4,3,2,1]) + + let !c = head . decodeUtf8 $ bs + !n = Data.ByteString.length . encodeUtf8 $ [c] + pure (c, fromIntegral n) + +-- | Like 'satisfy', but consuming a unicode character +satisfyUnicode :: (Char -> Bool) -> Parser Char +satisfyUnicode predicate = do + (c,n) <- peekUnicode + if predicate c + then Documentation.Haddock.Parser.Monad.take n *> pure c + else fail "satsifyUnicode" + anyChar :: Parser Char anyChar = lift Attoparsec.anyChar diff --git a/html-test/ref/Bug458.html b/html-test/ref/Bug458.html new file mode 100644 index 00000000..aa99e719 --- /dev/null +++ b/html-test/ref/Bug458.html @@ -0,0 +1,80 @@ +Bug458

                      Bar X = = X
                      Bar y = y = Y type (<>) X XXX <> XX type (<>) * Y a <> (a :: *) #
                      Safe HaskellSafe

                      Bug458

                      Synopsis

                      Documentation

                      (⊆) :: () -> () -> () #

                      See the defn of .

                      \ No newline at end of file diff --git a/html-test/src/Bug458.hs b/html-test/src/Bug458.hs new file mode 100644 index 00000000..6a3ac9a4 --- /dev/null +++ b/html-test/src/Bug458.hs @@ -0,0 +1,6 @@ +module Bug458 where + +-- | See the defn of @'⊆'@. +(⊆) :: () -> () -> () +_ ⊆ _ = () + -- cgit v1.2.3 From 1ac2f9569242f6cb074ba6e577285a4c33ae1197 Mon Sep 17 00:00:00 2001 From: alexbiehl Date: Fri, 2 Mar 2018 15:47:04 +0100 Subject: fix test --- html-test/ref/Bug458.html | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) (limited to 'html-test') diff --git a/html-test/ref/Bug458.html b/html-test/ref/Bug458.html index aa99e719..1a174f94 100644 --- a/html-test/ref/Bug458.html +++ b/html-test/ref/Bug458.html @@ -63,11 +63,7 @@ >

                      See the defn of '⊆'.

                      Date: Fri, 2 Mar 2018 16:20:19 +0100 Subject: haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. --- haddock-test/src/Test/Haddock/Config.hs | 13 +++++++++++-- html-test/ref/QuasiExpr.html | 10 ++++++++-- html-test/ref/TH.html | 6 +++++- html-test/ref/Threaded_TH.html | 12 ++++++++++-- 4 files changed, 34 insertions(+), 7 deletions(-) (limited to 'html-test') diff --git a/haddock-test/src/Test/Haddock/Config.hs b/haddock-test/src/Test/Haddock/Config.hs index 2d16fa63..8b395b6c 100644 --- a/haddock-test/src/Test/Haddock/Config.hs +++ b/haddock-test/src/Test/Haddock/Config.hs @@ -197,6 +197,7 @@ loadConfig ccfg dcfg flags files = do [ pure ["--no-warnings"] , pure ["--odir=" ++ dcfgOutDir dcfg] , pure ["--optghc=-w"] + , pure ["--optghc=-hide-all-packages"] , pure $ flagsHaddockOptions flags , baseDependencies ghcPath ] @@ -244,13 +245,21 @@ baseDependencies ghcPath = do #else pkgIndex <- getInstalledPackages normal [GlobalPackageDB] cfg #endif - mapM (getDependency pkgIndex) ["base", "process", "ghc-prim"] + let + pkgs = + [ "array" + , "base" + , "ghc-prim" + , "process" + , "template-haskell" + ] + concat `fmap` mapM (getDependency pkgIndex) pkgs where getDependency pkgIndex name = case ifaces pkgIndex name of [] -> do hPutStrLn stderr $ "Couldn't find base test dependency: " ++ name exitFailure - (ifArg:_) -> pure ifArg + (ifArg:_) -> pure ["--optghc=-package" ++ name, ifArg] ifaces pkgIndex name = do pkg <- join $ snd <$> lookupPackageName pkgIndex (mkPackageName name) iface <$> haddockInterfaces pkg <*> haddockHTMLs pkg diff --git a/html-test/ref/QuasiExpr.html b/html-test/ref/QuasiExpr.html index 66e31ec7..062ebb8d 100644 --- a/html-test/ref/QuasiExpr.html +++ b/html-test/ref/QuasiExpr.html @@ -301,7 +301,9 @@ >

                      expr :: QuasiQuoter :: QuasiQuoter #

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

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

                    • forkTH :: Q Exp
                    • :: Q Exp

                      forkTH :: Q Exp :: Q Exp #

                      Date: Fri, 2 Mar 2018 17:50:38 +0100 Subject: Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. --- html-test/ref/Bug458.html | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) (limited to 'html-test') diff --git a/html-test/ref/Bug458.html b/html-test/ref/Bug458.html index 1a174f94..aa99e719 100644 --- a/html-test/ref/Bug458.html +++ b/html-test/ref/Bug458.html @@ -63,7 +63,11 @@ >

                      See the defn of '⊆'.

                      Date: Fri, 2 Mar 2018 18:16:50 +0100 Subject: Fix Bug548 for real --- html-test/ref/Bug458.html | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'html-test') diff --git a/html-test/ref/Bug458.html b/html-test/ref/Bug458.html index aa99e719..f716d7d6 100644 --- a/html-test/ref/Bug458.html +++ b/html-test/ref/Bug458.html @@ -64,7 +64,7 @@ >

                      See the defn of Date: Wed, 21 Mar 2018 01:16:57 -0700 Subject: Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests --- haddock-api/src/Haddock/Backends/LaTeX.hs | 4 +- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 18 ++- haddock-api/src/Haddock/Backends/Xhtml/Layout.hs | 12 +- .../src/Haddock/Interface/AttachInstances.hs | 18 ++- haddock-api/src/Haddock/Interface/Rename.hs | 4 +- haddock-api/src/Haddock/Types.hs | 2 +- html-test/ref/Bug26.html | 6 +- html-test/ref/Bug294.html | 30 +++- html-test/ref/Bug548.html | 42 ++++- html-test/ref/Bug613.html | 18 ++- html-test/ref/Bug679.html | 12 +- html-test/ref/Bug7.html | 8 + html-test/ref/Hash.html | 18 ++- html-test/ref/HiddenInstances.html | 18 ++- html-test/ref/HiddenInstancesB.html | 8 + html-test/ref/Instances.html | 156 +++++++++++++++--- html-test/ref/OrphanInstances.html | 4 +- html-test/ref/OrphanInstancesClass.html | 6 +- html-test/ref/OrphanInstancesType.html | 6 +- html-test/ref/QuasiExpr.html | 12 +- html-test/ref/SpuriousSuperclassConstraints.html | 12 +- html-test/ref/Test.html | 12 +- html-test/ref/TypeFamilies.html | 180 ++++++++++++++++++--- html-test/ref/TypeFamilies2.html | 36 ++++- 24 files changed, 530 insertions(+), 112 deletions(-) (limited to 'html-test') diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index 1043453d..38fccf0c 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -530,14 +530,14 @@ ppDocInstances unicode (i : rest) (is, rest') = spanWith isUndocdInstance rest isUndocdInstance :: DocInstance a -> Maybe (InstHead a) -isUndocdInstance (i,Nothing,_) = Just i +isUndocdInstance (i,Nothing,_,_) = Just i isUndocdInstance _ = Nothing -- | Print a possibly commented instance. The instance header is printed inside -- an 'argBox'. The comment is printed to the right of the box in normal comment -- style. ppDocInstance :: Bool -> DocInstance DocNameI -> LaTeX -ppDocInstance unicode (instHead, doc, _) = +ppDocInstance unicode (instHead, doc, _, _) = declWithDoc (ppInstDecl unicode instHead) (fmap docToLaTeX $ fmap _doc doc) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 6e733373..d92bdd3a 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -566,8 +566,8 @@ ppInstances links origin instances splice unicode qual where instName = getOccString origin instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) - instDecl no (inst, mdoc, loc) = - ((ppInstHead links splice unicode qual mdoc origin False no inst), loc) + instDecl no (inst, mdoc, loc, mdl) = + ((ppInstHead links splice unicode qual mdoc origin False no inst mdl), loc) ppOrphanInstances :: LinksInfo @@ -581,8 +581,8 @@ ppOrphanInstances links instances splice unicode qual instOrigin inst = OriginClass (ihdClsName inst) instDecl :: Int -> DocInstance DocNameI -> (SubDecl,Located DocName) - instDecl no (inst, mdoc, loc) = - ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst), loc) + instDecl no (inst, mdoc, loc, mdl) = + ((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst mdl), loc) ppInstHead :: LinksInfo -> Splice -> Unicode -> Qualification @@ -591,13 +591,14 @@ ppInstHead :: LinksInfo -> Splice -> Unicode -> Qualification -> Bool -- ^ Is instance orphan -> Int -- ^ Normal -> InstHead DocNameI + -> Maybe Module -> SubDecl -ppInstHead links splice unicode qual mdoc origin orphan no ihd@(InstHead {..}) = +ppInstHead links splice unicode qual mdoc origin orphan no ihd@(InstHead {..}) mdl = case ihdInstType of ClassInst { .. } -> ( subInstHead iid $ ppContextNoLocs clsiCtx unicode qual HideEmptyContexts <+> typ , mdoc - , [subInstDetails iid ats sigs] + , [subInstDetails iid ats sigs mname] ) where sigs = ppInstanceSigs links splice unicode qual clsiSigs @@ -605,7 +606,7 @@ ppInstHead links splice unicode qual mdoc origin orphan no ihd@(InstHead {..}) = TypeInst rhs -> ( subInstHead iid ptype , mdoc - , [subFamInstDetails iid prhs] + , [subFamInstDetails iid prhs mname] ) where ptype = keyword "type" <+> typ @@ -614,11 +615,12 @@ ppInstHead links splice unicode qual mdoc origin orphan no ihd@(InstHead {..}) = DataInst dd -> ( subInstHead iid pdata , mdoc - , [subFamInstDetails iid pdecl]) + , [subFamInstDetails iid pdecl mname]) where pdata = keyword "data" <+> typ pdecl = pdata <+> ppShortDataDecl False True dd [] unicode qual where + mname = maybe noHtml (\m -> toHtml "Defined in" <+> ppModule m) mdl iid = instanceId origin no orphan ihd typ = ppAppNameTypes ihdClsName ihdTypes unicode qual diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index e020b909..217ca2af 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -47,7 +47,7 @@ import Haddock.Backends.Xhtml.Utils import Haddock.Types import Haddock.Utils (makeAnchorId, nameAnchorId) import qualified Data.Map as Map -import Text.XHtml hiding ( name, title, p, quote ) +import Text.XHtml hiding ( name, title, quote ) import FastString ( unpackFS ) import GHC @@ -228,15 +228,17 @@ subInstHead iid hdr = subInstDetails :: String -- ^ Instance unique id (for anchor generation) -> [Html] -- ^ Associated type contents -> [Html] -- ^ Method contents (pretty-printed signatures) + -> Html -- ^ Source module -> Html -subInstDetails iid ats mets = - subInstSection iid << (subAssociatedTypes ats <+> subMethods mets) +subInstDetails iid ats mets mdl = + subInstSection iid << (p mdl <+> subAssociatedTypes ats <+> subMethods mets) subFamInstDetails :: String -- ^ Instance unique id (for anchor generation) -> Html -- ^ Type or data family instance + -> Html -- ^ Source module TODO: use this -> Html -subFamInstDetails iid fi = - subInstSection iid << thediv ! [theclass "src"] << fi +subFamInstDetails iid fi mdl = + subInstSection iid << (p mdl <+> (thediv ! [theclass "src"] << fi)) subInstSection :: String -- ^ Instance unique id (for anchor generation) -> Html diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index ec8b98c8..d0ed1698 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -69,7 +69,7 @@ attachInstances expInfo ifaces instIfaceMap = do attachOrphanInstances :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap -> [ClsInst] -> [DocInstance GhcRn] attachOrphanInstances expInfo iface ifaceMap instIfaceMap cls_instances = - [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap, (L (getSrcSpan n) n)) + [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap, (L (getSrcSpan n) n), Nothing) | let is = [ (instanceSig i, getName i) | i <- cls_instances, isOrphan (is_orphan i) ] , (i@(_,_,cls,tys), n) <- sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo cls tys @@ -91,7 +91,11 @@ attachToExportItem index expInfo iface ifaceMap instIfaceMap export = let mb_instances = lookupNameEnv index (tcdName d) cls_instances = maybeToList mb_instances >>= fst fam_instances = maybeToList mb_instances >>= snd - fam_insts = [ (synifyFamInst i opaque, doc,spanNameE n (synifyFamInst i opaque) (L eSpan (tcdName d)) ) + fam_insts = [ ( synifyFamInst i opaque + , doc + , spanNameE n (synifyFamInst i opaque) (L eSpan (tcdName d)) + , nameModule_maybe n + ) | i <- sortBy (comparing instFam) fam_instances , let n = getName i , let doc = instLookup instDocMap n iface ifaceMap instIfaceMap @@ -99,14 +103,18 @@ attachToExportItem index expInfo iface ifaceMap instIfaceMap export = , not $ any (isTypeHidden expInfo) (fi_tys i) , let opaque = isTypeHidden expInfo (fi_rhs i) ] - cls_insts = [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap, spanName n (synifyInstHead i) (L eSpan (tcdName d))) + cls_insts = [ ( synifyInstHead i + , instLookup instDocMap n iface ifaceMap instIfaceMap + , spanName n (synifyInstHead i) (L eSpan (tcdName d)) + , nameModule_maybe n + ) | let is = [ (instanceSig i, getName i) | i <- cls_instances ] , (i@(_,_,cls,tys), n) <- sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo cls tys ] -- fam_insts but with failing type fams filtered out - cleanFamInsts = [ (fi, n, L l r) | (Right fi, n, L l (Right r)) <- fam_insts ] - famInstErrs = [ errm | (Left errm, _, _) <- fam_insts ] + cleanFamInsts = [ (fi, n, L l r, m) | (Right fi, n, L l (Right r), m) <- fam_insts ] + famInstErrs = [ errm | (Left errm, _, _, _) <- fam_insts ] in do dfs <- getDynFlags let mkBug = (text "haddock-bug:" <+>) . text diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index df25e6a7..b2d0e1e1 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -627,11 +627,11 @@ renameWc rn_thing (HsWC { hswc_body = thing }) , hswc_wcs = PlaceHolder }) } renameDocInstance :: DocInstance GhcRn -> RnM (DocInstance DocNameI) -renameDocInstance (inst, idoc, L l n) = do +renameDocInstance (inst, idoc, L l n, m) = do inst' <- renameInstHead inst n' <- rename n idoc' <- mapM renameDoc idoc - return (inst', idoc',L l n') + return (inst', idoc', L l n', m) renameExportItem :: ExportItem GhcRn -> RnM (ExportItem DocNameI) renameExportItem item = case item of diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 725606b2..2810862f 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -388,7 +388,7 @@ mkPseudoFamilyDecl (FamilyDecl { .. }) = PseudoFamilyDecl -- | An instance head that may have documentation and a source location. -type DocInstance name = (InstHead name, Maybe (MDoc (IdP name)), Located (IdP name)) +type DocInstance name = (InstHead name, Maybe (MDoc (IdP name)), Located (IdP name), Maybe Module) -- | The head of an instance. Consists of a class name, a list of type -- parameters (which may be annotated with kinds), and an instance type diff --git a/html-test/ref/Bug26.html b/html-test/ref/Bug26.html index 820fde3f..e50169ba 100644 --- a/html-test/ref/Bug26.html +++ b/html-test/ref/Bug26.html @@ -180,7 +180,11 @@ >

                      Instance details

                      Defined in Bug26

                      Methods

                      Instance details

                      Defined in Bug294

                      data
                      Instance details

                      Defined in Bug294

                      data
                      Instance details

                      Defined in Bug294

                      data
                      Instance details

                      Defined in Bug294

                      data
                      Instance details

                      Defined in Bug294

                      data
                      Instance details

                      Defined in Control.Applicative

                      Associated Types

                      Instance details

                      Defined in Control.Applicative

                      Methods

                      Instance details

                      Defined in Control.Applicative

                      Methods

                      Instance details

                      Defined in Control.Applicative

                      Methods

                      Instance details

                      Defined in Control.Applicative

                      Associated Types

                      Instance details

                      Defined in Control.Applicative

                      type
                      Instance details

                      Defined in Control.Applicative

                      type
                      Instance details

                      Defined in Bug613

                      Methods

                      Instance details

                      Defined in Bug613

                      Methods

                      Instance details

                      Defined in Bug613

                      Methods

                      Instance details

                      Defined in Bug679

                      Methods

                      Instance details

                      Defined in Bug679

                      Methods

                      Instance details

                      Defined in Bug7

                      Since: 2.1Since: base-2.1

                      Since: 2.1Since: base-2.1

                      Since: 2.1Since: base-2.1

                      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

                      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

                      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]

                      A Int
                      B Int
                      D Int Int
                      E Int
                      A a (a -> Int)
                      SomeNewTypeConst String

                      SomeOtherNewTypeConst String

                    • foo :: Int
                    • :: Int

                      foo :: Int :: Int #

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

                      some name

                      fooValue :: Int :: Int

                      data family SomeTypeFamily k :: * -> * k :: * -> *

                    • data family SomeOtherTypeFamily k :: * -> *
                    • k :: * -> *
                      data family SomeTypeFamily k :: * -> * k :: * -> * #

                      data family SomeOtherTypeFamily k :: * -> * k :: * -> * #

                      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
                    • Int Int
                    • C4 :: {..} -> H1 Int a
                    • Int a
                    • 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

                      HashFloat Float#

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

                      HashInt Int#

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

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

                      VisibleClassInt Int# 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]] #

                      FooMaybe Maybe#

                      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 :: * -> *)#

                      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) #

                      BarMaybe [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 #dataThudInt ( Int (Quux a [a] c)data ThudInt ( Int (Quux a [a] c) NorfIntBool Int Bool#typePlughInt c Bool :: * Int c Bool :: * #

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

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

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

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

                    • f :: Integer
                    • :: Integer

                      f :: Integer :: Integer #

                    • g :: Int
                    • :: Int

                      g :: Int :: Int #

                      type a <>< b :: * b :: *
                    • datatype a <>< b :: * b :: * infixl 2aClass :: 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
                    • data (a :: *) (a :: *) >< b = Emptypattern 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 aC3 :: {..} -> H1 Int IntC4 :: {..} -> H1 Int a
                      AType Int
                      Integer String String 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 #

                      dataSomeType (f :: * -> *) a (f :: * -> *) a #

                      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 (Maybe Float)
                    • | BT a b, T Int Float)
                    • Int Float)
                    • 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
                    • () -> IO Int
                    • o :: Float -> IO Float
                    • :: Float -> IO Float
                    • f' :: Int
                    • :: Int
                    • withType :: Int
                    • :: Int
                    • withoutType
                    • Int (Maybe Float) Int Float)d :: TFloat b Float b #

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

                      DInt Int#d :: TInt b Int b #

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

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

                      Int Int Float Float)-> IO ()
                      Show x => Show x => BlubCtor xBlub :: () => forall x. Show x => x -> x. Show x => x -> BlubType #

                      data (a :: *) (a :: *) >< b #pattern PatWithExplicitSig :: Eq somex => somex -> :: Eq somex => somex -> FooType somex #data Pattern :: [*] -> * :: [*] -> * where #

                      Cons :: Maybe h -> :: Maybe h -> Pattern t -> PatternRevPattern :: RevList * -> * * -> * where #RevCons :: Maybe h -> :: Maybe h -> RevPattern t -> RevPatterndata Tuple :: (*, *) -> * :: (*, *) -> * where #
                    • fib :: Integer -> Integer
                    • :: Integer -> Integer

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

                      Fibonacci number of given IntegerInteger.

                      fib n <= fib (n + 1)
                      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-> IO Int
                      :: (Int, Int, Float)

                      takes a triple

                      -> Int

                      returns an IntInt

                      -> IO Int

                      and the return value

                      :: Float-> IO FloatX<> (a :: *) (a :: *)#X<> (a :: *) = (a :: *) = XAssocDY :: * :: * #

                      AssocT Y :: * :: * #

                      Y<> (a :: *) (a :: *)#Y<> (a :: *) = a (a :: *) = a
                    • BatZ1 :: :: forall (z :: Z). Z -> Bat ZA
                    • BatZ2 :: :: forall (z :: Z). {..} -> Bat ZBdata family Bat (a :: k) :: * (a :: k) :: * #

                    • BatZ1 :: :: forall (z :: Z). Z -> Bat ZA
                    • BatZ2 :: :: forall (z :: Z). {..} -> Bat ZBdata AssocD a :: * a :: * #

                      type AssocT a :: * a :: * #

                      AssocD Y :: * :: * #

                      AssocT Y :: * :: * #

                      AssocD X :: * :: * #

                      AssocT X :: * :: * #

                      Y <> (a :: *) (a :: *) #Y <> (a :: *) = a (a :: *) = aX <> (a :: *) (a :: *) #X <> (a :: *) = (a :: *) = X
                    • x :: Int
                    • :: Int

                      x :: Int :: Int #

                      :: 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 #

                      data family Bat (a :: k) :: * (a :: k) :: *
                    • classdata AssocD a :: *
                    • a :: *
                    • type AssocT a :: *
                    • a :: *
                    • AssocD X :: * :: * #

                      AssocT X :: * :: * #

                    • Foo X :: *)
                      :: *)