Hello community,

here is the log from the commit of package ghc-vector-binary-instances for 
openSUSE:Factory checked in at 2016-03-16 10:36:19
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-vector-binary-instances (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-vector-binary-instances.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-vector-binary-instances"

Changes:
--------
--- 
/work/SRC/openSUSE:Factory/ghc-vector-binary-instances/ghc-vector-binary-instances.changes
  2015-11-26 17:03:21.000000000 +0100
+++ 
/work/SRC/openSUSE:Factory/.ghc-vector-binary-instances.new/ghc-vector-binary-instances.changes
     2016-03-16 10:36:37.000000000 +0100
@@ -1,0 +2,15 @@
+Tue Mar 15 07:40:08 UTC 2016 - mimi...@gmail.com
+
+- update to 0.2.3.1 
+
+-------------------------------------------------------------------
+Sat Mar 12 09:36:08 UTC 2016 - mimi...@gmail.com
+
+- update to 0.2.3.0 
+
+-------------------------------------------------------------------
+Sat Mar 12 09:32:39 UTC 2016 - mimi...@gmail.com
+
+- update to 0.2.1.1 
+
+-------------------------------------------------------------------

Old:
----
  vector-binary-instances-0.2.1.0.tar.gz

New:
----
  vector-binary-instances-0.2.3.1.tar.gz

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

Other differences:
------------------
++++++ ghc-vector-binary-instances.spec ++++++
--- /var/tmp/diff_new_pack.7Ym08w/_old  2016-03-16 10:36:38.000000000 +0100
+++ /var/tmp/diff_new_pack.7Ym08w/_new  2016-03-16 10:36:38.000000000 +0100
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-vector-binary-instances
 #
-# Copyright (c) 2015 SUSE LINUX GmbH, Nuernberg, Germany.
+# Copyright (c) 2016 SUSE LINUX GmbH, Nuernberg, Germany.
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -15,15 +15,16 @@
 # Please submit bugfixes or comments via http://bugs.opensuse.org/
 #
 
+
 %global pkg_name vector-binary-instances
 
 Name:           ghc-vector-binary-instances
-Version:        0.2.1.0
+Version:        0.2.3.1
 Release:        0
 Summary:        Instances of Data.Binary and Data.Serialize for vector
+License:        BSD-3-Clause
 Group:          System/Libraries
 
-License:        BSD-3-Clause
 Url:            https://hackage.haskell.org/package/%{pkg_name}
 Source0:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz
 BuildRoot:      %{_tmppath}/%{name}-%{version}-build
@@ -70,30 +71,23 @@
 %prep
 %setup -q -n %{pkg_name}-%{version}
 
-
 %build
 %ghc_lib_build
 
-
 %install
 %ghc_lib_install
 
-
 %post devel
 %ghc_pkg_recache
 
-
 %postun devel
 %ghc_pkg_recache
 
-
 %files -f %{name}.files
 %defattr(-,root,root,-)
 %doc LICENSE
 
-
 %files devel -f %{name}-devel.files
 %defattr(-,root,root,-)
 
-
 %changelog

++++++ vector-binary-instances-0.2.1.0.tar.gz -> 
vector-binary-instances-0.2.3.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/vector-binary-instances-0.2.1.0/Data/Vector/Binary.hs 
new/vector-binary-instances-0.2.3.1/Data/Vector/Binary.hs
--- old/vector-binary-instances-0.2.1.0/Data/Vector/Binary.hs   2013-04-14 
06:25:20.000000000 +0200
+++ new/vector-binary-instances-0.2.3.1/Data/Vector/Binary.hs   2016-03-13 
12:20:32.000000000 +0100
@@ -1,5 +1,4 @@
-{-# LANGUAGE FlexibleInstances    #-}
-{-# LANGUAGE UndecidableInstances #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
 --------------------------------------------------------------------
 -- |
 -- Module    : Data.Vector.Binary
@@ -15,6 +14,13 @@
 -- making it easy to serialize vectors to and from disk. We use the
 -- generic interface to vectors, so all vector types are supported.
 --
+-- All functions in this module use same data format. Different
+-- representations for vector length and its elements could be used
+-- but general shape is same.
+--
+-- > [number of elements]
+-- > [vector element    ] : N times
+--
 -- To serialize a vector:
 --
 -- > *Data.Vector.Binary> let v = Data.Vector.fromList [1..10]
@@ -29,71 +35,86 @@
 -- > Chunk "\US\139\b\NUL\NUL\N...\229\240,\254:\NUL\NUL\NUL" Empty
 --
 --------------------------------------------------------------------
-
-module Data.Vector.Binary () where
+module Data.Vector.Binary (
+    genericGetVector
+  , genericGetVectorWith
+  , genericPutVector
+  , genericPutVectorWith
+  ) where
 
 import Data.Binary
-import Control.Monad
 
-import qualified Data.Vector.Generic as G
-import qualified Data.Vector.Unboxed as U
-import qualified Data.Vector.Storable as S
+import qualified Data.Vector.Generic   as G
+import qualified Data.Vector.Generic.Mutable as GM
+import qualified Data.Vector.Unboxed   as U
+import qualified Data.Vector.Storable  as S
+import qualified Data.Vector.Primitive as P
 import Data.Vector (Vector)
-
 import System.IO.Unsafe
-import qualified Data.Vector.Generic.Mutable as M
+
 import Foreign.Storable (Storable)
 
 -- Enumerate the instances to avoid the nasty overlapping instances.
 
 -- | Boxed, generic vectors.
 instance Binary a => Binary (Vector a) where
-    put = putGeneric
-    get = getGeneric
+    put = genericPutVector
+    get = genericGetVector
     {-# INLINE get #-}
 
 -- | Unboxed vectors
 instance (U.Unbox a, Binary a) => Binary (U.Vector a) where
-    put = putGeneric
-    get = getGeneric
+    put = genericPutVector
+    get = genericGetVector
+    {-# INLINE get #-}
+
+-- | Primitive vectors
+instance (P.Prim a, Binary a) => Binary (P.Vector a) where
+    put = genericPutVector
+    get = genericGetVector
     {-# INLINE get #-}
 
 -- | Storable vectors
 instance (Storable a, Binary a) => Binary (S.Vector a) where
-    put = putGeneric
-    get = getGeneric
+    put = genericPutVector
+    get = genericGetVector
     {-# INLINE get #-}
 
 ------------------------------------------------------------------------
 
--- this is morally sound, if very awkward.
--- all effects are contained, and can't escape the unsafeFreeze
-getGeneric :: (G.Vector v a, Binary a) => Get (v a)
-{-# INLINE getGeneric #-}
-getGeneric = do
-    n  <- get
-
-    -- new unitinialized array
-    mv <- lift $ M.new n
-
-    let fill i
-            | i < n = do
-                x <- get
-                (unsafePerformIO $ M.unsafeWrite mv i x) `seq` return ()
-                fill (i+1)
-
-            | otherwise = return ()
-
-    fill 0
-
-    lift $ G.unsafeFreeze mv
+-- | Deserialize vector using custom parsers.
+genericGetVectorWith :: (G.Vector v a, Binary a)
+    => Get Int       -- ^ Parser for vector size
+    -> Get a         -- ^ Parser for vector's element
+    -> Get (v a)
+{-# INLINE genericGetVectorWith #-}
+genericGetVectorWith getN getA = do
+    n <- getN
+    v <- return $ unsafePerformIO $ GM.unsafeNew n
+    let go 0 = return ()
+        go i = do x <- getA
+                  () <- return $ unsafePerformIO $ GM.unsafeWrite v (n-i) x
+                  go (i-1)
+    () <- go n
+    return $ unsafePerformIO $ G.unsafeFreeze v
+
+-- | Generic put for anything in the G.Vector class which uses custom
+--   encoders.
+genericPutVectorWith :: (G.Vector v a, Binary a)
+    => (Int -> Put)  -- ^ Encoder for vector size
+    -> (a   -> Put)  -- ^ Encoder for vector's element
+    -> v a -> Put
+{-# INLINE genericPutVectorWith #-}
+genericPutVectorWith putN putA v = do
+    putN (G.length v)
+    G.mapM_ putA v
+
+-- | Generic function for vector deserialization.
+genericGetVector :: (G.Vector v a, Binary a) => Get (v a)
+{-# INLINE genericGetVector #-}
+genericGetVector = genericGetVectorWith get get
 
 -- | Generic put for anything in the G.Vector class.
-putGeneric :: (G.Vector v a, Binary a) => v a -> Put
-{-# INLINE putGeneric #-}
-putGeneric v = do
-    put (G.length v)
-    G.mapM_ put v
-
-lift :: IO b -> Get b
-lift = return .unsafePerformIO
+genericPutVector :: (G.Vector v a, Binary a) => v a -> Put
+{-# INLINE genericPutVector #-}
+genericPutVector = genericPutVectorWith put put
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/vector-binary-instances-0.2.1.0/Data/Vector/Cereal.hs 
new/vector-binary-instances-0.2.3.1/Data/Vector/Cereal.hs
--- old/vector-binary-instances-0.2.1.0/Data/Vector/Cereal.hs   2013-04-14 
06:25:20.000000000 +0200
+++ new/vector-binary-instances-0.2.3.1/Data/Vector/Cereal.hs   1970-01-01 
01:00:00.000000000 +0100
@@ -1,84 +0,0 @@
-{-# LANGUAGE FlexibleInstances    #-}
-{-# LANGUAGE UndecidableInstances #-}
---------------------------------------------------------------------
--- |
--- Module    : Data.Vector.Cereal
--- Copyright : (c) Don Stewart 2010-2012
-
--- License   : BSD3
---
--- Maintainer: Don Stewart <don...@gmail.com>
--- Stability : provisional
--- Portability: GHC only
---
--- Instances for Serialize for the types defined in the vector package,
--- making it easy to serialize vectors to and from disk. We use the
--- generic interface to vectors, so all vector types are supported.
---
---------------------------------------------------------------------
-
-module Data.Vector.Cereal () where
-
-import Data.Serialize
-import Control.Monad
-
-import qualified Data.Vector.Generic as G
-import qualified Data.Vector.Unboxed as U
-import qualified Data.Vector.Storable as S
-import Data.Vector (Vector)
-
-import System.IO.Unsafe
-import qualified Data.Vector.Generic.Mutable as M
-import Foreign.Storable (Storable)
-
--- | Boxed, generic vectors.
-instance Serialize a => Serialize (Vector a) where
-    put = putGeneric
-    get = getGeneric
-    {-# INLINE get #-}
-
--- | Unboxed vectors
-instance (U.Unbox a, Serialize a) => Serialize (U.Vector a) where
-    put = putGeneric
-    get = getGeneric
-    {-# INLINE get #-}
-
--- | Storable vectors
-instance (Storable a, Serialize a) => Serialize (S.Vector a) where
-    put = putGeneric
-    get = getGeneric
-    {-# INLINE get #-}
-
-------------------------------------------------------------------------
-
--- this is morally sound, if very awkward.
--- all effects are contained, and can't escape the unsafeFreeze
-getGeneric :: (G.Vector v a, Serialize a) => Get (v a)
-{-# INLINE getGeneric #-}
-getGeneric = do
-    n  <- get
-
-    -- new unitinialized array
-    mv <- lift $ M.new n
-
-    let fill i
-            | i < n = do
-                x <- get
-                (unsafePerformIO $ M.unsafeWrite mv i x) `seq` return ()
-                fill (i+1)
-
-            | otherwise = return ()
-
-    fill 0
-
-    lift $ G.unsafeFreeze mv
-
--- | Generic put for anything in the G.Vector class.
-putGeneric :: (G.Vector v a, Serialize a) => v a -> Put
-{-# INLINE putGeneric #-}
-putGeneric v = do
-    put (G.length v)
-    G.mapM_ put v
-
-lift :: IO b -> Get b
-lift = return .unsafePerformIO
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/vector-binary-instances-0.2.1.0/benchmarks/Benchmarks.hs 
new/vector-binary-instances-0.2.3.1/benchmarks/Benchmarks.hs
--- old/vector-binary-instances-0.2.1.0/benchmarks/Benchmarks.hs        
1970-01-01 01:00:00.000000000 +0100
+++ new/vector-binary-instances-0.2.3.1/benchmarks/Benchmarks.hs        
2016-03-13 12:20:32.000000000 +0100
@@ -0,0 +1,62 @@
+import Criterion.Main
+import Data.Binary
+import Data.Binary.Get
+
+import qualified Data.ByteString.Lazy     as BS
+import qualified Data.Vector.Unboxed as U
+import Data.Vector.Binary
+
+
+vec1,vec2,vec3,vec4,vec5 :: U.Vector Int
+vec1 = U.enumFromN 0 3
+vec2 = U.enumFromN 0 30
+vec3 = U.enumFromN 0 300
+vec4 = U.enumFromN 0 30000
+vec5 = U.enumFromN 0 300000
+
+bs1,bs2,bs3,bs4,bs5 :: BS.ByteString
+bs1 = encode vec1
+bs2 = encode vec2
+bs3 = encode vec3
+bs4 = encode vec4
+bs5 = encode vec5
+
+naiveGet :: (Binary a, U.Unbox a) => Get (U.Vector a)
+naiveGet = do
+    n <- get
+    U.replicateM n get
+
+naiveGet' :: (Binary a, U.Unbox a) => Get (U.Vector a)
+naiveGet' = do
+    n <- get
+    U.replicateM n get
+-- A feeble attempt at simulating what will happen if we end up with a 
situation
+-- where we are unable to specialize to the element type
+{-# NOINLINE naiveGet' #-}
+
+type V = BS.ByteString -> U.Vector Int
+
+benchGetSize :: String -> BS.ByteString -> Benchmark
+benchGetSize name bs = bgroup name
+    [ bench "U.Vector Int"                 $ nf (decode :: V) bs
+    , bench "naive U.Vector Int"           $ nf (runGet naiveGet :: V) bs
+    , bench "noinline naive U.Vector Int"  $ nf (runGet naiveGet' :: V) bs
+    ]
+
+main = defaultMain
+  [ bgroup "encode"
+    [ bench "U.Vector Int 3"      $ nf encode vec1
+    , bench "U.Vector Int 30"     $ nf encode vec2
+    , bench "U.Vector Int 300"    $ nf encode vec3
+    , bench "U.Vector Int 30000"  $ nf encode vec4
+    , bench "U.Vector Int 300000" $ nf encode vec5
+    ]
+  , bgroup "decode"
+    [ benchGetSize "size=3" bs1
+    , benchGetSize "size=30" bs2
+    , benchGetSize "size=300" bs3
+    , benchGetSize "size=30000" bs4
+    , benchGetSize "size=300000" bs5
+    ]
+  ]
+
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-binary-instances-0.2.1.0/test/Main.hs 
new/vector-binary-instances-0.2.3.1/test/Main.hs
--- old/vector-binary-instances-0.2.1.0/test/Main.hs    1970-01-01 
01:00:00.000000000 +0100
+++ new/vector-binary-instances-0.2.3.1/test/Main.hs    2016-03-13 
12:20:32.000000000 +0100
@@ -0,0 +1,24 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
+import Test.Tasty
+import Test.Tasty.QuickCheck
+import Data.Binary
+import Data.Vector.Binary
+import qualified Data.Vector as V
+import qualified Data.Vector.Generic as VG
+import qualified Data.Vector.Unboxed as VU
+import qualified Data.Vector.Storable as VS
+
+roundTrip :: forall v a. (Eq (v a), Binary (v a), VG.Vector v a)
+          => v a -> Property
+roundTrip v =
+    let v' = decode $ encode v :: v a
+    in property $ v' == v
+
+main = defaultMain $ testGroup "Vector Binary instances"
+    [ testProperty "Unboxed"  $ roundTrip $ VU.enumFromTo z 100
+    , testProperty "Storable" $ roundTrip $ VS.enumFromTo z 100
+    , testProperty "Boxed"    $ roundTrip $ V.enumFromTo  z 100
+    ]
+  where
+    z = 0 :: Int
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/vector-binary-instances-0.2.1.0/vector-binary-instances.cabal 
new/vector-binary-instances-0.2.3.1/vector-binary-instances.cabal
--- old/vector-binary-instances-0.2.1.0/vector-binary-instances.cabal   
2013-04-14 06:25:20.000000000 +0200
+++ new/vector-binary-instances-0.2.3.1/vector-binary-instances.cabal   
2016-03-13 12:20:32.000000000 +0100
@@ -1,18 +1,6 @@
--- binary-vector-instances.cabal auto-generated by cabal init. For
--- additional options, see
--- 
http://www.haskell.org/cabal/release/cabal-latest/doc/users-guide/authors.html#pkg-descr.
--- The name of the package.
 Name:                vector-binary-instances
-
--- The package version. See the Haskell package versioning policy
--- (http://www.haskell.org/haskellwiki/Package_versioning_policy) for
--- standards guiding when and how versions should be incremented.
-Version:             0.2.1.0
-
--- A short (one-line) description of the package.
+Version:             0.2.3.1
 Synopsis:            Instances of Data.Binary and Data.Serialize for vector
-
--- A longer description of the package.
 Description:
    Instances for Binary for the types defined in the vector package,
    making it easy to serialize vectors to and from disk. We use the
@@ -36,50 +24,57 @@
 -- URL for the project homepage or repository.
 Homepage:            https://github.com/bos/vector-binary-instances
 bug-reports:         https://github.com/bos/vector-binary-instances/issues
-
--- The license under which the package is released.
 License:             BSD3
-
--- The file containing the license text.
 License-file:        LICENSE
-
--- The package author(s).
 Author:              Don Stewart
-
--- An email address to which users can send suggestions, bug reports,
--- and patches.
-Maintainer:          don...@gmail.com, b...@serpentine.com
+Maintainer:          don...@gmail.com, b...@serpentine.com, Ben Gamari 
<b...@smart-cactus.org>
 
 -- A copyright notice.
 -- Copyright:
 
 -- Stability of the pakcage (experimental, provisional, stable...)
 Stability:           Experimental
-
 Category:            Data
-
 Build-type:          Simple
 
--- Extra files to be distributed with the package, such as examples or
--- a README.
--- Extra-source-files:
-
 -- Constraint on the version of Cabal needed to build this package.
-Cabal-version:       >=1.6
+Cabal-version:       >=1.8
 
 
 Library
+  Ghc-options: -Wall
   -- Modules exported by the library.
   Exposed-modules:
-    Data.Vector.Binary,
-    Data.Vector.Cereal
+    Data.Vector.Binary
 
   -- Packages needed in order to build this package.
   Build-depends:
-    base > 3 && < 6,
-    vector >= 0.6,
+    base > 3 && < 4.10,
+    vector >= 0.6 && < 0.12,
+    binary >= 0.7 && < 0.9
+
+Benchmark benchmarks
+  Type:           exitcode-stdio-1.0
+  Main-is:        Benchmarks.hs
+  Build-depends:
+    base,
+    vector-binary-instances,
+    vector,
+    bytestring,
+    binary,
+    criterion
+  hs-source-dirs: benchmarks
+
+Test-Suite tests
+  Type:           exitcode-stdio-1.0
+  Main-is:        test/Main.hs
+  Build-depends:
+    base,
+    vector-binary-instances,
+    vector,
     binary,
-    cereal
+    tasty,
+    tasty-quickcheck
 
 source-repository head
   type:     git


Reply via email to