#5467: Template Haskell: support for Haddock comments
---------------------------------+------------------------------------------
    Reporter:  reinerp           |       Owner:                  
        Type:  feature request   |      Status:  new             
    Priority:  normal            |   Component:  Template Haskell
     Version:  7.2.1             |    Keywords:                  
    Testcase:                    |   Blockedby:                  
          Os:  Unknown/Multiple  |    Blocking:                  
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
---------------------------------+------------------------------------------
 I would like Template Haskell to be aware of Haddock comments.

 Here's a concrete example. The data-accessor-template package
 (http://hackage.haskell.org/package/data-accessor-template) can be used as
 follows:

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 module Example where
 import Data.Accessor
 import Data.Accessor.Template

 data MyRecord = MyRecord
  { field1_ :: Int -- ^ a field
  , field2_ :: Int -- ^ another field
  }

 deriveAccessors ''MyRecord
 -- produces these:
 -- field1, field2 :: Accessor MyRecord Int
 }}}

 We would like the values {{{field1}}} and {{{field2}}} to inherit the
 documentation from {{{field1_}}} and {{{field2_}}}, but there is no way to
 automate this in Template Haskell -- or even to document {{{field1}}} and
 {{{field2}}} by hand! I would like Template Haskell to support this.

 There are two related features required to make this work: firstly, the
 {{{Dec}}} datatype needs to be extended to support Haddock comments;
 secondly, {{{reify}}} needs to return these comments.

 I suspect the second feature may require significant plumbing to work in
 the general case, because I believe that {{{.hi}}} files don't store
 Haddock comments. A tolerable compromise in this particular example would
 be to only reify comments for things defined in the current module.

 A possible API would be

 {{{
 data Dec =
   ...
   | DocD Name String -- attach the given docstring to the given name
   | SigD Name Type (Maybe [String]) -- a type signature, with a possibly-
 empty docstring for each argument and for the result type
   ...
 }}}

 The {{{DocD}}} constructor is new, but the {{{SigD}}} constructor is
 unfortunately a modification of the current {{{SigD Name Type}}}
 constructor. We make this modification to support comments of this form:

 {{{
 f :: Int   -- ^ The 'Int' argument
   -> Float -- ^ The 'Float' argument
   -> IO () -- ^ The return value
 }}}

 A possible API for reifying comments would be

 {{{
 reifyDocs :: Name -> (Maybe String, Maybe [String]) -- documentation
 string; documentation for individual arguments
 }}}

 Reiner

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5467>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to