[commit: packages/binary] master: Remove indentation of sample code in haddock. (043f0f3)

git at git.haskell.org git at git.haskell.org
Sun Dec 14 17:54:14 UTC 2014


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

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/043f0f3d713469dfd1a17d2f37939d6a4339293e

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

commit 043f0f3d713469dfd1a17d2f37939d6a4339293e
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date:   Tue Nov 12 23:15:38 2013 +0400

    Remove indentation of sample code in haddock.
    
    The rendered layout breaks when a code segment has multiple functions,
    it renders without the given indentation. In this commit we set the
    base indentation to 0 spaces, and thus it renders correctly.


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

043f0f3d713469dfd1a17d2f37939d6a4339293e
 src/Data/Binary/Get.hs | 116 ++++++++++++++++++++++++-------------------------
 1 file changed, 58 insertions(+), 58 deletions(-)

diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs
index e5d7219..ce6ab9d 100644
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@ -32,13 +32,13 @@
 --
 -- A corresponding Haskell value looks like this:
 --
--- @
--- data Trade = Trade
---   { timestamp :: !'Word32'
---   , price     :: !'Word32'
---   , qty       :: !'Word16'
---   } deriving ('Show')
--- @
+--@
+--data Trade = Trade
+--  { timestamp :: !'Word32'
+--  , price     :: !'Word32'
+--  , qty       :: !'Word16'
+--  } deriving ('Show')
+--@
 --
 -- The fields in @Trade@ are marked as strict (using @!@) since we don't need
 -- laziness here. In practise, you would probably consider using the UNPACK
@@ -47,21 +47,21 @@
 --
 -- Now, let's have a look at a decoder for this format.
 --
--- @
--- getTrade :: 'Get' Trade
--- getTrade = do
---   timestamp <- 'getWord32le'
---   price     <- 'getWord32le'
---   quantity  <- 'getWord16le'
---   return '$!' Trade timestamp price quantity
--- @
+--@
+--getTrade :: 'Get' Trade
+--getTrade = do
+--  timestamp <- 'getWord32le'
+--  price     <- 'getWord32le'
+--  quantity  <- 'getWord16le'
+--  return '$!' Trade timestamp price quantity
+--@
 --
 -- Or even simpler using applicative style:
 --
--- @
--- getTrade' :: 'Get' Trade
--- getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le'
--- @
+--@
+--getTrade' :: 'Get' Trade
+--getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le'
+--@
 --
 -- The applicative style can sometimes result in faster code, as @binary@
 -- will try to optimize the code by grouping the reads together.
@@ -72,25 +72,25 @@
 --
 -- Let's first define a function that decodes many @Trade at s.
 --
--- @
--- getTrades :: Get [Trade]
--- getTrades = do
---   empty <- 'isEmpty'
---   if empty
---     then return []
---     else do trade <- getTrade
---             trades <- getTrades
---             return (trade:trades)
--- @
+--@
+--getTrades :: Get [Trade]
+--getTrades = do
+--  empty <- 'isEmpty'
+--  if empty
+--    then return []
+--    else do trade <- getTrade
+--            trades <- getTrades
+--            return (trade:trades)
+--@
 --
 -- Finally, we run the decoder:
 --
--- @
--- lazyIOExample :: IO [Trade]
--- lazyIOExample = do
---  input <- BL.readFile \"trades.bin\"
---  return ('runGet' getTrades input)
--- @
+--@
+--lazyIOExample :: IO [Trade]
+--lazyIOExample = do
+-- input <- BL.readFile \"trades.bin\"
+-- return ('runGet' getTrades input)
+--@
 --
 -- This decoder has the downside that it will need to read all the input before
 -- it can return. On the other hand, it will not return anything until
@@ -100,31 +100,31 @@
 -- and get the following decoder. It will start to return data without knowing
 -- that it can decode all input.
 --
--- @
--- incrementalExample :: BL.ByteString -> [Trade]
--- incrementalExample input0 = go decoder input0
---   where
---     decoder = 'runGetIncremental' getTrade
---     go :: 'Decoder' Trade -> BL.ByteString -> [Trade]
---     go ('Done' leftover _consumed trade) input =
---       trade : go decoder (BL.chunk leftover input)
---     go ('Partial' k) input                     =
---       go (k . takeHeadChunk $ input) (dropHeadChunk input)
---     go ('Fail' _leftover _consumed msg) _input =
---       error msg
+--@
+--incrementalExample :: BL.ByteString -> [Trade]
+--incrementalExample input0 = go decoder input0
+--  where
+--    decoder = 'runGetIncremental' getTrade
+--    go :: 'Decoder' Trade -> BL.ByteString -> [Trade]
+--    go ('Done' leftover _consumed trade) input =
+--      trade : go decoder (BL.chunk leftover input)
+--    go ('Partial' k) input                     =
+--      go (k . takeHeadChunk $ input) (dropHeadChunk input)
+--    go ('Fail' _leftover _consumed msg) _input =
+--      error msg
 --
--- takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString
--- takeHeadChunk lbs =
---   case lbs of
---     (BL.Chunk bs _) -> Just bs
---     _ -> Nothing
+--takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString
+--takeHeadChunk lbs =
+--  case lbs of
+--    (BL.Chunk bs _) -> Just bs
+--    _ -> Nothing
 --
--- dropHeadChunk :: BL.ByteString -> BL.ByteString
--- dropHeadChunk lbs =
---   case lbs of
---     (BL.Chunk _ lbs') -> lbs'
---     _ -> BL.Empty
--- @
+--dropHeadChunk :: BL.ByteString -> BL.ByteString
+--dropHeadChunk lbs =
+--  case lbs of
+--    (BL.Chunk _ lbs') -> lbs'
+--    _ -> BL.Empty
+--@
 --
 -- The @lazyIOExample@ uses lazy I/O to read the file from the disk, which is
 -- not suitable in all applications, and certainly not if you need to read



More information about the ghc-commits mailing list