diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index d7960c83..736e5ce0 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -28,6 +28,8 @@ jobs: - { cabal: "3.10", os: ubuntu-latest, ghc: "9.2.8" } - { cabal: "3.10", os: ubuntu-latest, ghc: "9.4.8" } - { cabal: "3.10", os: ubuntu-latest, ghc: "9.6.3" } + - { cabal: "3.10", os: ubuntu-latest, ghc: "9.6.3", + flags: "-fUnsafeChecks -fInternalChecks" } - { cabal: "3.10", os: ubuntu-latest, ghc: "9.8.1" } # Win - { cabal: "3.10", os: windows-latest, ghc: "8.4.4" } @@ -89,7 +91,8 @@ jobs: # ---------------- - name: Build run: | - cabal configure --haddock-all --enable-tests --enable-benchmarks --benchmark-option=-l + set -x + cabal configure ${{ matrix.flags }} --haddock-all --enable-tests --enable-benchmarks --benchmark-option=-l cabal build all --write-ghc-environment-files=always # ---------------- - name: Test diff --git a/vector/src/Data/Vector.hs b/vector/src/Data/Vector.hs index 4aa14363..5a6f89cb 100644 --- a/vector/src/Data/Vector.hs +++ b/vector/src/Data/Vector.hs @@ -122,7 +122,7 @@ module Data.Vector ( takeWhile, dropWhile, -- ** Partitioning - partition, unstablePartition, partitionWith, span, break, groupBy, group, + partition, unstablePartition, partitionWith, span, break, spanR, breakR, groupBy, group, -- ** Searching elem, notElem, find, findIndex, findIndexR, findIndices, elemIndex, elemIndices, @@ -1400,16 +1400,62 @@ unstablePartition = G.unstablePartition -- | /O(n)/ Split the vector into the longest prefix of elements that satisfy -- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.span (<4) $ V.generate 10 id +-- ([0,1,2,3],[4,5,6,7,8,9]) span :: (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE span #-} span = G.span -- | /O(n)/ Split the vector into the longest prefix of elements that do not -- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.break (>4) $ V.generate 10 id +-- ([0,1,2,3,4],[5,6,7,8,9]) break :: (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE break #-} break = G.break +-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy +-- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.spanR (>4) $ V.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +spanR :: (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE spanR #-} +spanR = G.spanR + +-- | /O(n)/ Split the vector into the longest prefix of elements that do not +-- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- @since NEXT_VERSION +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.breakR (<5) $ V.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +breakR :: (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE breakR #-} +breakR = G.breakR + -- | /O(n)/ Split a vector into a list of slices, using a predicate function. -- -- The concatenation of this list of slices is equal to the argument vector, @@ -2252,4 +2298,4 @@ copy = G.copy -- $setup -- >>> :set -Wno-type-defaults --- >>> import Prelude (Char, String, Bool(True, False), min, max, fst, even, undefined) +-- >>> import Prelude (Char, String, Bool(True, False), min, max, fst, even, undefined, Ord(..)) diff --git a/vector/src/Data/Vector/Generic.hs b/vector/src/Data/Vector/Generic.hs index 867f02d3..ec847c20 100644 --- a/vector/src/Data/Vector/Generic.hs +++ b/vector/src/Data/Vector/Generic.hs @@ -110,7 +110,7 @@ module Data.Vector.Generic ( takeWhile, dropWhile, -- ** Partitioning - partition, partitionWith, unstablePartition, span, break, groupBy, group, + partition, partitionWith, unstablePartition, span, break, spanR, breakR, groupBy, group, -- ** Searching elem, notElem, find, findIndex, findIndexR, findIndices, elemIndex, elemIndices, @@ -1536,18 +1536,70 @@ unstablePartition_new f (New.New p) = runST ( -- | /O(n)/ Split the vector into the longest prefix of elements that satisfy -- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.span (<4) $ V.generate 10 id +-- ([0,1,2,3],[4,5,6,7,8,9]) span :: Vector v a => (a -> Bool) -> v a -> (v a, v a) {-# INLINE span #-} span f = break (not . f) -- | /O(n)/ Split the vector into the longest prefix of elements that do not -- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.break (>4) $ V.generate 10 id +-- ([0,1,2,3,4],[5,6,7,8,9]) break :: Vector v a => (a -> Bool) -> v a -> (v a, v a) {-# INLINE break #-} break f xs = case findIndex f xs of Just i -> (unsafeSlice 0 i xs, unsafeSlice i (length xs - i) xs) Nothing -> (xs, empty) +-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy +-- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.spanR (>4) $ V.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +spanR :: Vector v a => (a -> Bool) -> v a -> (v a, v a) +{-# INLINE spanR #-} +spanR f = breakR (not . f) + +-- | /O(n)/ Split the vector into the longest prefix of elements that do not +-- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- @since NEXT_VERSION +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector as V +-- >>> V.breakR (<5) $ V.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +breakR :: Vector v a => (a -> Bool) -> v a -> (v a, v a) +{-# INLINE breakR #-} +breakR f xs = case findIndexR f xs of + Just i -> ( unsafeSlice (i+1) (length xs - i - 1) xs + , unsafeSlice 0 (i+1) xs) + Nothing -> (xs, empty) + + + + -- | /O(n)/ Split a vector into a list of slices. -- -- The concatenation of this list of slices is equal to the argument vector, @@ -2659,4 +2711,4 @@ dataCast f = gcast1 f -- $setup -- >>> :set -XFlexibleContexts -- >>> :set -Wno-type-defaults --- >>> import Prelude (Bool(True, False), even) +-- >>> import Prelude (Bool(True, False), even, Ord(..)) diff --git a/vector/src/Data/Vector/Primitive.hs b/vector/src/Data/Vector/Primitive.hs index f6f3988d..981f3abe 100644 --- a/vector/src/Data/Vector/Primitive.hs +++ b/vector/src/Data/Vector/Primitive.hs @@ -107,7 +107,7 @@ module Data.Vector.Primitive ( takeWhile, dropWhile, -- ** Partitioning - partition, unstablePartition, partitionWith, span, break, groupBy, group, + partition, unstablePartition, partitionWith, span, break, spanR, breakR, groupBy, group, -- ** Searching elem, notElem, find, findIndex, findIndexR, findIndices, elemIndex, elemIndices, @@ -1156,16 +1156,62 @@ unstablePartition = G.unstablePartition -- | /O(n)/ Split the vector into the longest prefix of elements that satisfy -- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Primitive as VP +-- >>> VP.span (<4) $ VP.generate 10 id +-- ([0,1,2,3],[4,5,6,7,8,9]) span :: Prim a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE span #-} span = G.span -- | /O(n)/ Split the vector into the longest prefix of elements that do not -- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Primitive as VP +-- >>> VP.break (>4) $ VP.generate 10 id +-- ([0,1,2,3,4],[5,6,7,8,9]) break :: Prim a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE break #-} break = G.break +-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy +-- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Primitive as VP +-- >>> VP.spanR (>4) $ VP.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +spanR :: Prim a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE spanR #-} +spanR = G.spanR + +-- | /O(n)/ Split the vector into the longest prefix of elements that do not +-- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- @since NEXT_VERSION +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Primitive as VP +-- >>> VP.breakR (<5) $ VP.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +breakR :: Prim a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE breakR #-} +breakR = G.breakR + -- | /O(n)/ Split a vector into a list of slices, using a predicate function. -- -- The concatenation of this list of slices is equal to the argument vector, @@ -1894,4 +1940,4 @@ copy :: (Prim a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m () copy = G.copy -- $setup --- >>> import Prelude (($), min, even, max, succ) +-- >>> import Prelude (($), min, even, max, succ, id, Ord(..)) diff --git a/vector/src/Data/Vector/Storable.hs b/vector/src/Data/Vector/Storable.hs index e3daf354..4a052a07 100644 --- a/vector/src/Data/Vector/Storable.hs +++ b/vector/src/Data/Vector/Storable.hs @@ -104,7 +104,7 @@ module Data.Vector.Storable ( takeWhile, dropWhile, -- ** Partitioning - partition, unstablePartition, partitionWith, span, break, groupBy, group, + partition, unstablePartition, partitionWith, span, break, spanR, breakR, groupBy, group, -- ** Searching elem, notElem, find, findIndex, findIndexR, findIndices, elemIndex, elemIndices, @@ -1178,16 +1178,62 @@ unstablePartition = G.unstablePartition -- | /O(n)/ Split the vector into the longest prefix of elements that satisfy -- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Storable as VS +-- >>> VS.span (<4) $ VS.generate 10 id +-- ([0,1,2,3],[4,5,6,7,8,9]) span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE span #-} span = G.span -- | /O(n)/ Split the vector into the longest prefix of elements that do not -- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Storable as VS +-- >>> VS.break (>4) $ VS.generate 10 id +-- ([0,1,2,3,4],[5,6,7,8,9]) break :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE break #-} break = G.break +-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy +-- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Storable as VS +-- >>> VS.spanR (>4) $ VS.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +spanR :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE spanR #-} +spanR = G.spanR + +-- | /O(n)/ Split the vector into the longest prefix of elements that do not +-- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- @since NEXT_VERSION +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Storable as VS +-- >>> VS.breakR (<5) $ VS.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +breakR :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE breakR #-} +breakR = G.breakR + -- | /O(n)/ Split a vector into a list of slices, using a predicate function. -- -- The concatenation of this list of slices is equal to the argument vector, @@ -1998,4 +2044,4 @@ unsafeWith :: Storable a => Vector a -> (Ptr a -> IO b) -> IO b unsafeWith (Vector _ fp) = withForeignPtr fp -- $setup --- >>> import Prelude (Bool(..), Double, ($), (+), (/), succ, even, min, max) +-- >>> import Prelude (Bool(..), Double, ($), (+), (/), succ, even, min, max, id, Ord(..)) diff --git a/vector/src/Data/Vector/Unboxed.hs b/vector/src/Data/Vector/Unboxed.hs index e7e9d8fd..0f5ed15c 100644 --- a/vector/src/Data/Vector/Unboxed.hs +++ b/vector/src/Data/Vector/Unboxed.hs @@ -149,7 +149,7 @@ module Data.Vector.Unboxed ( takeWhile, dropWhile, -- ** Partitioning - partition, unstablePartition, partitionWith, span, break, groupBy, group, + partition, unstablePartition, partitionWith, span, break, spanR, breakR, groupBy, group, -- ** Searching elem, notElem, find, findIndex, findIndexR, findIndices, elemIndex, elemIndices, @@ -1169,16 +1169,62 @@ unstablePartition = G.unstablePartition -- | /O(n)/ Split the vector into the longest prefix of elements that satisfy -- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Unboxed as VU +-- >>> VU.span (<4) $ VU.generate 10 id +-- ([0,1,2,3],[4,5,6,7,8,9]) span :: Unbox a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE span #-} span = G.span -- | /O(n)/ Split the vector into the longest prefix of elements that do not -- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Unboxed as VU +-- >>> VU.break (>4) $ VU.generate 10 id +-- ([0,1,2,3,4],[5,6,7,8,9]) break :: Unbox a => (a -> Bool) -> Vector a -> (Vector a, Vector a) {-# INLINE break #-} break = G.break +-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy +-- the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Unboxed as VU +-- >>> VU.spanR (>4) $ VU.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +spanR :: Unbox a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE spanR #-} +spanR = G.spanR + +-- | /O(n)/ Split the vector into the longest prefix of elements that do not +-- satisfy the predicate and the rest without copying. +-- +-- Does not fuse. +-- +-- @since NEXT_VERSION +-- +-- ==== __Examples__ +-- +-- >>> import qualified Data.Vector.Unboxed as VU +-- >>> VU.breakR (<5) $ VU.generate 10 id +-- ([5,6,7,8,9],[0,1,2,3,4]) +breakR :: Unbox a => (a -> Bool) -> Vector a -> (Vector a, Vector a) +{-# INLINE breakR #-} +breakR = G.breakR + -- | /O(n)/ Split a vector into a list of slices, using a predicate function. -- -- The concatenation of this list of slices is equal to the argument vector, @@ -1974,4 +2020,4 @@ copy = G.copy #include "unbox-tuple-instances" -- $setup --- >>> import Prelude (Bool(True, False), ($), (+), min, max, even, fst, pred, succ, undefined) +-- >>> import Prelude (Bool(True, False), ($), (+), min, max, even, fst, pred, id, succ, undefined, Ord(..)) diff --git a/vector/tests/Tests/Vector/Property.hs b/vector/tests/Tests/Vector/Property.hs index 667df6f5..dc8f0b63 100644 --- a/vector/tests/Tests/Vector/Property.hs +++ b/vector/tests/Tests/Vector/Property.hs @@ -171,6 +171,7 @@ testPolymorphicFunctions _ = $(testProperties [ 'prop_partition, {- 'prop_unstablePartition, -} 'prop_partitionWith, 'prop_span, 'prop_break, + 'prop_spanR, 'prop_breakR, 'prop_groupBy, -- Searching @@ -337,6 +338,8 @@ testPolymorphicFunctions _ = $(testProperties [ = V.partitionWith `eq` partitionWith prop_span :: P ((a -> Bool) -> v a -> (v a, v a)) = V.span `eq` span prop_break :: P ((a -> Bool) -> v a -> (v a, v a)) = V.break `eq` break + prop_spanR :: P ((a -> Bool) -> v a -> (v a, v a)) = V.spanR `eq` spanR + prop_breakR :: P ((a -> Bool) -> v a -> (v a, v a)) = V.breakR `eq` breakR prop_groupBy :: P ((a -> a -> Bool) -> v a -> [v a]) = V.groupBy `eq` groupBy prop_elem :: P (a -> v a -> Bool) = V.elem `eq` elem diff --git a/vector/tests/Utilities.hs b/vector/tests/Utilities.hs index fe0f16a9..7e151315 100644 --- a/vector/tests/Utilities.hs +++ b/vector/tests/Utilities.hs @@ -6,6 +6,7 @@ module Utilities where import Test.QuickCheck +import Control.Arrow ((***)) import Data.Foldable import Data.Bifunctor import qualified Data.Vector as DV @@ -292,6 +293,12 @@ imapMaybe f = catMaybes . withIndexFirst map f indexedLeftFold fld f z = fld (uncurry . f) z . zip [0..] +spanR :: (a -> Bool) -> [a] -> ([a], [a]) +spanR f = (reverse *** reverse) . span f . reverse + +breakR :: (a -> Bool) -> [a] -> ([a], [a]) +breakR f = (reverse *** reverse) . break f . reverse + ifoldl :: (a -> Int -> a -> a) -> a -> [a] -> a ifoldl = indexedLeftFold foldl