[commit: ghc] master: Fix new Haddock doc parse failures. (5f2cdca)

git at git.haskell.org git at git.haskell.org
Sun Jan 12 20:45:41 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5f2cdca8d745bd47847c3f29c8c32786ce728c8b/ghc

>---------------------------------------------------------------

commit 5f2cdca8d745bd47847c3f29c8c32786ce728c8b
Author: Austin Seipp <austin at well-typed.com>
Date:   Sun Jan 12 12:37:59 2014 -0600

    Fix new Haddock doc parse failures.
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>


>---------------------------------------------------------------

5f2cdca8d745bd47847c3f29c8c32786ce728c8b
 compiler/llvmGen/Llvm/MetaData.hs    |   13 ++++++-------
 compiler/typecheck/TcGenGenerics.lhs |    8 ++++----
 compiler/types/Coercion.lhs          |    5 +++--
 compiler/utils/UniqFM.lhs            |   18 +++++++++++-------
 4 files changed, 24 insertions(+), 20 deletions(-)

diff --git a/compiler/llvmGen/Llvm/MetaData.hs b/compiler/llvmGen/Llvm/MetaData.hs
index dda3ca0..36efcd7 100644
--- a/compiler/llvmGen/Llvm/MetaData.hs
+++ b/compiler/llvmGen/Llvm/MetaData.hs
@@ -1,5 +1,9 @@
---------------------------------------------------------------------------------
--- | The LLVM Metadata System.
+module Llvm.MetaData where
+
+import Llvm.Types
+import Outputable
+
+-- The LLVM Metadata System.
 --
 -- The LLVM metadata feature is poorly documented but roughly follows the
 -- following design:
@@ -50,11 +54,6 @@
 --   For example:
 --     !llvm.module.linkage = !{ !0, !1 }
 --
-module Llvm.MetaData where
-
-import Llvm.Types
-
-import Outputable
 
 -- | LLVM metadata expressions
 data MetaExpr = MetaStr LMString
diff --git a/compiler/typecheck/TcGenGenerics.lhs b/compiler/typecheck/TcGenGenerics.lhs
index 872b969..2387625 100644
--- a/compiler/typecheck/TcGenGenerics.lhs
+++ b/compiler/typecheck/TcGenGenerics.lhs
@@ -528,11 +528,11 @@ data ArgTyAlg a = ArgTyAlg
 -- > arg t = case t of
 -- >   _ | isTyVar t         -> if (t == argVar) then Par1 else Par0 t
 -- >   App f [t'] |
---       representable1 f &&
---       t' == argVar        -> Rec1 f
+-- >     representable1 f &&
+-- >     t' == argVar        -> Rec1 f
 -- >   App f [t'] |
---       representable1 f &&
---       t' has tyvars       -> f :.: (arg t')
+-- >     representable1 f &&
+-- >     t' has tyvars       -> f :.: (arg t')
 -- >   _                     -> Rec0 t
 --
 -- where @argVar@ is the last type variable in the data type declaration we are
diff --git a/compiler/types/Coercion.lhs b/compiler/types/Coercion.lhs
index 9dc0313..0887bf7 100644
--- a/compiler/types/Coercion.lhs
+++ b/compiler/types/Coercion.lhs
@@ -1160,11 +1160,12 @@ mkCoCast c g
 %************************************************************************
 
 \begin{code}
-instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, Coercion)
--- ^ If @co :: T ts ~ rep_ty@ then:
+-- | If @co :: T ts ~ rep_ty@ then:
 --
 -- > instNewTyCon_maybe T ts = Just (rep_ty, co)
+--
 -- Checks for a newtype, and for being saturated
+instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, Coercion)
 instNewTyCon_maybe tc tys
   | Just (tvs, ty, co_tc) <- unwrapNewTyCon_maybe tc  -- Check for newtype
   , tys `lengthIs` tyConArity tc                      -- Check saturated
diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs
index d37041c..7fde82a 100644
--- a/compiler/utils/UniqFM.lhs
+++ b/compiler/utils/UniqFM.lhs
@@ -135,13 +135,17 @@ plusUFM         :: UniqFM elt -> UniqFM elt -> UniqFM elt
 plusUFM_C       :: (elt -> elt -> elt)
                 -> UniqFM elt -> UniqFM elt -> UniqFM elt
 
--- | plusUFM_CD  f m1 d1 m2 d2
---   merges the maps using `f` as the combinding function and d1 resp. d2 as
---   the default value if there is no entry in m1 reps. m2. The domain is the union
---   of the domains of m1 m2.
---   Representative example:
---   > plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42
---   >   == {A: f 1 42, B: f 2 3, C: f 23 4 }
+-- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the
+-- combinding function and `d1` resp. `d2` as the default value if
+-- there is no entry in `m1` reps. `m2`. The domain is the union of
+-- the domains of `m1` and `m2`.
+--
+-- Representative example:
+--
+-- @
+-- plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42
+--    == {A: f 1 42, B: f 2 3, C: f 23 4 }
+-- @
 plusUFM_CD      :: (elt -> elt -> elt)
                 -> UniqFM elt -> elt -> UniqFM elt -> elt -> UniqFM elt
 



More information about the ghc-commits mailing list