Hello community,

here is the log from the commit of package ghc-cereal for openSUSE:Factory 
checked in at 2016-12-06 14:24:20
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-cereal (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-cereal.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-cereal"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-cereal/ghc-cereal.changes    2016-10-22 
13:20:10.000000000 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-cereal.new/ghc-cereal.changes       
2016-12-06 14:24:20.000000000 +0100
@@ -1,0 +2,5 @@
+Mon Nov 14 09:30:03 UTC 2016 - psim...@suse.com
+
+- Update to version 0.5.4.0 with cabal2obs.
+
+-------------------------------------------------------------------

Old:
----
  cereal-0.5.3.0.tar.gz

New:
----
  cereal-0.5.4.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-cereal.spec ++++++
--- /var/tmp/diff_new_pack.IZDecf/_old  2016-12-06 14:24:21.000000000 +0100
+++ /var/tmp/diff_new_pack.IZDecf/_new  2016-12-06 14:24:21.000000000 +0100
@@ -19,7 +19,7 @@
 %global pkg_name cereal
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.5.3.0
+Version:        0.5.4.0
 Release:        0
 Summary:        A binary serialization library
 License:        BSD-3-Clause

++++++ cereal-0.5.3.0.tar.gz -> cereal-0.5.4.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cereal-0.5.3.0/cereal.cabal 
new/cereal-0.5.4.0/cereal.cabal
--- old/cereal-0.5.3.0/cereal.cabal     2016-07-22 20:26:13.000000000 +0200
+++ new/cereal-0.5.4.0/cereal.cabal     2016-11-09 01:40:53.000000000 +0100
@@ -1,5 +1,5 @@
 name:                   cereal
-version:                0.5.3.0
+version:                0.5.4.0
 license:                BSD3
 license-file:           LICENSE
 author:                 Lennart Kolmodin <kolmo...@dtek.chalmers.se>,
@@ -25,16 +25,29 @@
   type:     git
   location: git://github.com/GaloisInc/cereal.git
 
+flag bytestring-builder
+  description:
+    Decides whether to use an older version of bytestring along with 
bytestring-builder or just a newer version of bytestring.
+    .
+    This flag normally toggles automatically but you can use 
`-fbytestring-builder` or `-f-bytestring-builder` to explicitly change it.
+  default: False
+  manual: False
+
 library
         default-language:       Haskell2010
 
-        build-depends:          bytestring >= 0.10.2.0,
-                                base >= 4.4 && < 5, containers, array,
+        build-depends:          base >= 4.4 && < 5, containers, array,
                                 ghc-prim >= 0.2
 
         if !impl(ghc >= 8.0)
           build-depends:        fail == 4.9.*
 
+        if flag(bytestring-builder)
+          build-depends:        bytestring >= 0.9    && < 0.10.4,
+                                bytestring-builder >= 0.10.4 && < 1
+        else
+          build-depends:        bytestring >= 0.10.4 && < 1
+
         hs-source-dirs:         src
 
         exposed-modules:        Data.Serialize,
@@ -52,7 +65,7 @@
         type:                   exitcode-stdio-1.0
 
         build-depends:          base == 4.*,
-                                bytestring >= 0.10.8.1,
+                                bytestring >= 0.9,
                                 QuickCheck,
                                 test-framework,
                                 test-framework-quickcheck2,
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cereal-0.5.3.0/src/Data/Serialize/Get.hs 
new/cereal-0.5.4.0/src/Data/Serialize/Get.hs
--- old/cereal-0.5.3.0/src/Data/Serialize/Get.hs        2016-07-22 
20:26:13.000000000 +0200
+++ new/cereal-0.5.4.0/src/Data/Serialize/Get.hs        2016-11-09 
01:40:53.000000000 +0100
@@ -59,10 +59,7 @@
     -- ** ByteStrings
     , getByteString
     , getLazyByteString
-
-#if MIN_VERSION_bytestring(0,10,4)
     , getShortByteString
-#endif
 
     -- ** Big-endian reads
     , getWord16be
@@ -116,6 +113,7 @@
 import qualified Data.ByteString.Internal as B
 import qualified Data.ByteString.Unsafe   as B
 import qualified Data.ByteString.Lazy     as L
+import qualified Data.ByteString.Short    as BS
 import qualified Data.IntMap              as IntMap
 import qualified Data.IntSet              as IntSet
 import qualified Data.Map                 as Map
@@ -123,12 +121,6 @@
 import qualified Data.Set                 as Set
 import qualified Data.Tree                as T
 
-
-#if MIN_VERSION_bytestring(0,10,4)
-import qualified Data.ByteString.Short as BS
-#endif
-
-
 #if defined(__GLASGOW_HASKELL__) && !defined(__HADDOCK__)
 import GHC.Base
 import GHC.Word
@@ -511,12 +503,10 @@
 getLazyByteString n = f `fmap` getByteString (fromIntegral n)
   where f bs = L.fromChunks [bs]
 
-#if MIN_VERSION_bytestring(0,10,4)
 getShortByteString :: Int -> Get BS.ShortByteString
 getShortByteString n = do
   bs <- getBytes n
   return $! BS.toShort bs
-#endif
 
 
 ------------------------------------------------------------------------
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cereal-0.5.3.0/src/Data/Serialize/Put.hs 
new/cereal-0.5.4.0/src/Data/Serialize/Put.hs
--- old/cereal-0.5.3.0/src/Data/Serialize/Put.hs        2016-07-22 
20:26:13.000000000 +0200
+++ new/cereal-0.5.4.0/src/Data/Serialize/Put.hs        2016-11-09 
01:40:53.000000000 +0100
@@ -1,3 +1,4 @@
+{-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE FlexibleInstances #-}
 
@@ -14,7 +15,7 @@
 -- Module      : Data.Serialize.Put
 -- Copyright   : Lennart Kolmodin, Galois Inc. 2009
 -- License     : BSD3-style (see LICENSE)
--- 
+--
 -- Maintainer  : Trevor Elliott <tre...@galois.com>
 -- Stability   :
 -- Portability :
@@ -41,28 +42,36 @@
 
     -- * Primitives
     , putWord8
+    , putInt8
     , putByteString
     , putLazyByteString
-
-#if MIN_VERSION_bytestring(0,10,4)
     , putShortByteString
-#endif
 
     -- * Big-endian primitives
     , putWord16be
     , putWord32be
     , putWord64be
+    , putInt16be
+    , putInt32be
+    , putInt64be
 
     -- * Little-endian primitives
     , putWord16le
     , putWord32le
     , putWord64le
+    , putInt16le
+    , putInt32le
+    , putInt64le
 
     -- * Host-endian, unaligned writes
     , putWordhost
     , putWord16host
     , putWord32host
     , putWord64host
+    , putInthost
+    , putInt16host
+    , putInt32host
+    , putInt64host
 
     -- * Containers
     , putTwoOf
@@ -81,27 +90,17 @@
   ) where
 
 
-#if MIN_VERSION_bytestring(0,10,2)
 import           Data.ByteString.Builder (Builder, toLazyByteString)
 import qualified Data.ByteString.Builder as B
 import qualified Data.ByteString.Builder.Extra as B
-#elif MIN_VERSION_bytestring(0,10,0)
-import           Data.ByteString.Lazy.Builder (Builder, toLazyByteString)
-import qualified Data.ByteString.Lazy.Builder as B
-import qualified Data.ByteString.Lazy.Builder.Extras as B
-#else
-#error "cereal requires bytestring >= 0.10.0.0"
-#endif
-
-#if MIN_VERSION_bytestring(0,10,4)
 import qualified Data.ByteString.Short as BS
-#endif
 
 import qualified Control.Applicative as A
 import Data.Array.Unboxed
 import qualified Data.Monoid as M
 import qualified Data.Foldable as F
 import Data.Word
+import Data.Int
 import qualified Data.ByteString        as S
 import qualified Data.ByteString.Lazy   as L
 import qualified Data.IntMap            as IntMap
@@ -117,9 +116,17 @@
 import Data.Monoid
 #endif
 
+#if !(MIN_VERSION_bytestring(0,10,0))
+import Foreign.ForeignPtr (withForeignPtr)
+import Foreign.Marshal.Utils (copyBytes)
+import Foreign.Ptr (plusPtr)
+import qualified Data.ByteString.Internal as S
+import qualified Data.ByteString.Lazy.Internal as L
+#endif
+
 ------------------------------------------------------------------------
 
--- XXX Strict in builder only. 
+-- XXX Strict in builder only.
 data PairS a = PairS a !Builder
 
 sndS :: PairS a -> Builder
@@ -190,12 +197,12 @@
 
 -- | Run the 'Put' monad with a serialiser
 runPut :: Put -> S.ByteString
-runPut = L.toStrict . runPutLazy
+runPut = lazyToStrictByteString . runPutLazy
 {-# INLINE runPut #-}
 
 -- | Run the 'Put' monad with a serialiser and get its result
 runPutM :: PutM a -> (a, S.ByteString)
-runPutM (Put (PairS f s)) = (f, L.toStrict (toLazyByteString s))
+runPutM (Put (PairS f s)) = (f, lazyToStrictByteString (toLazyByteString s))
 {-# INLINE runPutM #-}
 
 -- | Run the 'Put' monad with a serialiser
@@ -221,16 +228,19 @@
 putWord8            = tell . B.word8
 {-# INLINE putWord8 #-}
 
+-- | Efficiently write an int into the output buffer
+putInt8             :: Putter Int8
+putInt8             = tell . B.int8
+{-# INLINE putInt8 #-}
+
 -- | An efficient primitive to write a strict ByteString into the output 
buffer.
 -- It flushes the current buffer, and writes the argument into a new chunk.
 putByteString       :: Putter S.ByteString
 putByteString       = tell . B.byteString
 {-# INLINE putByteString #-}
 
-#if MIN_VERSION_bytestring(0,10,4)
 putShortByteString  :: Putter BS.ShortByteString
 putShortByteString   = tell . B.shortByteString
-#endif
 
 -- | Write a lazy ByteString efficiently, simply appending the lazy
 -- ByteString chunks to the output buffer
@@ -299,6 +309,67 @@
 putWord64host       = tell . B.word64Host
 {-# INLINE putWord64host #-}
 
+-- | Write a Int16 in big endian format
+putInt16be         :: Putter Int16
+putInt16be         = tell . B.int16BE
+{-# INLINE putInt16be #-}
+
+-- | Write a Int16 in little endian format
+putInt16le         :: Putter Int16
+putInt16le         = tell . B.int16LE
+{-# INLINE putInt16le #-}
+
+-- | Write a Int32 in big endian format
+putInt32be         :: Putter Int32
+putInt32be         = tell . B.int32BE
+{-# INLINE putInt32be #-}
+
+-- | Write a Int32 in little endian format
+putInt32le         :: Putter Int32
+putInt32le         = tell . B.int32LE
+{-# INLINE putInt32le #-}
+
+-- | Write a Int64 in big endian format
+putInt64be         :: Putter Int64
+putInt64be         = tell . B.int64BE
+{-# INLINE putInt64be #-}
+
+-- | Write a Int64 in little endian format
+putInt64le         :: Putter Int64
+putInt64le         = tell . B.int64LE
+{-# INLINE putInt64le #-}
+
+------------------------------------------------------------------------
+
+-- | /O(1)./ Write a single native machine int. The int is
+-- written in host order, host endian form, for the machine you're on.
+-- On a 64 bit machine the Int is an 8 byte value, on a 32 bit machine,
+-- 4 bytes. Values written this way are not portable to
+-- different endian or int sized machines, without conversion.
+--
+putInthost         :: Putter Int
+putInthost         = tell . B.intHost
+{-# INLINE putInthost #-}
+
+-- | /O(1)./ Write a Int16 in native host order and host endianness.
+-- For portability issues see @putInthost@.
+putInt16host       :: Putter Int16
+putInt16host       = tell . B.int16Host
+{-# INLINE putInt16host #-}
+
+-- | /O(1)./ Write a Int32 in native host order and host endianness.
+-- For portability issues see @putInthost@.
+putInt32host       :: Putter Int32
+putInt32host       = tell . B.int32Host
+{-# INLINE putInt32host #-}
+
+-- | /O(1)./ Write a Int64 in native host order
+-- On a 32 bit machine we write two host order Int32s, in big endian form.
+-- For portability issues see @putInthost@.
+putInt64host       :: Putter Int64
+putInt64host       = tell . B.int64Host
+{-# INLINE putInt64host #-}
+
 
 -- Containers 
------------------------------------------------------------------
 
@@ -326,12 +397,12 @@
 
 putSeqOf :: Putter a -> Putter (Seq.Seq a)
 putSeqOf pa = \s -> do
-    putWord64be (fromIntegral $ Seq.length s) 
+    putWord64be (fromIntegral $ Seq.length s)
     F.mapM_ pa s
 {-# INLINE putSeqOf #-}
 
 putTreeOf :: Putter a -> Putter (T.Tree a)
-putTreeOf pa = 
+putTreeOf pa =
     tell . go
   where
     go (T.Node x cs) = execPut (pa x) `M.mappend` encodeListOf go cs
@@ -370,3 +441,27 @@
     let bs = runPut putVal
     putLen (S.length bs)
     putByteString bs
+
+-------------------------------------------------------------------------------
+-- pre-bytestring-0.10 compatibility
+-------------------------------------------------------------------------------
+
+{-# INLINE lazyToStrictByteString #-}
+lazyToStrictByteString :: L.ByteString -> S.ByteString
+#if MIN_VERSION_bytestring(0,10,0)
+lazyToStrictByteString = L.toStrict
+#else
+lazyToStrictByteString = packChunks
+
+-- packChunks is taken from the blaze-builder package.
+
+-- | Pack the chunks of a lazy bytestring into a single strict bytestring.
+packChunks :: L.ByteString -> S.ByteString
+packChunks lbs = S.unsafeCreate (fromIntegral $ L.length lbs) (copyChunks lbs)
+  where
+    copyChunks !L.Empty                         !_pf = return ()
+    copyChunks !(L.Chunk (S.PS fpbuf o l) lbs') !pf  = do
+        withForeignPtr fpbuf $ \pbuf ->
+            copyBytes pf (pbuf `plusPtr` o) l
+        copyChunks lbs' (pf `plusPtr` l)
+#endif
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cereal-0.5.3.0/src/Data/Serialize.hs 
new/cereal-0.5.4.0/src/Data/Serialize.hs
--- old/cereal-0.5.3.0/src/Data/Serialize.hs    2016-07-22 20:26:13.000000000 
+0200
+++ new/cereal-0.5.4.0/src/Data/Serialize.hs    2016-11-09 01:40:53.000000000 
+0100
@@ -16,7 +16,7 @@
 -- Module      : Data.Serialize
 -- Copyright   : Lennart Kolmodin, Galois Inc. 2009
 -- License     : BSD3-style (see LICENSE)
--- 
+--
 -- Maintainer  : Trevor Elliott <tre...@galois.com>
 -- Stability   :
 -- Portability :
@@ -199,23 +199,23 @@
 
 -- Int8s are written as a single byte.
 instance Serialize Int8 where
-    put i   = put (fromIntegral i :: Word8)
-    get     = liftM fromIntegral (get :: Get Word8)
+    put     = putInt8
+    get     = getInt8
 
 -- Int16s are written as a 2 bytes in big endian format
 instance Serialize Int16 where
-    put i   = put (fromIntegral i :: Word16)
-    get     = liftM fromIntegral (get :: Get Word16)
+    put     = putInt16be
+    get     = getInt16be
 
 -- Int32s are written as a 4 bytes in big endian format
 instance Serialize Int32 where
-    put i   = put (fromIntegral i :: Word32)
-    get     = liftM fromIntegral (get :: Get Word32)
+    put     = putInt32be
+    get     = getInt32be
 
 -- Int64s are written as a 8 bytes in big endian format
 instance Serialize Int64 where
-    put i   = put (fromIntegral i :: Word64)
-    get     = liftM fromIntegral (get :: Get Word64)
+    put     = putInt64be
+    get     = getInt64be
 
 ------------------------------------------------------------------------
 
@@ -230,7 +230,7 @@
     get     = liftM fromIntegral (get :: Get Int64)
 
 ------------------------------------------------------------------------
--- 
+--
 -- Portable, and pretty efficient, serialisation of Integer
 --
 
@@ -312,7 +312,7 @@
 
 ------------------------------------------------------------------------
 
--- Safely wrap `chr` to avoid exceptions. 
+-- Safely wrap `chr` to avoid exceptions.
 -- `chr` source: 
http://hackage.haskell.org/package/base-4.7.0.2/docs/src/GHC-Char.html#chr
 chrEither :: Int -> Either String Char
 chrEither i
@@ -362,7 +362,7 @@
                                 return (z .|. shiftL6 (y .|. shiftL6
                                         (x .|. shiftL6 (xor 0xf0 w))))
         case chrEither r of
-            Right r' -> 
+            Right r' ->
                 return $! r'
             Left err ->
                 fail err
@@ -388,7 +388,7 @@
     put (a,b,c,d,e)     = put a >> put b >> put c >> put d >> put e
     get                 = liftM5 (,,,,) get get get get get
 
--- 
+--
 -- and now just recurse:
 --
 


Reply via email to