Skip to content
This repository was archived by the owner on Aug 3, 2024. It is now read-only.

Constructor and pattern synonym argument docs #709

Merged
merged 9 commits into from
Jan 13, 2018

Conversation

harpocrates
Copy link
Collaborator

@harpocrates harpocrates commented Nov 25, 2017

This adds support for

  • docs on arguments of non-record plain data constructors
  • docs on arguments of non-record GADTs data constructors
  • docs on arguments of bundled patterns
  • docs on arguments of non-bundled patterns

Here is the diff to Phabricator (currently blocked until this PR is done) which introduces changes in the GHC parser to make this possible. Consider the following module:

{-# LANGUAGE GADTs, PatternSynonyms #-}

module Test (Foo(..), Boo(Foo, Fo), pattern Bo) where

data Foo
   = Boa             -- ^ doc on the `Boa` constrictor
       Int           -- ^ doc on the `Int` field of `Boa`
       String        -- ^ doc on the `String` field of `Boa`

   | Int             -- ^ doc on the `Int` field of the `:*` constructor
       :*            -- ^ doc on the `:*` constructor
     String          -- ^ doc on the `String` field of the `:*` constructor

infixr 1 `Foo`
infixr 2 `Boa`
infixr 3 :*

data Boo where
  -- | Info about a 'Foo'
  Foo :: Int    -- ^ `Int` field of `Foo`
      -> String -- ^ `String` field of `Foo`
      -> Boo    -- ^ Make a `Boo`

infixr 4 `Boo`

-- | Info about bundled 'Fo'
pattern Fo :: Int    -- ^ an 'Int'
           -> String -- ^ a 'String'
           -> Boo    -- ^ a 'Boo'
pattern Fo x y = Foo x y

infixr 5 `Fo`

-- | Info about not-bundled 'Bo'
pattern Bo :: Int    -- ^ an 'Int'
           -> String -- ^ a 'String'
           -> Boo    -- ^ a 'Boo'
pattern Bo x y = Foo x y

infixr 6 `Bo`

Without this PR, this is what the generated docs used to look like:

screen shot 2017-11-24 at 8 40 03 pm

Now, they look like:

screen shot 2017-11-24 at 8 42 12 pm

Note that the constructor arguments only get expanded out if there are docs on at least one of them (same for pattern synonyms). Although this is still WIP, I'd appreciate any thoughts/feedback.

TODO

  • check if the LaTeX (or some other) backend needs to be also updated
  • add tests for the new functionality

@alexbiehl
Copy link
Member

Nice, will have a look when I get home later!

@harpocrates
Copy link
Collaborator Author

I've taken a look at the LaTeX backend, but I'm a bit unsure how to proceed. AFAICT, that is the only other backend that needs to be updated. Does that sound right?

Generating docs from sample source, some things look suspiciously ugly - records on data declarations are completely misaligned. I even had to trim out some empty tables to get everything to compile. Is the LaTeX backend currently broken? If not, are there any pictures (or DVI, PDF, PS) of what that output is supposed to look like? I wouldn't be surprised if it was my LaTeX setup that was broken...

@alexbiehl
Copy link
Member

Yes, latex is the only other backend which needs updates. Sounds bad. Have you tried the latex backend on master branch does it make a difference?

@harpocrates
Copy link
Collaborator Author

Doesn't look like the master branch is any different. After a handful of tiny LaTeX tweaks (I'm again not sure if this is my setup, or the generated code), I get some gross output. Here's the input:

