[commit: ghc] wip/T16188: Fix invalid doc comment (e67384f)

git at git.haskell.org git at git.haskell.org
Sun Feb 10 21:31:34 UTC 2019


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

On branch  : wip/T16188
Link       : http://ghc.haskell.org/trac/ghc/changeset/e67384f43060000f5e9e6b5cb7539bd5042835a9/ghc

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

commit e67384f43060000f5e9e6b5cb7539bd5042835a9
Author: Alec Theriault <alec.theriault at gmail.com>
Date:   Tue Jan 29 00:35:24 2019 -0800

    Fix invalid doc comment
    
    The invalid doc comments were exposed by 24b39ce53eedad4cefc30f6786542d2072d1f9b0.
    The fix is to properly escaped the `{-` and `-}` in the doc comments.
    Some other miscallaneous markup issues are also fixed.


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

e67384f43060000f5e9e6b5cb7539bd5042835a9
 libraries/ghc-prim/GHC/Classes.hs | 38 ++++++++++++++++++++++----------------
 1 file changed, 22 insertions(+), 16 deletions(-)

diff --git a/libraries/ghc-prim/GHC/Classes.hs b/libraries/ghc-prim/GHC/Classes.hs
index 1143883..14e7ae3 100644
--- a/libraries/ghc-prim/GHC/Classes.hs
+++ b/libraries/ghc-prim/GHC/Classes.hs
@@ -37,7 +37,7 @@ module GHC.Classes(
     Eq(..),
     Ord(..),
     -- ** Monomorphic equality operators
-    -- | See GHC.Classes#matching_overloaded_methods_in_rules
+    -- $matching_overloaded_methods_in_rules
     eqInt, neInt,
     eqWord, neWord,
     eqChar, neChar,
@@ -81,9 +81,11 @@ Matching on class methods (e.g. @(==)@) in rewrite rules tends to be a bit
 fragile. For instance, consider this motivating example from the @bytestring@
 library,
 
-> break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
-> breakByte :: Word8 -> ByteString -> (ByteString, ByteString)
-> {-# RULES "break -> breakByte" forall a. break (== x) = breakByte x #-}
+@
+break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
+breakByte :: Word8 -> ByteString -> (ByteString, ByteString)
+\{\-\# RULES "break -> breakByte" forall a. break (== x) = breakByte x \#\-\}
+@
 
 Here we have two functions, with @breakByte@ providing an optimized
 implementation of @break@ where the predicate is merely testing for equality
@@ -95,23 +97,27 @@ For this reason, most of the primitive types in @base@ have 'Eq' and 'Ord'
 instances defined in terms of helper functions with inlinings delayed to phase
 1. For instance, @Word8@\'s @Eq@ instance looks like,
 
-> instance Eq Word8 where
->     (==) = eqWord8
->     (/=) = neWord8
->
-> eqWord8, neWord8 :: Word8 -> Word8 -> Bool
-> eqWord8 (W8# x) (W8# y) = ...
-> neWord8 (W8# x) (W8# y) = ...
-> {-# INLINE [1] eqWord8 #-}
-> {-# INLINE [1] neWord8 #-}
+@
+instance Eq Word8 where
+    (==) = eqWord8
+    (/=) = neWord8
+
+eqWord8, neWord8 :: Word8 -> Word8 -> Bool
+eqWord8 (W8# x) (W8# y) = ...
+neWord8 (W8# x) (W8# y) = ...
+\{\-\# INLINE [1] eqWord8 \#\-\}
+\{\-\# INLINE [1] neWord8 \#\-\}
+@
 
 This allows us to save our @break@ rule above by rewriting it to instead match
 against @eqWord8@,
 
-> {-# RULES "break -> breakByte" forall a. break (`eqWord8` x) = breakByte x #-}
+@
+\{\-\# RULES "break -> breakByte" forall a. break (`eqWord8` x) = breakByte x \#\-\}
+@
 
-Currently this is only done for '(==)', '(/=)', '(<)', '(<=)', '(>)', and '(>=)'
-for the types in "GHC.Word" and "GHC.Int".
+Currently this is only done for @('==')@, @('/=')@, @('<')@, @('<=')@, @('>')@,
+and @('>=')@ for the types in "GHC.Word" and "GHC.Int".
 -}
 
 -- | The 'Eq' class defines equality ('==') and inequality ('/=').



More information about the ghc-commits mailing list