Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-vector for openSUSE:Factory 
checked in at 2021-10-12 21:49:10
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-vector (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-vector.new.2443 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-vector"

Tue Oct 12 21:49:10 2021 rev:29 rq:923802 version:0.12.3.1

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-vector/ghc-vector.changes    2021-09-10 
23:41:36.654578515 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-vector.new.2443/ghc-vector.changes  
2021-10-12 21:50:25.235963392 +0200
@@ -1,0 +2,12 @@
+Wed Sep 22 08:52:39 UTC 2021 - [email protected]
+
+- Update vector to version 0.12.3.1.
+  # Changes in version 0.12.3.1
+
+  * Bugfix for ghcjs and `Double` memset for `Storable` vector:
+    [#410](https://github.com/haskell/vector/issues/410)
+  * Avoid haddock bug: [#383](https://github.com/haskell/vector/issues/383)
+  * Improve haddock and doctests
+  * Disable problematic tests with -boundschecks 
[#407](https://github.com/haskell/vector/pull/407)
+
+-------------------------------------------------------------------

Old:
----
  vector-0.12.3.0.tar.gz
  vector.cabal

New:
----
  vector-0.12.3.1.tar.gz

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

Other differences:
------------------
++++++ ghc-vector.spec ++++++
--- /var/tmp/diff_new_pack.dpfmsH/_old  2021-10-12 21:50:25.819964228 +0200
+++ /var/tmp/diff_new_pack.dpfmsH/_new  2021-10-12 21:50:25.819964228 +0200
@@ -19,13 +19,12 @@
 %global pkg_name vector
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.12.3.0
+Version:        0.12.3.1
 Release:        0
 Summary:        Efficient Arrays
 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
-Source1:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/revision/2.cabal#/%{pkg_name}.cabal
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-deepseq-devel
 BuildRequires:  ghc-primitive-devel
@@ -78,7 +77,6 @@
 
 %prep
 %autosetup -n %{pkg_name}-%{version}
-cp -p %{SOURCE1} %{pkg_name}.cabal
 
 %build
 %ghc_lib_build

++++++ vector-0.12.3.0.tar.gz -> vector-0.12.3.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Generic/Mutable.hs 
new/vector-0.12.3.1/Data/Vector/Generic/Mutable.hs
--- old/vector-0.12.3.0/Data/Vector/Generic/Mutable.hs  2021-04-04 
16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector/Generic/Mutable.hs  2021-09-21 
18:02:15.000000000 +0200
@@ -85,134 +85,6 @@
 
 #include "vector.h"
 
-{-
-type family Immutable (v :: * -> * -> *) :: * -> *
-
--- | Class of mutable vectors parametrised with a primitive state token.
---
-class MBundle.Pointer u a => MVector v a where
-  -- | Length of the mutable vector. This method should not be
-  -- called directly, use 'length' instead.
-  basicLength       :: v s a -> Int
-
-  -- | Yield a part of the mutable vector without copying it. This method
-  -- should not be called directly, use 'unsafeSlice' instead.
-  basicUnsafeSlice :: Int  -- ^ starting index
-                   -> Int  -- ^ length of the slice
-                   -> v s a
-                   -> v s a
-
-  -- Check whether two vectors overlap. This method should not be
-  -- called directly, use 'overlaps' instead.
-  basicOverlaps    :: v s a -> v s a -> Bool
-
-  -- | Create a mutable vector of the given length. This method should not be
-  -- called directly, use 'unsafeNew' instead.
-  basicUnsafeNew   :: PrimMonad m => Int -> m (v (PrimState m) a)
-
-  -- | Create a mutable vector of the given length and fill it with an
-  -- initial value. This method should not be called directly, use
-  -- 'replicate' instead.
-  basicUnsafeReplicate :: PrimMonad m => Int -> a -> m (v (PrimState m) a)
-
-  -- | Yield the element at the given position. This method should not be
-  -- called directly, use 'unsafeRead' instead.
-  basicUnsafeRead  :: PrimMonad m => v (PrimState m) a -> Int -> m a
-
-  -- | Replace the element at the given position. This method should not be
-  -- called directly, use 'unsafeWrite' instead.
-  basicUnsafeWrite :: PrimMonad m => v (PrimState m) a -> Int -> a -> m ()
-
-  -- | Reset all elements of the vector to some undefined value, clearing all
-  -- references to external objects. This is usually a noop for unboxed
-  -- vectors. This method should not be called directly, use 'clear' instead.
-  basicClear       :: PrimMonad m => v (PrimState m) a -> m ()
-
-  -- | Set all elements of the vector to the given value. This method should
-  -- not be called directly, use 'set' instead.
-  basicSet         :: PrimMonad m => v (PrimState m) a -> a -> m ()
-
-  basicUnsafeCopyPointer :: PrimMonad m => v (PrimState m) a
-                                        -> Immutable v a
-                                        -> m ()
-
-  -- | Copy a vector. The two vectors may not overlap. This method should not
-  -- be called directly, use 'unsafeCopy' instead.
-  basicUnsafeCopy  :: PrimMonad m => v (PrimState m) a   -- ^ target
-                                  -> v (PrimState m) a   -- ^ source
-                                  -> m ()
-
-  -- | Move the contents of a vector. The two vectors may overlap. This method
-  -- should not be called directly, use 'unsafeMove' instead.
-  basicUnsafeMove  :: PrimMonad m => v (PrimState m) a   -- ^ target
-                                  -> v (PrimState m) a   -- ^ source
-                                  -> m ()
-
-  -- | Grow a vector by the given number of elements. This method should not be
-  -- called directly, use 'unsafeGrow' instead.
-  basicUnsafeGrow  :: PrimMonad m => v (PrimState m) a -> Int
-                                                       -> m (v (PrimState m) a)
-
-  {-# INLINE basicUnsafeReplicate #-}
-  basicUnsafeReplicate n x
-    = do
-        v <- basicUnsafeNew n
-        basicSet v x
-        return v
-
-  {-# INLINE basicClear #-}
-  basicClear _ = return ()
-
-  {-# INLINE basicSet #-}
-  basicSet !v x
-    | n == 0    = return ()
-    | otherwise = do
-                    basicUnsafeWrite v 0 x
-                    do_set 1
-    where
-      !n = basicLength v
-
-      do_set i | 2*i < n = do basicUnsafeCopy (basicUnsafeSlice i i v)
-                                              (basicUnsafeSlice 0 i v)
-                              do_set (2*i)
-               | otherwise = basicUnsafeCopy (basicUnsafeSlice i (n-i) v)
-                                             (basicUnsafeSlice 0 (n-i) v)
-
-  {-# INLINE basicUnsafeCopyPointer #-}
-  basicUnsafeCopyPointer !dst !src = do_copy 0 src
-    where
-      do_copy !i p | Just (x,q) <- MBundle.pget p = do
-                                                      basicUnsafeWrite dst i x
-                                                      do_copy (i+1) q
-                   | otherwise = return ()
-
-  {-# INLINE basicUnsafeCopy #-}
-  basicUnsafeCopy !dst !src = do_copy 0
-    where
-      !n = basicLength src
-
-      do_copy i | i < n = do
-                            x <- basicUnsafeRead src i
-                            basicUnsafeWrite dst i x
-                            do_copy (i+1)
-                | otherwise = return ()
-
-  {-# INLINE basicUnsafeMove #-}
-  basicUnsafeMove !dst !src
-    | basicOverlaps dst src = do
-        srcCopy <- clone src
-        basicUnsafeCopy dst srcCopy
-    | otherwise = basicUnsafeCopy dst src
-
-  {-# INLINE basicUnsafeGrow #-}
-  basicUnsafeGrow v by
-    = do
-        v' <- basicUnsafeNew (n+by)
-        basicUnsafeCopy (basicUnsafeSlice 0 n v') v
-        return v'
-    where
-      n = basicLength v
--}
 
 -- ------------------
 -- Internal functions
@@ -334,16 +206,6 @@
                Just n  -> munstreamMax     s n
                Nothing -> munstreamUnknown s
 
--- FIXME: I can't think of how to prevent GHC from floating out
--- unstreamUnknown. That is bad because SpecConstr then generates two
--- specialisations: one for when it is called from unstream (it doesn't know
--- the shape of the vector) and one for when the vector has grown. To see the
--- problem simply compile this:
---
--- fromList = Data.Vector.Unboxed.unstream . Bundle.fromList
---
--- I'm not sure this still applies (19/04/2010)
-
 munstreamMax :: (PrimMonad m, MVector v a)
              => MBundle m u a -> Int -> m (v (PrimState m) a)
 {-# INLINE munstreamMax #-}
@@ -399,16 +261,6 @@
                Just n  -> vmunstreamMax     s n
                Nothing -> vmunstreamUnknown s
 
--- FIXME: I can't think of how to prevent GHC from floating out
--- unstreamUnknown. That is bad because SpecConstr then generates two
--- specialisations: one for when it is called from unstream (it doesn't know
--- the shape of the vector) and one for when the vector has grown. To see the
--- problem simply compile this:
---
--- fromList = Data.Vector.Unboxed.unstream . Bundle.fromList
---
--- I'm not sure this still applies (19/04/2010)
-
 vmunstreamMax :: (PrimMonad m, V.Vector v a)
               => MBundle m v a -> Int -> m (V.Mutable v (PrimState m) a)
 {-# INLINE vmunstreamMax #-}
@@ -526,10 +378,16 @@
 slice i n v = BOUNDS_CHECK(checkSlice) "slice" i n (length v)
             $ unsafeSlice i n v
 
+-- | Take @n@ first elements of the mutable vector without making a
+-- copy. For negative @n@ empty vector is returned. If @n@ is larger
+-- than vector's length empty vector is returned,
 take :: MVector v a => Int -> v s a -> v s a
 {-# INLINE take #-}
 take n v = unsafeSlice 0 (min (max n 0) (length v)) v
 
+-- | Drop @n@ first element of the mutable vector without making a
+-- copy. For negative @n@ vector is returned unchanged and if @n@ is
+-- larger than vector's length empty vector is returned.
 drop :: MVector v a => Int -> v s a -> v s a
 {-# INLINE drop #-}
 drop n v = unsafeSlice (min m n') (max 0 (m - n')) v
@@ -547,10 +405,14 @@
       n'  = max n 0
       len = length v
 
+-- | Drop last element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 init :: MVector v a => v s a -> v s a
 {-# INLINE init #-}
 init v = slice 0 (length v - 1) v
 
+-- | Drop first element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 tail :: MVector v a => v s a -> v s a
 {-# INLINE tail #-}
 tail v = slice 1 (length v - 1) v
@@ -565,18 +427,24 @@
 unsafeSlice i n v = UNSAFE_CHECK(checkSlice) "unsafeSlice" i n (length v)
                   $ basicUnsafeSlice i n v
 
+-- | Same as 'init' but doesn't do range checks.
 unsafeInit :: MVector v a => v s a -> v s a
 {-# INLINE unsafeInit #-}
 unsafeInit v = unsafeSlice 0 (length v - 1) v
 
+-- | Same as 'tail' but doesn't do range checks.
 unsafeTail :: MVector v a => v s a -> v s a
 {-# INLINE unsafeTail #-}
 unsafeTail v = unsafeSlice 1 (length v - 1) v
 
+-- | Unsafe variant of 'take'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeTake :: MVector v a => Int -> v s a -> v s a
 {-# INLINE unsafeTake #-}
 unsafeTake n v = unsafeSlice 0 n v
 
+-- | Unsafe variant of 'drop'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeDrop :: MVector v a => Int -> v s a -> v s a
 {-# INLINE unsafeDrop #-}
 unsafeDrop n v = unsafeSlice n (length v - n) v
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Generic.hs 
new/vector-0.12.3.1/Data/Vector/Generic.hs
--- old/vector-0.12.3.0/Data/Vector/Generic.hs  2021-04-04 16:15:20.000000000 
+0200
+++ new/vector-0.12.3.1/Data/Vector/Generic.hs  2021-09-21 18:02:15.000000000 
+0200
@@ -2164,8 +2164,32 @@
 {-# INLINE freeze #-}
 freeze mv = unsafeFreeze =<< M.clone mv
 
--- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
--- copying. The immutable vector may not be used after this operation.
+-- | /O(1)/ Unsafely convert an immutable vector to a mutable one
+-- without copying. Note that this is very dangerous function and
+-- generally it's only safe to read from resulting vector. In which
+-- case immutable vector could be used safely as well.
+--
+-- Problem with mutation happens because GHC has a lot of freedom to
+-- introduce sharing. As a result mutable vectors produced by
+-- @unsafeThaw@ may or may not share same underlying buffer. For
+-- example:
+--
+-- > foo = do
+-- >   let vec = V.generate 10 id
+-- >   mvec <- V.unsafeThaw vec
+-- >   do_something mvec
+--
+-- Here GHC could lift @vec@ outside of foo which means all calls to
+-- @do_something@ will use same buffer with possibly disastrous
+-- results. Whether such aliasing happens or not depends on program in
+-- question, optimization levels, and GHC flags.
+--
+-- All in all attempts to modify vector after unsafeThaw falls out of
+-- domain of software engineering and into realm of black magic, dark
+-- rituals, and unspeakable horrors. Only advice that could be given
+-- is: "don't attempt to mutate vector after unsafeThaw unless you
+-- know how to prevent GHC from aliasing buffers accidentally. We
+-- don't"
 unsafeThaw :: (PrimMonad m, Vector v a) => v a -> m (Mutable v (PrimState m) a)
 {-# INLINE_FUSED unsafeThaw #-}
 unsafeThaw = basicUnsafeThaw
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Mutable.hs 
new/vector-0.12.3.1/Data/Vector/Mutable.hs
--- old/vector-0.12.3.0/Data/Vector/Mutable.hs  2021-04-04 16:15:20.000000000 
+0200
+++ new/vector-0.12.3.1/Data/Vector/Mutable.hs  2021-09-21 18:02:15.000000000 
+0200
@@ -14,7 +14,7 @@
 
 module Data.Vector.Mutable (
   -- * Mutable boxed vectors
-  MVector(..), IOVector, STVector,
+  MVector(MVector), IOVector, STVector,
 
   -- * Accessors
 
@@ -76,9 +76,13 @@
 
 
 -- | Mutable boxed vectors keyed on the monad they live in ('IO' or @'ST' s@).
-data MVector s a = MVector {-# UNPACK #-} !Int                -- ^ Offset in 
underlying array
-                           {-# UNPACK #-} !Int                -- ^ Size of 
slice
-                           {-# UNPACK #-} !(MutableArray s a) -- ^ Underlying 
array
+data MVector s a = MVector { _offset :: {-# UNPACK #-} !Int
+                           -- ^ Offset in underlying array
+                           , _size   :: {-# UNPACK #-} !Int
+                           -- ^ Size of slice
+                           , _array  :: {-# UNPACK #-} !(MutableArray s a)
+                           -- ^ Underlying array
+                           }
         deriving ( Typeable )
 
 type IOVector = MVector RealWorld
@@ -225,10 +229,16 @@
 {-# INLINE slice #-}
 slice = G.slice
 
+-- | Take @n@ first elements of the mutable vector without making a
+-- copy. For negative @n@ empty vector is returned. If @n@ is larger
+-- than vector's length empty vector is returned,
 take :: Int -> MVector s a -> MVector s a
 {-# INLINE take #-}
 take = G.take
 
+-- | Drop @n@ first element of the mutable vector without making a
+-- copy. For negative @n@ vector is returned unchanged and if @n@ is
+-- larger than vector's length empty vector is returned.
 drop :: Int -> MVector s a -> MVector s a
 {-# INLINE drop #-}
 drop = G.drop
@@ -237,10 +247,14 @@
 splitAt :: Int -> MVector s a -> (MVector s a, MVector s a)
 splitAt = G.splitAt
 
+-- | Drop last element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 init :: MVector s a -> MVector s a
 {-# INLINE init #-}
 init = G.init
 
+-- | Drop first element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 tail :: MVector s a -> MVector s a
 {-# INLINE tail #-}
 tail = G.tail
@@ -254,18 +268,24 @@
 {-# INLINE unsafeSlice #-}
 unsafeSlice = G.unsafeSlice
 
+-- | Unsafe variant of 'take'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeTake :: Int -> MVector s a -> MVector s a
 {-# INLINE unsafeTake #-}
 unsafeTake = G.unsafeTake
 
+-- | Unsafe variant of 'drop'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeDrop :: Int -> MVector s a -> MVector s a
 {-# INLINE unsafeDrop #-}
 unsafeDrop = G.unsafeDrop
 
+-- | Same as 'init' but doesn't do range checks.
 unsafeInit :: MVector s a -> MVector s a
 {-# INLINE unsafeInit #-}
 unsafeInit = G.unsafeInit
 
+-- | Same as 'tail' but doesn't do range checks.
 unsafeTail :: MVector s a -> MVector s a
 {-# INLINE unsafeTail #-}
 unsafeTail = G.unsafeTail
@@ -352,16 +372,16 @@
 --
 -- >>> MV.write mv' 3 999
 -- >>> MV.write mv' 4 777
--- >>> V.unsafeFreeze mv'
+-- >>> V.freeze mv'
 -- [10,20,30,999,777]
 --
 -- It is important to note that the source mutable vector is not affected when
 -- the newly allocated one is mutated.
 --
 -- >>> MV.write mv' 2 888
--- >>> V.unsafeFreeze mv'
+-- >>> V.freeze mv'
 -- [10,20,888,999,777]
--- >>> V.unsafeFreeze mv
+-- >>> V.freeze mv
 -- [10,20,30]
 --
 -- @since 0.5
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Primitive/Mutable.hs 
new/vector-0.12.3.1/Data/Vector/Primitive/Mutable.hs
--- old/vector-0.12.3.0/Data/Vector/Primitive/Mutable.hs        2021-04-04 
16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector/Primitive/Mutable.hs        2021-09-21 
18:02:15.000000000 +0200
@@ -111,7 +111,7 @@
   {-# INLINE basicUnsafeNew #-}
   basicUnsafeNew n
     | n < 0 = error $ "Primitive.basicUnsafeNew: negative length: " ++ show n
-    | n > mx = error $ "Primitive.basicUnsafeNew: length to large: " ++ show n
+    | n > mx = error $ "Primitive.basicUnsafeNew: length too large: " ++ show n
     | otherwise = MVector 0 n `liftM` newByteArray (n * size)
     where
       size = sizeOf (undefined :: a)
@@ -171,10 +171,16 @@
 {-# INLINE slice #-}
 slice = G.slice
 
+-- | Take @n@ first elements of the mutable vector without making a
+-- copy. For negative @n@ empty vector is returned. If @n@ is larger
+-- than vector's length empty vector is returned,
 take :: Prim a => Int -> MVector s a -> MVector s a
 {-# INLINE take #-}
 take = G.take
 
+-- | Drop @n@ first element of the mutable vector without making a
+-- copy. For negative @n@ vector is returned unchanged and if @n@ is
+-- larger than vector's length empty vector is returned.
 drop :: Prim a => Int -> MVector s a -> MVector s a
 {-# INLINE drop #-}
 drop = G.drop
@@ -183,10 +189,14 @@
 {-# INLINE splitAt #-}
 splitAt = G.splitAt
 
+-- | Drop last element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 init :: Prim a => MVector s a -> MVector s a
 {-# INLINE init #-}
 init = G.init
 
+-- | Drop first element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 tail :: Prim a => MVector s a -> MVector s a
 {-# INLINE tail #-}
 tail = G.tail
@@ -201,18 +211,24 @@
 {-# INLINE unsafeSlice #-}
 unsafeSlice = G.unsafeSlice
 
+-- | Unsafe variant of 'take'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeTake :: Prim a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeTake #-}
 unsafeTake = G.unsafeTake
 
+-- | Unsafe variant of 'drop'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeDrop :: Prim a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeDrop #-}
 unsafeDrop = G.unsafeDrop
 
+-- | Same as 'init' but doesn't do range checks.
 unsafeInit :: Prim a => MVector s a -> MVector s a
 {-# INLINE unsafeInit #-}
 unsafeInit = G.unsafeInit
 
+-- | Same as 'tail' but doesn't do range checks.
 unsafeTail :: Prim a => MVector s a -> MVector s a
 {-# INLINE unsafeTail #-}
 unsafeTail = G.unsafeTail
@@ -296,22 +312,22 @@
 -- etc. However, if `unsafeGrow` was used instead this would not have been
 -- guaranteed and some garbage would be there instead:
 --
--- >>> VP.unsafeFreeze mv'
+-- >>> VP.freeze mv'
 -- [10,20,30,0,0]
 --
 -- Having the extra space we can write new values in there:
 --
 -- >>> MVP.write mv' 3 999
--- >>> VP.unsafeFreeze mv'
+-- >>> VP.freeze mv'
 -- [10,20,30,999,0]
 --
 -- It is important to note that the source mutable vector is not affected when
 -- the newly allocated one is mutated.
 --
 -- >>> MVP.write mv' 2 888
--- >>> VP.unsafeFreeze mv'
+-- >>> VP.freeze mv'
 -- [10,20,888,999,0]
--- >>> VP.unsafeFreeze mv
+-- >>> VP.freeze mv
 -- [10,20,30]
 --
 -- @since 0.5
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Primitive.hs 
new/vector-0.12.3.1/Data/Vector/Primitive.hs
--- old/vector-0.12.3.0/Data/Vector/Primitive.hs        2021-04-04 
16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector/Primitive.hs        2021-09-21 
18:02:15.000000000 +0200
@@ -290,7 +290,7 @@
   mempty = empty
 
   {-# INLINE mappend #-}
-  mappend = (++)
+  mappend = (<>)
 
   {-# INLINE mconcat #-}
   mconcat = concat
@@ -1685,8 +1685,32 @@
 {-# INLINE unsafeFreeze #-}
 unsafeFreeze = G.unsafeFreeze
 
--- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
--- copying. The immutable vector may not be used after this operation.
+-- | /O(1)/ Unsafely convert an immutable vector to a mutable one
+-- without copying. Note that this is very dangerous function and
+-- generally it's only safe to read from resulting vector. In which
+-- case immutable vector could be used safely as well.
+--
+-- Problem with mutation happens because GHC has a lot of freedom to
+-- introduce sharing. As a result mutable vectors produced by
+-- @unsafeThaw@ may or may not share same underlying buffer. For
+-- example:
+--
+-- > foo = do
+-- >   let vec = V.generate 10 id
+-- >   mvec <- V.unsafeThaw vec
+-- >   do_something mvec
+--
+-- Here GHC could lift @vec@ outside of foo which means all calls to
+-- @do_something@ will use same buffer with possibly disastrous
+-- results. Whether such aliasing happens or not depends on program in
+-- question, optimization levels, and GHC flags.
+--
+-- All in all attempts to modify vector after unsafeThaw falls out of
+-- domain of software engineering and into realm of black magic, dark
+-- rituals, and unspeakable horrors. Only advice that could be given
+-- is: "don't attempt to mutate vector after unsafeThaw unless you
+-- know how to prevent GHC from aliasing buffers accidentally. We
+-- don't"
 unsafeThaw :: (Prim a, PrimMonad m) => Vector a -> m (MVector (PrimState m) a)
 {-# INLINE unsafeThaw #-}
 unsafeThaw = G.unsafeThaw
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Storable/Mutable.hs 
new/vector-0.12.3.1/Data/Vector/Storable/Mutable.hs
--- old/vector-0.12.3.0/Data/Vector/Storable/Mutable.hs 2021-04-04 
16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector/Storable/Mutable.hs 2021-09-21 
18:02:15.000000000 +0200
@@ -205,7 +205,9 @@
                   1 -> storableSetAsPrim n fp x (undefined :: Word8)
                   2 -> storableSetAsPrim n fp x (undefined :: Word16)
                   4 -> storableSetAsPrim n fp x (undefined :: Word32)
+#if !defined(ghcjs_HOST_OS)
                   8 -> storableSetAsPrim n fp x (undefined :: Word64)
+#endif
                   _ -> unsafeWithForeignPtr fp $ \p -> do
                        poke p x
 
@@ -300,10 +302,16 @@
 {-# INLINE slice #-}
 slice = G.slice
 
+-- | Take @n@ first elements of the mutable vector without making a
+-- copy. For negative @n@ empty vector is returned. If @n@ is larger
+-- than vector's length empty vector is returned,
 take :: Storable a => Int -> MVector s a -> MVector s a
 {-# INLINE take #-}
 take = G.take
 
+-- | Drop @n@ first element of the mutable vector without making a
+-- copy. For negative @n@ vector is returned unchanged and if @n@ is
+-- larger than vector's length empty vector is returned.
 drop :: Storable a => Int -> MVector s a -> MVector s a
 {-# INLINE drop #-}
 drop = G.drop
@@ -312,10 +320,14 @@
 {-# INLINE splitAt #-}
 splitAt = G.splitAt
 
+-- | Drop last element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 init :: Storable a => MVector s a -> MVector s a
 {-# INLINE init #-}
 init = G.init
 
+-- | Drop first element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 tail :: Storable a => MVector s a -> MVector s a
 {-# INLINE tail #-}
 tail = G.tail
@@ -330,18 +342,24 @@
 {-# INLINE unsafeSlice #-}
 unsafeSlice = G.unsafeSlice
 
+-- | Unsafe variant of 'take'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeTake :: Storable a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeTake #-}
 unsafeTake = G.unsafeTake
 
+-- | Unsafe variant of 'drop'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeDrop :: Storable a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeDrop #-}
 unsafeDrop = G.unsafeDrop
 
+-- | Same as 'init' but doesn't do range checks.
 unsafeInit :: Storable a => MVector s a -> MVector s a
 {-# INLINE unsafeInit #-}
 unsafeInit = G.unsafeInit
 
+-- | Same as 'tail' but doesn't do range checks.
 unsafeTail :: Storable a => MVector s a -> MVector s a
 {-# INLINE unsafeTail #-}
 unsafeTail = G.unsafeTail
@@ -425,22 +443,22 @@
 -- etc. However, if `unsafeGrow` was used instead this would not have been
 -- guaranteed and some garbage would be there instead:
 --
--- >>> VS.unsafeFreeze mv'
+-- >>> VS.freeze mv'
 -- [10,20,30,0,0]
 --
 -- Having the extra space we can write new values in there:
 --
 -- >>> MVS.write mv' 3 999
--- >>> VS.unsafeFreeze mv'
+-- >>> VS.freeze mv'
 -- [10,20,30,999,0]
 --
 -- It is important to note that the source mutable vector is not affected when
 -- the newly allocated one is mutated.
 --
 -- >>> MVS.write mv' 2 888
--- >>> VS.unsafeFreeze mv'
+-- >>> VS.freeze mv'
 -- [10,20,888,999,0]
--- >>> VS.unsafeFreeze mv
+-- >>> VS.freeze mv
 -- [10,20,30]
 --
 -- @since 0.5
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Storable.hs 
new/vector-0.12.3.1/Data/Vector/Storable.hs
--- old/vector-0.12.3.0/Data/Vector/Storable.hs 2021-04-04 16:15:20.000000000 
+0200
+++ new/vector-0.12.3.1/Data/Vector/Storable.hs 2021-09-21 18:02:15.000000000 
+0200
@@ -305,7 +305,7 @@
   mempty = empty
 
   {-# INLINE mappend #-}
-  mappend = (++)
+  mappend = (<>)
 
   {-# INLINE mconcat #-}
   mconcat = concat
@@ -1753,8 +1753,32 @@
 {-# INLINE unsafeFreeze #-}
 unsafeFreeze = G.unsafeFreeze
 
--- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
--- copying. The immutable vector may not be used after this operation.
+-- | /O(1)/ Unsafely convert an immutable vector to a mutable one
+-- without copying. Note that this is very dangerous function and
+-- generally it's only safe to read from resulting vector. In which
+-- case immutable vector could be used safely as well.
+--
+-- Problem with mutation happens because GHC has a lot of freedom to
+-- introduce sharing. As a result mutable vectors produced by
+-- @unsafeThaw@ may or may not share same underlying buffer. For
+-- example:
+--
+-- > foo = do
+-- >   let vec = V.generate 10 id
+-- >   mvec <- V.unsafeThaw vec
+-- >   do_something mvec
+--
+-- Here GHC could lift @vec@ outside of foo which means all calls to
+-- @do_something@ will use same buffer with possibly disastrous
+-- results. Whether such aliasing happens or not depends on program in
+-- question, optimization levels, and GHC flags.
+--
+-- All in all attempts to modify vector after unsafeThaw falls out of
+-- domain of software engineering and into realm of black magic, dark
+-- rituals, and unspeakable horrors. Only advice that could be given
+-- is: "don't attempt to mutate vector after unsafeThaw unless you
+-- know how to prevent GHC from aliasing buffers accidentally. We
+-- don't"
 unsafeThaw
         :: (Storable a, PrimMonad m) => Vector a -> m (MVector (PrimState m) a)
 {-# INLINE unsafeThaw #-}
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Unboxed/Mutable.hs 
new/vector-0.12.3.1/Data/Vector/Unboxed/Mutable.hs
--- old/vector-0.12.3.0/Data/Vector/Unboxed/Mutable.hs  2021-04-04 
16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector/Unboxed/Mutable.hs  2021-09-21 
18:02:15.000000000 +0200
@@ -100,10 +100,16 @@
 {-# INLINE slice #-}
 slice = G.slice
 
+-- | Take @n@ first elements of the mutable vector without making a
+-- copy. For negative @n@ empty vector is returned. If @n@ is larger
+-- than vector's length empty vector is returned,
 take :: Unbox a => Int -> MVector s a -> MVector s a
 {-# INLINE take #-}
 take = G.take
 
+-- | Drop @n@ first element of the mutable vector without making a
+-- copy. For negative @n@ vector is returned unchanged and if @n@ is
+-- larger than vector's length empty vector is returned.
 drop :: Unbox a => Int -> MVector s a -> MVector s a
 {-# INLINE drop #-}
 drop = G.drop
@@ -112,10 +118,14 @@
 {-# INLINE splitAt #-}
 splitAt = G.splitAt
 
+-- | Drop last element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 init :: Unbox a => MVector s a -> MVector s a
 {-# INLINE init #-}
 init = G.init
 
+-- | Drop first element of the mutable vector without making a copy. If
+-- vector is empty exception is thrown.
 tail :: Unbox a => MVector s a -> MVector s a
 {-# INLINE tail #-}
 tail = G.tail
@@ -130,18 +140,24 @@
 {-# INLINE unsafeSlice #-}
 unsafeSlice = G.unsafeSlice
 
+-- | Unsafe variant of 'take'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeTake :: Unbox a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeTake #-}
 unsafeTake = G.unsafeTake
 
+-- | Unsafe variant of 'drop'. If called with out of range @n@ it will
+-- simply create invalid slice that likely violate memory safety
 unsafeDrop :: Unbox a => Int -> MVector s a -> MVector s a
 {-# INLINE unsafeDrop #-}
 unsafeDrop = G.unsafeDrop
 
+-- | Same as 'init' but doesn't do range checks.
 unsafeInit :: Unbox a => MVector s a -> MVector s a
 {-# INLINE unsafeInit #-}
 unsafeInit = G.unsafeInit
 
+-- | Same as 'tail' but doesn't do range checks.
 unsafeTail :: Unbox a => MVector s a -> MVector s a
 {-# INLINE unsafeTail #-}
 unsafeTail = G.unsafeTail
@@ -225,22 +241,22 @@
 -- etc. However, if `unsafeGrow` was used instead this would not have been
 -- guaranteed and some garbage would be there instead:
 --
--- >>> VU.unsafeFreeze mv'
+-- >>> VU.freeze mv'
 -- [('a',10),('b',20),('c',30),('\NUL',0),('\NUL',0)]
 --
 -- Having the extra space we can write new values in there:
 --
 -- >>> MVU.write mv' 3 ('d', 999)
--- >>> VU.unsafeFreeze mv'
+-- >>> VU.freeze mv'
 -- [('a',10),('b',20),('c',30),('d',999),('\NUL',0)]
 --
 -- It is important to note that the source mutable vector is not affected when
 -- the newly allocated one is mutated.
 --
 -- >>> MVU.write mv' 2 ('X', 888)
--- >>> VU.unsafeFreeze mv'
+-- >>> VU.freeze mv'
 -- [('a',10),('b',20),('X',888),('d',999),('\NUL',0)]
--- >>> VU.unsafeFreeze mv
+-- >>> VU.freeze mv
 -- [('a',10),('b',20),('c',30)]
 --
 -- @since 0.5
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector/Unboxed.hs 
new/vector-0.12.3.1/Data/Vector/Unboxed.hs
--- old/vector-0.12.3.0/Data/Vector/Unboxed.hs  2021-04-04 16:15:20.000000000 
+0200
+++ new/vector-0.12.3.1/Data/Vector/Unboxed.hs  2021-09-21 18:02:15.000000000 
+0200
@@ -249,7 +249,7 @@
   mempty = empty
 
   {-# INLINE mappend #-}
-  mappend = (++)
+  mappend = (<>)
 
   {-# INLINE mconcat #-}
   mconcat = concat
@@ -1711,8 +1711,32 @@
 {-# INLINE unsafeFreeze #-}
 unsafeFreeze = G.unsafeFreeze
 
--- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
--- copying. The immutable vector may not be used after this operation.
+-- | /O(1)/ Unsafely convert an immutable vector to a mutable one
+-- without copying. Note that this is very dangerous function and
+-- generally it's only safe to read from resulting vector. In which
+-- case immutable vector could be used safely as well.
+--
+-- Problem with mutation happens because GHC has a lot of freedom to
+-- introduce sharing. As a result mutable vectors produced by
+-- @unsafeThaw@ may or may not share same underlying buffer. For
+-- example:
+--
+-- > foo = do
+-- >   let vec = V.generate 10 id
+-- >   mvec <- V.unsafeThaw vec
+-- >   do_something mvec
+--
+-- Here GHC could lift @vec@ outside of foo which means all calls to
+-- @do_something@ will use same buffer with possibly disastrous
+-- results. Whether such aliasing happens or not depends on program in
+-- question, optimization levels, and GHC flags.
+--
+-- All in all attempts to modify vector after unsafeThaw falls out of
+-- domain of software engineering and into realm of black magic, dark
+-- rituals, and unspeakable horrors. Only advice that could be given
+-- is: "don't attempt to mutate vector after unsafeThaw unless you
+-- know how to prevent GHC from aliasing buffers accidentally. We
+-- don't"
 unsafeThaw :: (Unbox a, PrimMonad m) => Vector a -> m (MVector (PrimState m) a)
 {-# INLINE unsafeThaw #-}
 unsafeThaw = G.unsafeThaw
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/Data/Vector.hs 
new/vector-0.12.3.1/Data/Vector.hs
--- old/vector-0.12.3.0/Data/Vector.hs  2021-04-04 16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/Data/Vector.hs  2021-09-21 18:02:15.000000000 +0200
@@ -351,7 +351,7 @@
   mempty = empty
 
   {-# INLINE mappend #-}
-  mappend = (++)
+  mappend = (<>)
 
   {-# INLINE mconcat #-}
   mconcat = concat
@@ -2002,8 +2002,32 @@
 {-# INLINE unsafeFreeze #-}
 unsafeFreeze = G.unsafeFreeze
 
--- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
--- copying. The immutable vector may not be used after this operation.
+-- | /O(1)/ Unsafely convert an immutable vector to a mutable one
+-- without copying. Note that this is very dangerous function and
+-- generally it's only safe to read from resulting vector. In which
+-- case immutable vector could be used safely as well.
+--
+-- Problem with mutation happens because GHC has a lot of freedom to
+-- introduce sharing. As a result mutable vectors produced by
+-- @unsafeThaw@ may or may not share same underlying buffer. For
+-- example:
+--
+-- > foo = do
+-- >   let vec = V.generate 10 id
+-- >   mvec <- V.unsafeThaw vec
+-- >   do_something mvec
+--
+-- Here GHC could lift @vec@ outside of foo which means all calls to
+-- @do_something@ will use same buffer with possibly disastrous
+-- results. Whether such aliasing happens or not depends on program in
+-- question, optimization levels, and GHC flags.
+--
+-- All in all attempts to modify vector after unsafeThaw falls out of
+-- domain of software engineering and into realm of black magic, dark
+-- rituals, and unspeakable horrors. Only advice that could be given
+-- is: "don't attempt to mutate vector after unsafeThaw unless you
+-- know how to prevent GHC from aliasing buffers accidentally. We
+-- don't"
 unsafeThaw :: PrimMonad m => Vector a -> m (MVector (PrimState m) a)
 {-# INLINE unsafeThaw #-}
 unsafeThaw = G.unsafeThaw
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/changelog.md 
new/vector-0.12.3.1/changelog.md
--- old/vector-0.12.3.0/changelog.md    2021-04-04 16:15:20.000000000 +0200
+++ new/vector-0.12.3.1/changelog.md    2021-09-21 18:02:15.000000000 +0200
@@ -1,3 +1,11 @@
+# Changes in version 0.12.3.1
+
+* Bugfix for ghcjs and `Double` memset for `Storable` vector:
+  [#410](https://github.com/haskell/vector/issues/410)
+* Avoid haddock bug: [#383](https://github.com/haskell/vector/issues/383)
+* Improve haddock and doctests
+* Disable problematic tests with -boundschecks 
[#407](https://github.com/haskell/vector/pull/407)
+
 # Changes in version 0.12.3.0
 
  * Fix performance regression due to introduction of `keepAlive#` primop in 
ghc-9.0: [#372](https://github.com/haskell/vector/pull/372)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/tests/Tests/Vector/UnitTests.hs 
new/vector-0.12.3.1/tests/Tests/Vector/UnitTests.hs
--- old/vector-0.12.3.0/tests/Tests/Vector/UnitTests.hs 2021-04-01 
22:12:03.000000000 +0200
+++ new/vector-0.12.3.1/tests/Tests/Vector/UnitTests.hs 2021-09-21 
18:02:15.000000000 +0200
@@ -13,6 +13,7 @@
 import qualified Data.List as List
 import qualified Data.Vector.Generic  as Generic
 import qualified Data.Vector as Boxed
+import qualified Data.Vector.Internal.Check as Check
 import qualified Data.Vector.Mutable as MBoxed
 import qualified Data.Vector.Primitive as Primitive
 import qualified Data.Vector.Storable as Storable
@@ -44,6 +45,12 @@
     dummy :: a
     dummy = undefined
 
+withBoundsChecksOnly :: [TestTree] -> [TestTree]
+withBoundsChecksOnly ts =
+  if Check.doChecks Check.Bounds
+     then ts
+     else []
+
 tests :: [TestTree]
 tests =
   [ testGroup "Data.Vector.Storable.Vector Alignment"
@@ -67,14 +74,15 @@
       , regression188 ([] :: [Char])
       ]
     ]
-  , testGroup "Negative tests"
-    [ testGroup "slice out of bounds #257"
+  , testGroup "Negative tests" $
+    withBoundsChecksOnly [ testGroup "slice out of bounds #257"
       [ testGroup "Boxed" $ testsSliceOutOfBounds Boxed.slice
       , testGroup "Primitive" $ testsSliceOutOfBounds Primitive.slice
       , testGroup "Storable" $ testsSliceOutOfBounds Storable.slice
       , testGroup "Unboxed" $ testsSliceOutOfBounds Unboxed.slice
-      ]
-    , testGroup "take #282"
+      ]]
+    ++
+    [ testGroup "take #282"
       [ testCase "Boxed" $ testTakeOutOfMemory Boxed.take
       , testCase "Primitive" $ testTakeOutOfMemory Primitive.take
       , testCase "Storable" $ testTakeOutOfMemory Storable.take
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/vector-0.12.3.0/vector.cabal 
new/vector-0.12.3.1/vector.cabal
--- old/vector-0.12.3.0/vector.cabal    2021-04-04 16:26:38.000000000 +0200
+++ new/vector-0.12.3.1/vector.cabal    2021-09-21 18:02:15.000000000 +0200
@@ -1,5 +1,5 @@
 Name:           vector
-Version:        0.12.3.0
+Version:        0.12.3.1
 -- don't forget to update the changelog file!
 License:        BSD3
 License-File:   LICENSE
@@ -152,9 +152,9 @@
   Install-Includes:
         vector.h
 
-  Build-Depends: base >= 4.5 && < 4.16
+  Build-Depends: base >= 4.5 && < 4.17
                , primitive >= 0.6.4.0 && < 0.8
-               , ghc-prim >= 0.2 && < 0.8
+               , ghc-prim >= 0.2 && < 0.9
                , deepseq >= 1.1 && < 1.5
   if !impl(ghc > 8.0)
     Build-Depends: fail == 4.9.*
@@ -277,7 +277,7 @@
   main-is:          doctests.hs
   hs-source-dirs:   tests
   default-language: Haskell2010
-  -- Older GHC choke on {-# UNPACK #-} pragma for some reason
+  -- Older GHC don't support DerivingVia
   if impl(ghc < 8.6)
     buildable: False
   -- GHC 8.10 fails to run doctests for some reason
@@ -285,6 +285,6 @@
     buildable: False
   build-depends:
         base      -any
-      , doctest   >=0.15 && <0.18
+      , doctest   >=0.15 && <0.19
       , primitive >= 0.6.4.0 && < 0.8
       , vector    -any

Reply via email to