[PATCH] Haddockify some existing comments.

Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk
Fri Jun 7 00:16:51 CEST 2013


---
 compiler/hsSyn/HsBinds.lhs | 78 ++++++++++++++++++++++++++--------------------
 1 file changed, 45 insertions(+), 33 deletions(-)

diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs
index cb2538f..1d99767 100644
--- a/compiler/hsSyn/HsBinds.lhs
+++ b/compiler/hsSyn/HsBinds.lhs
@@ -53,7 +53,7 @@ Global bindings (where clauses)
 
 type HsLocalBinds id = HsLocalBindsLR id id
 
-data HsLocalBindsLR idL idR    -- Bindings in a 'let' expression
+data HsLocalBindsLR idL idR    -- ^ Bindings in a 'let' expression
                                -- or a 'where' clause
   = HsValBinds (HsValBindsLR idL idR)
   | HsIPBinds  (HsIPBinds idR)
@@ -62,7 +62,7 @@ data HsLocalBindsLR idL idR    -- Bindings in a 'let' expression
 
 type HsValBinds id = HsValBindsLR id id
 
-data HsValBindsLR idL idR  -- Value bindings (not implicit parameters)
+data HsValBindsLR idL idR  -- ^ Value bindings (not implicit parameters)
   = ValBindsIn             -- Before renaming RHS; idR is always RdrName
         (LHsBindsLR idL idR) [LSig idR] -- Not dependency analysed
                                         -- Recursive by default
@@ -132,14 +132,14 @@ data HsBindLR idL idR
                -- the bound variables.
     }
 
