[Haskell-cafe] How to add Haddock comment for standalone derived instances?

Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk
Sat Aug 23 11:18:22 UTC 2014


On 08/23/2014 11:04 AM, Hiromi ISHII wrote:
> Hi cafe,
> 
> Is there any way to add the documentation comment for the instances defined with StandaloneDeriving?
> 
> I'm currently defining data-type using GADTs and its Typeable instance.
> Normally, this can be done only StandaloneDeriving and DeriveDataTypeable extensions:
> 
>> {-# LANGUAGE StandaloneDeriving, GADTs, DeriveDataTypeable #-}
>> data Ordinal n where
>>   OZ :: Ordinal (S n)
>>   OS :: Ordinal n -> Ordinal (S n)
>>
>> deriving instance Typeable Ordinal
> 
> I added `Typeable` instance for Ordinal recently, so I want to add some comments like "Since 0.2.3.0".
> But any of the following doesn't work or, even worse, haddock won't compile:
> 
> * Just before `deriving instance` line using  `-- | `
> * Just after `deriving` keyword but before `instance` using `-- | `
> * Just after the `Typeable Ordinal`, but no newline in-between, with `-- ^ `
> * The next line of `deriving` clause with `-- ^ `
> 
> Is there any way to add documentation for instances with standalone deriving, or it's just not supported yet?
> 
> -- Hiromi ISHII
> konn.jinro at gmail.com
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

I don't think there's support. Problem with these kind of issues is that
they have to be fixed in the GHC lexer + parser. Please open a GHC and
Haddock issue to track this if you want eventually want it to make it in.

-- 
Mateusz K.


More information about the Haskell-Cafe mailing list