Skip to content

Commit 08c3756

Browse files
authored
Merge pull request #130 from Shimuuar/uniq
Add uniq function
2 parents 16c2632 + df7ffb4 commit 08c3756

File tree

7 files changed

+52
-6
lines changed

7 files changed

+52
-6
lines changed

Data/Vector.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -113,7 +113,7 @@ module Data.Vector (
113113
-- * Working with predicates
114114

115115
-- ** Filtering
116-
filter, ifilter,
116+
filter, ifilter, uniq,
117117
mapMaybe, imapMaybe,
118118
filterM,
119119
takeWhile, dropWhile,
@@ -1169,6 +1169,11 @@ ifilter :: (Int -> a -> Bool) -> Vector a -> Vector a
11691169
{-# INLINE ifilter #-}
11701170
ifilter = G.ifilter
11711171

1172+
-- | /O(n)/ Drop repeated adjacent elements.
1173+
uniq :: (Eq a) => Vector a -> Vector a
1174+
{-# INLINE uniq #-}
1175+
uniq = G.uniq
1176+
11721177
-- | /O(n)/ Drop elements when predicate returns Nothing
11731178
mapMaybe :: (a -> Maybe b) -> Vector a -> Vector b
11741179
{-# INLINE mapMaybe #-}

Data/Vector/Fusion/Stream/Monadic.hs

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ module Data.Vector.Fusion.Stream.Monadic (
4040
eq, cmp,
4141

4242
-- * Filtering
43-
filter, filterM, mapMaybe, takeWhile, takeWhileM, dropWhile, dropWhileM,
43+
filter, filterM, uniq, mapMaybe, takeWhile, takeWhileM, dropWhile, dropWhileM,
4444

4545
-- * Searching
4646
elem, notElem, find, findM, findIndex, findIndexM,
@@ -719,6 +719,24 @@ filterM f (Stream step t) = Stream step' t
719719
Skip s' -> return $ Skip s'
720720
Done -> return $ Done
721721

722+
-- | Drop repeated adjacent elements.
723+
uniq :: (Eq a, Monad m) => Stream m a -> Stream m a
724+
{-# INLINE_FUSED uniq #-}
725+
uniq (Stream step st) = Stream step' (Nothing,st)
726+
where
727+
{-# INLINE_INNER step' #-}
728+
step' (Nothing, s) = do r <- step s
729+
case r of
730+
Yield x s' -> return $ Yield x (Just x , s')
731+
Skip s' -> return $ Skip (Nothing, s')
732+
Done -> return Done
733+
step' (Just x0, s) = do r <- step s
734+
case r of
735+
Yield x s' | x == x0 -> return $ Skip (Just x0, s')
736+
| otherwise -> return $ Yield x (Just x , s')
737+
Skip s' -> return $ Skip (Just x0, s')
738+
Done -> return Done
739+
722740
-- | Longest prefix of elements that satisfy the predicate
723741
takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a
724742
{-# INLINE takeWhile #-}

Data/Vector/Generic.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ module Data.Vector.Generic (
9696
-- * Working with predicates
9797

9898
-- ** Filtering
99-
filter, ifilter,
99+
filter, ifilter, uniq,
100100
mapMaybe, imapMaybe,
101101
filterM,
102102
takeWhile, dropWhile,
@@ -1315,6 +1315,11 @@ ifilter f = unstream
13151315
. inplace (S.map snd . S.filter (uncurry f) . S.indexed) toMax
13161316
. stream
13171317

1318+
-- | /O(n)/ Drop repeated adjacent elements.
1319+
uniq :: (Vector v a, Eq a) => v a -> v a
1320+
{-# INLINE uniq #-}
1321+
uniq = unstream . inplace S.uniq toMax . stream
1322+
13181323
-- | /O(n)/ Drop elements when predicate returns Nothing
13191324
mapMaybe :: (Vector v a, Vector v b) => (a -> Maybe b) -> v a -> v b
13201325
{-# INLINE mapMaybe #-}

Data/Vector/Primitive.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ module Data.Vector.Primitive (
9292
-- * Working with predicates
9393

9494
-- ** Filtering
95-
filter, ifilter,
95+
filter, ifilter, uniq,
9696
mapMaybe, imapMaybe,
9797
filterM,
9898
takeWhile, dropWhile,
@@ -928,6 +928,11 @@ ifilter :: Prim a => (Int -> a -> Bool) -> Vector a -> Vector a
928928
{-# INLINE ifilter #-}
929929
ifilter = G.ifilter
930930

931+
-- | /O(n)/ Drop repeated adjacent elements.
932+
uniq :: (Prim a, Eq a) => Vector a -> Vector a
933+
{-# INLINE uniq #-}
934+
uniq = G.uniq
935+
931936
-- | /O(n)/ Drop elements when predicate returns Nothing
932937
mapMaybe :: (Prim a, Prim b) => (a -> Maybe b) -> Vector a -> Vector b
933938
{-# INLINE mapMaybe #-}

Data/Vector/Storable.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ module Data.Vector.Storable (
8989
-- * Working with predicates
9090

9191
-- ** Filtering
92-
filter, ifilter,
92+
filter, ifilter, uniq,
9393
mapMaybe, imapMaybe,
9494
filterM,
9595
takeWhile, dropWhile,
@@ -938,6 +938,11 @@ ifilter :: Storable a => (Int -> a -> Bool) -> Vector a -> Vector a
938938
{-# INLINE ifilter #-}
939939
ifilter = G.ifilter
940940

941+
-- | /O(n)/ Drop repeated adjacent elements.
942+
uniq :: (Storable a, Eq a) => Vector a -> Vector a
943+
{-# INLINE uniq #-}
944+
uniq = G.uniq
945+
941946
-- | /O(n)/ Drop elements when predicate returns Nothing
942947
mapMaybe :: (Storable a, Storable b) => (a -> Maybe b) -> Vector a -> Vector b
943948
{-# INLINE mapMaybe #-}

Data/Vector/Unboxed.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,7 @@ module Data.Vector.Unboxed (
119119
-- * Working with predicates
120120

121121
-- ** Filtering
122-
filter, ifilter,
122+
filter, ifilter, uniq,
123123
mapMaybe, imapMaybe,
124124
filterM,
125125
takeWhile, dropWhile,
@@ -979,6 +979,11 @@ filter :: Unbox a => (a -> Bool) -> Vector a -> Vector a
979979
{-# INLINE filter #-}
980980
filter = G.filter
981981

982+
-- | /O(n)/ Drop repeated adjacent elements.
983+
uniq :: (Unbox a, Eq a) => Vector a -> Vector a
984+
{-# INLINE uniq #-}
985+
uniq = G.uniq
986+
982987
-- | /O(n)/ Drop elements that do not satisfy the predicate which is applied to
983988
-- values and their indices
984989
ifilter :: Unbox a => (Int -> a -> Bool) -> Vector a -> Vector a

tests/Tests/Vector.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -172,6 +172,7 @@ testPolymorphicFunctions _ = $(testProperties [
172172

173173
-- Filtering
174174
'prop_filter, 'prop_ifilter, {- prop_filterM, -}
175+
'prop_uniq,
175176
'prop_mapMaybe, 'prop_imapMaybe,
176177
'prop_takeWhile, 'prop_dropWhile,
177178

@@ -410,6 +411,8 @@ testPolymorphicFunctions _ = $(testProperties [
410411
where
411412
prop :: P ((a -> v a) -> v a -> v a) = V.concatMap `eq` concatMap
412413

414+
prop_uniq :: P (v a -> v a)
415+
= V.uniq `eq` (map head . group)
413416
--prop_span = (V.span :: (a -> Bool) -> v a -> (v a, v a)) `eq2` span
414417
--prop_break = (V.break :: (a -> Bool) -> v a -> (v a, v a)) `eq2` break
415418
--prop_splitAt = (V.splitAt :: Int -> v a -> (v a, v a)) `eq2` splitAt

0 commit comments

Comments
 (0)