-  | VarBind {   -- Dictionary binding and suchlike
+  | VarBind {   -- | Dictionary binding and suchlike
         var_id     :: idL,           -- All VarBinds are introduced by the type checker
         var_rhs    :: LHsExpr idR,   -- Located only for consistency
         var_inline :: Bool           -- True <=> inline this binding regardless
                                      -- (used for implication constraints only)
     }
 
-  | AbsBinds {                          -- Binds abstraction; TRANSLATION
+  | AbsBinds {                          -- | Binds abstraction; TRANSLATION
         abs_tvs     :: [TyVar],
         abs_ev_vars :: [EvVar],  -- Includes equality constraints
 
@@ -174,7 +174,7 @@ data ABExport id
   } deriving (Data, Typeable)
 
 placeHolderNames :: NameSet
--- Used for the NameSet in FunBind and PatBind prior to the renamer
+-- | Used for the NameSet in 'FunBind' and 'PatBind' prior to the renamer
 placeHolderNames = panic "placeHolderNames"
 \end{code}
 
@@ -457,7 +457,7 @@ pprTicks pp_no_debug pp_when_debug
 data HsIPBinds id
   = IPBinds
         [LIPBind id]
-        TcEvBinds       -- Only in typechecker output; binds
+        TcEvBinds       -- ^ Only in typechecker output; binds
                         -- uses of the implicit parameters
   deriving (Data, Typeable)
 
@@ -501,42 +501,54 @@ serves for both.
 \begin{code}
 type LSig name = Located (Sig name)
 
-data Sig name   -- Signatures and pragmas
-  =     -- An ordinary type signature
-        -- f :: Num a => a -> a
+data Sig name   -- ^ Signatures and pragmas
+  =     -- | An ordinary type signature
+        -- @
+        --     f :: Num a => a -> a
+        -- @
     TypeSig [Located name] (LHsType name)
 
-        -- A type signature for a default method inside a class
-        -- default eq :: (Representable0 a, GEq (Rep0 a)) => a -> a -> Bool
+        -- | A type signature for a default method inside a class
+        -- @
+        --      default eq :: (Representable0 a, GEq (Rep0 a)) => a -> a -> Bool
+        -- @
   | GenericSig [Located name] (LHsType name)
 
-        -- A type signature in generated code, notably the code
+        -- | A type signature in generated code, notably the code
         -- generated for record selectors.  We simply record
         -- the desired Id itself, replete with its name, type
         -- and IdDetails.  Otherwise it's just like a type
         -- signature: there should be an accompanying binding
   | IdSig Id
 
-        -- An ordinary fixity declaration
+        -- | An ordinary fixity declaration
+        -- @
         --      infixl *** 8
+        -- @
   | FixSig (FixitySig name)
 
-        -- An inline pragma
-        -- {#- INLINE f #-}
-  | InlineSig   (Located name)  -- Function name
-                InlinePragma    -- Never defaultInlinePragma
-
-        -- A specialisation pragma
-        -- {-# SPECIALISE f :: Int -> Int #-}
-  | SpecSig     (Located name)  -- Specialise a function or datatype ...
-                (LHsType name)  -- ... to these types
-                InlinePragma    -- The pragma on SPECIALISE_INLINE form
+        -- | An inline pragma
+        -- @
+        --      {#- INLINE f #-}
+        -- @
+  | InlineSig   (Located name)  -- ^ Function name
+                InlinePragma    -- ^ Never defaultInlinePragma
+
+        -- | A specialisation pragma
+        -- @
+        --      {-# SPECIALISE f :: Int -> Int #-}
+        -- @
+  | SpecSig     (Located name)  -- ^ Specialise a function or datatype ...
+                (LHsType name)  -- ^ ... to these types
+                InlinePragma    -- ^ The pragma on SPECIALISE_INLINE form
                                 -- If it's just defaultInlinePragma, then we said
                                 --    SPECIALISE, not SPECIALISE_INLINE
 
-        -- A specialisation pragma for instance declarations only
-        -- {-# SPECIALISE instance Eq [Int] #-}
-  | SpecInstSig (LHsType name)  -- (Class tys); should be a specialisation of the
+        -- | A specialisation pragma for instance declarations only
+        -- @
+        --      {-# SPECIALISE instance Eq [Int] #-}
+        -- @
+  | SpecInstSig (LHsType name)  -- ^ @(Class tys)@; should be a specialisation of the
                                 -- current instance decl
   deriving (Data, Typeable)
 
@@ -545,9 +557,9 @@ type LFixitySig name = Located (FixitySig name)
 data FixitySig name = FixitySig (Located name) Fixity
   deriving (Data, Typeable)
 
--- TsSpecPrags conveys pragmas from the type checker to the desugarer
+-- | TsSpecPrags conveys pragmas from the type checker to the desugarer
 data TcSpecPrags
-  = IsDefaultMethod     -- Super-specialised: a default method should
+  = IsDefaultMethod     -- ^ Super-specialised: a default method should
                         -- be macro-expanded at every call site
   | SpecPrags [LTcSpecPrag]
   deriving (Data, Typeable)
@@ -556,9 +568,9 @@ type LTcSpecPrag = Located TcSpecPrag
 
 data TcSpecPrag
   = SpecPrag
-        Id              -- The Id to be specialised
-        HsWrapper       -- An wrapper, that specialises the polymorphic function
-        InlinePragma    -- Inlining spec for the specialised function
+        Id              -- ^ The Id to be specialised
+        HsWrapper       -- ^ A wrapper, that specialises the polymorphic function
+        InlinePragma    -- ^ Inlining spec for the specialised function
   deriving (Data, Typeable)
 
 noSpecPrags :: TcSpecPrags
@@ -579,13 +591,13 @@ isFixityLSig :: LSig name -> Bool
 isFixityLSig (L _ (FixSig {})) = True
 isFixityLSig _                 = False
 
-isVanillaLSig :: LSig name -> Bool       -- User type signatures
+isVanillaLSig :: LSig name -> Bool       -- ^ User type signatures
 -- A badly-named function, but it's part of the GHCi (used
 -- by Haddock) so I don't want to change it gratuitously.
 isVanillaLSig (L _(TypeSig {})) = True
 isVanillaLSig _                 = False
 
-isTypeLSig :: LSig name -> Bool  -- Type signatures
+isTypeLSig :: LSig name -> Bool  -- ^ Checks whether 'LSig' is a type signature
 isTypeLSig (L _(TypeSig {}))    = True
 isTypeLSig (L _(GenericSig {})) = True
 isTypeLSig (L _(IdSig {}))      = True
-- 
1.8.2.1


--------------070708050204080004010804--



More information about the ghc-devs mailing list