{-# LANGUAGE GADTs, PatternSynonyms #-}

module Test (Foo(..), Boo(Boo, Fo), pattern Bo) where

data Foo = Foo
     { x :: String  -- ^ doc on the `String` field of `Boa`
     , y :: String  -- ^ doc on the `String` field of the `:*` constructor
     }

data Boo where
  -- | Info about a 'Foo'
  Boo :: Int -> String -> Boo

-- | Info about bundled 'Fo'
pattern Fo :: Int -> String -> Boo
pattern Fo x y = Boo x y

-- | Info about not-bundled 'Bo'
pattern Bo :: Int -> String -> Boo
pattern Bo x y = Boo x y

And here is a screenshot of the output.

screen shot 2017-11-26 at 7 34 30 pm

Looks like GADTs, bundled pattern synonyms, and record fields are all pretty gross. If you could confirm that this is not just something with my LaTeX setup (I really don't think it is), and that this is all not intended behaviour, I'd like to fix these issues as part of this PR (seems pretty on-topic anyways).

@alexbiehl
Copy link
Member

alexbiehl commented Nov 27, 2017

I can confirm that it indeed looks broken! When fixing this could you add test cases for html and latex? Would be great to catch these when they regress again.

@alexbiehl
Copy link
Member

@harpocrates How does it look now? :)

@harpocrates
Copy link
Collaborator Author

The handling of data declarations and some stuff around pattern synonyms has been rewritten. I've mirrored as much as possible the XHTML backend approach. That said, I've had to make some more opinionated choices here, so I'd appreciate feedback (both on the rendered output and the generated LaTeX).

Given this code:

{-# LANGUAGE GADTs, PatternSynonyms #-}

module Test (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where

data Foo
  = Rec             -- ^ doc on a record
     { x :: String  -- ^ doc on the `String` field of `Rec`
     , y :: String  -- ^ doc on the `String` field of `Rec`
     }
   | Baz Int String  -- ^ old prefix doc style
   | Boa             -- ^ doc on the `Boa` constrictor
       Int           -- ^ doc on the `Int` field of `Boa`
       String        -- ^ doc on the `String` field of `Boa`
   | Int :| String   -- ^ old infix doc style
   | Int             -- ^ doc on the `Int` field of the `:*` constructor
       :*            -- ^ doc on the `:*` constructor
     String          -- ^ doc on the `String` field of the `:*` constructor

infixr 1 `Foo`
infixr 2 `Boa`
infixr 3 :*

data Boo where
  -- | Info about a 'Foo'
  Foo :: Int    -- ^ `Int` field of `Foo`
      -> String -- ^ `String` field of `Foo`
      -> Boo    -- ^ Make a `Boo`

  -- | no argument docs GADT
  Foa :: Int -> Boo

infixr 4 `Boo`

-- | Info about bundled 'Fo'
pattern Fo :: Int    -- ^ an 'Int'
           -> String -- ^ a 'String'
           -> Boo    -- ^ a 'Boo'
pattern Fo x y = Foo x y

-- | Bundled and no argument docs
pattern Fo' :: Boo
pattern Fo' = Foo 1 "hi"

infixr 5 `Fo`

-- | Info about not-bundled 'Bo'
pattern Bo :: Int    -- ^ an 'Int'
           -> String -- ^ a 'String'
           -> Boo -- ^ a 'Boo' pattern
pattern Bo x y = Foo x y

-- | Not bunded and no argument docs
pattern Bo' :: Int -> String -> Boo
pattern Bo' x y = Foo x y

infixr 6 `Bo`

The LaTeX backend now produces the following rendered output:

screen shot 2017-11-27 at 11 05 37 am

I'm a bit short on time right now, so I haven't yet had time to clean up the code in the LaTeX backend. I don't expect to change the actual LaTeX or XHTML output anymore though.

@harpocrates
Copy link
Collaborator Author

harpocrates commented Nov 27, 2017

So, I'd like to confirm:

  • does the XHTML output look satisfactory?
  • does the LaTeX output look satisfactory?

If so, I'm going to start cleaning up the code (without changing the output) and add tests. Unless there are any objections, I don't intend to change the output anymore.

@harpocrates
Copy link
Collaborator Author

Mentioning this before I forget about it: this PR would close:

Additionally, some related tickets that I can confirm are fixed but still open:

@alexbiehl
Copy link
Member

Both HTML and LaTex are both looking reasonable.

I am happy that LaTeX is working again! Though nobody complained so far so it is probably not really used by anyone.

Please don't forget to add a changelog entry when you are done.

@harpocrates
Copy link
Collaborator Author

I said I was done with changes, but I ran into one more issue while cleaning up: GADT record constructors. The existing way of rendering those does not lend itself well to adding docs to the return type (something I think is actually going to be useful for GADTs). It appears that the new way of printing these is close to what the initial implementer also wanted to do, as witnessed by #461.

The LaTeX backend did not support any form of GADT record constructors. Now it does.

Given

{-# LANGUAGE GADTs, PatternSynonyms #-}

module Test (Boo(..)) where

data Boo where
  Fot :: { x :: Int  -- ^ an 'x'
         , y :: Int  -- ^ a 'y'
         } -> Boo

  -- | Record GADT with docs
  Fob :: { w :: Int  -- ^ a 'w'
         , z :: Int  -- ^ a 'z'
         } -> Boo    -- ^ a 'Boo'

We get the XHTML

screen shot 2017-11-27 at 5 26 37 pm

And the LaTeX

screen shot 2017-11-27 at 5 26 48 pm

This is pretty different from what you get today:

screen shot 2017-11-27 at 5 28 19 pm

How does this change sound?

@harpocrates
Copy link
Collaborator Author

harpocrates commented Nov 28, 2017

I'm also having some weird issues about GADT-style constructors sometimes being handled as regular prefix data constructors (in this branch, in GHC head, and in master). I haven't been able to narrow down the behaviour to a test case yet. Any idea what that might be about?

I'm slowly learning about Haddock. Turns out that record GADTs only get interpreted as GADTs if their record fields are exported. In some cases, that's OK. Other cases like this are a bit funky:

{-# LANGUAGE GADTs #-}

module Test (Boo(Boo)) where

data Boo where
  Boo :: { n :: Int } -> Boo

renders as

screen shot 2017-11-27 at 7 13 33 pm

but if you add n to the import list, it renders as

screen shot 2017-11-27 at 7 14 03 pm

That seems incorrect...

@alexbiehl
Copy link
Member

alexbiehl commented Nov 28, 2017

I am honestly surprised how much we gain from your changes! I was under the impression these problems were solved.

Btw. Have you checked if master also renders Boo in the same way? I recently restructured the way export lists are processed..

Edit: Yes, master has the same behaviour. And the behaviour is the same as for data declarations:

module Test(Foo(Foo)) where

data Foo = Foo { x :: Int }

Shows the same symptoms.

Edit: N.B. On ghc-head exports are calculated on the Avails ghc calculates for each export list item. So this is exactly what GHC exports. Not some weird haddock interpretation.

@harpocrates
Copy link
Collaborator Author

harpocrates commented Nov 28, 2017

I'd love to run the tests, but I'm not sure how to. Right now, I've been relying on the cabal new-* commands. I've new-configure'ed with my GHC branch, then I can new-build Haddock. Unfortunately new-test seems unable to come up with a build plan for the tests (--allow-newer fails to compile). Since even theghc-head branch suffers from this problem, I'm not sure what to do...

Edit: Yes, master has the same behaviour. And the behaviour is the same as for data declarations:

Yes, although that bothers me a bit less than the GADT case - if the record field of data Foo = Foo { x :: Int } is not exported, Foo may as well be defined as data Foo = Foo Int to an end user. That is not the case for data Foo a where Foo :: { x :: Int } -> Foo Int.

@alexbiehl
Copy link
Member

Tests in ghc-head are a bit flaky. Although haddock(-api) is buildable by GHC-HEAD the test suite is not due to external dependencies which are not updated to work with HEAD yet.

@alexbiehl
Copy link
Member

And yes, you are right with the GADTs exports... Can you fix that?

@harpocrates
Copy link
Collaborator Author

Tests in ghc-head are a bit flaky. Although haddock(-api) is buildable by GHC-HEAD the test suite is not due to external dependencies which are not updated to work with HEAD yet.

I'll try see if I can fix the broken (test-suite) dependencies in a cabal sandbox; I hope most of those are missing Semigroup instances (I've already contacted one maintainer about this). What would be a good criterion for merging this PR? Is being able to run tests locally with patched versions of dependencies good enough given the circumstances?

And yes, you are right with the GADTs exports... Can you fix that?

I don't think this will be easy... I'm trying to finish off my TODO stack before the end of the year, so I'm not taking on anything new for now (this PR is one of the larger things in that stack). I'll at least open a ticket though.

@alexbiehl
Copy link
Member

alexbiehl commented Nov 29, 2017 via email

@alexbiehl
Copy link
Member

alexbiehl commented Nov 29, 2017 via email

@harpocrates
Copy link
Collaborator Author

I would be willing to merge as is. I did so with other pull requests targeting ghc-head. The plan is: As soon as ghc-8.4 stabilizes I will take care of the test suite

Hm. I'm mostly trying to build up confidence that my changes haven't inadvertently broken something else. I'm going to spend an hour now to see if by some happy hazard I can at least run the tests in a patched up sandbox. Then, I'm going to:

  1. Report back here on the results
  2. Let the GHC folks know that this PR is ready so that they can merge in my differential
  3. Report back here once 2 is merged in so we can merge this PR

And by the way, this change is independent of the differential in GHC, right?

Yes, modulo the fact that Haddocks won't parse on constructor arguments without the differential. I'd prefer the user manual not claim something is possible if it isn't yet. 😄

@alexbiehl
Copy link
Member

alexbiehl commented Nov 29, 2017 via email

@harpocrates
Copy link
Collaborator Author

harpocrates commented Nov 29, 2017

Alright. I give up. I was able to build the tests, but they fail for other reasons related to the test runner (I'm triggering this error and I'm not sure why...). In case you want to pick up where I left off, the transitive dependencies that are broken are all because of missing Semigroup. These are:

  • colour (I notified the maintainer by email) fixed in colour-2.3.4
  • primitive (HEAD of primitive is already fixed)
  • hspec (I opened an issue)

I'll go inform GHC we are ready for them to merge my differential.

@harpocrates harpocrates changed the title WIP Constructor and pattern synonym argument docs Constructor and pattern synonym argument docs Nov 29, 2017
@alexbiehl
Copy link
Member

I am afraid this needs rework after spjs ConDecl patches.

@harpocrates
Copy link
Collaborator Author

harpocrates commented Dec 10, 2017

Great.

Hopefully it will be mostly the GHC diff that will need reworking - most of this PR is just rendering. Any pointers on where/when these changes happened? More importantly, what is the usual way of proceeding for this sort of thing?

@alexbiehl
Copy link
Member

alexbiehl commented Dec 11, 2017

@harpocrates You mean how to fix the issues?

Usually I do something like this:

$ git fetch
$ git rebase origin/ghc-head
<fix all the issues>
$ git commit 
$ git push

Sorry for the overhead :(

@harpocrates
Copy link
Collaborator Author

I meant more for the GHC side of things (the Haddock workflow is clear). In particular: should I wait for things to settle down first (the commit message mentioned some followup annotation work), and should I continue working on that differential or just start a new one?

@alexbiehl
Copy link
Member

Looking at https://ghc.haskell.org/trac/ghc/ticket/14529 I think the refactoring itself is done now.

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.
It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.
Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.
This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs
This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.
Made code/comments consistent between the LaTeX and XHTML backend
when possible.
@harpocrates
Copy link
Collaborator Author

I'm not sure yet what the status of the Phabricator diff is. I thought it would need reworking, but I've looked at it again and this appears not to be the case. Since it has been accepted, I suppose it is just merging that is taking a long time. I'll check back in a couple of days on that.

That aside, I've rebased on top of SPJ's changes and checked that all of the screenshots above are still correct, so this is now merge-ready again.

We want return values to be documentable on record GADT constructors.
@alexbiehl alexbiehl merged commit aa33be5 into haskell:ghc-head Jan 13, 2018
@alexbiehl
Copy link
Member

I see the corresponding patch has landed in GHC! Let's merge this!

@harpocrates harpocrates mentioned this pull request Jan 25, 2018
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
bgamari pushed a commit to bgamari/haddock that referenced this pull request Jan 27, 2018
* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

(cherry picked from commit aa33be5)
@harpocrates harpocrates deleted the constructor-args branch July 21, 2018 15:07
@sjakobi
Copy link
Member

sjakobi commented Jul 21, 2018

Do we already have any tests for this new functionality?

@harpocrates
Copy link
Collaborator Author

Do we already have any tests for this new functionality?

Only recently, but yes! #858 covered everything I could think of.

@andreasabel
Copy link
Member

Released with haddock 2.21 (2018 Oct 16).

Sign up for free to subscribe to this conversation on GitHub. Already have an account? Sign in.
Labels
None yet
Projects
None yet
Development

Successfully merging this pull request may close these issues.

4 participants