Repository : ssh://darcs.haskell.org//srv/darcs/packages/bytestring

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3011df8d7adc383c07fb83f6b6fea87c1b91cc3c

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

commit 3011df8d7adc383c07fb83f6b6fea87c1b91cc3c
Author: Duncan Coutts <[email protected]>
Date:   Thu Sep 20 08:37:08 2012 +0000

    Add a show instance for Builder just for convenience

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

 Data/ByteString/Builder/Internal.hs |    9 +++++++++
 1 files changed, 9 insertions(+), 0 deletions(-)

diff --git a/Data/ByteString/Builder/Internal.hs 
b/Data/ByteString/Builder/Internal.hs
index fdfea77..264ae38 100644
--- a/Data/ByteString/Builder/Internal.hs
+++ b/Data/ByteString/Builder/Internal.hs
@@ -297,6 +297,15 @@ instance Monoid Builder where
   {-# INLINE mconcat #-}
   mconcat = foldr mappend mempty
 
+instance Show Builder where
+  show = show . showBuilder
+
+{-# NOINLINE showBuilder #-} -- ensure code is shared
+showBuilder :: Builder -> L.ByteString
+showBuilder = toLazyByteStringWith
+    (safeStrategy L.smallChunkSize L.smallChunkSize) L.Empty
+
+
 -- | Flush the current buffer. This introduces a chunk boundary.
 --
 {-# INLINE flush #-}



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to