[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Add intersperse for Seq (2e6f6de)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:39:55 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: changelog-foldtree,cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/2e6f6dedc15ca19fff292f7151693cdb2cde0ab3

>---------------------------------------------------------------

commit 2e6f6dedc15ca19fff292f7151693cdb2cde0ab3
Author: David Feuer <David.Feuer at gmail.com>
Date:   Sat Dec 27 21:09:28 2014 -0500

    Add intersperse for Seq
    
    `intersperse` is just like the one in `Data.List`. It is
    implemented using `<**>` for optimal performance.


>---------------------------------------------------------------

2e6f6dedc15ca19fff292f7151693cdb2cde0ab3
 Data/Sequence.hs        | 10 +++++++++-
 changelog.md            |  2 ++
 tests/seq-properties.hs |  5 +++++
 3 files changed, 16 insertions(+), 1 deletion(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 2a90928..fa7dd18 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -162,6 +162,7 @@ module Data.Sequence (
     mapWithIndex,   -- :: (Int -> a -> b) -> Seq a -> Seq b
     traverseWithIndex, -- :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b)
     reverse,        -- :: Seq a -> Seq a
+    intersperse,    -- :: a -> Seq a -> Seq a
     -- ** Zips
     zip,            -- :: Seq a -> Seq b -> Seq (a, b)
     zipWith,        -- :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
@@ -186,7 +187,7 @@ import Prelude hiding (
     scanl, scanl1, scanr, scanr1, replicate, zip, zipWith, zip3, zipWith3,
     takeWhile, dropWhile, iterate, reverse, filter, mapM, sum, all)
 import qualified Data.List
-import Control.Applicative (Applicative(..), (<$>), Alternative,
+import Control.Applicative (Applicative(..), (<$>), (<**>),  Alternative,
                             WrappedMonad(..), liftA, liftA2, liftA3)
 import qualified Control.Applicative as Applicative (Alternative(..))
 import Control.DeepSeq (NFData(rnf))
@@ -567,6 +568,13 @@ thin12 s pr m (Two a b) = DeepTh s pr (thin m) (Two12 a b)
 thin12 s pr m (Three a b c) = DeepTh s pr (thin $ m `snocTree` node2 a b) (One12 c)
 thin12 s pr m (Four a b c d) = DeepTh s pr (thin $ m `snocTree` node2 a b) (Two12 c d)
 
+-- | Intersperse an element between the elements of a sequence.
+-- > intersperse a empty = empty
+-- > intersperse a (singleton x) = singleton x
+-- > intersperse a (fromList [x,y]) = fromList [x,a,y]
+-- > intersperse a (fromList [x,y,z]) = fromList [x,a,y,a,z]
+intersperse :: a -> Seq a -> Seq a
+intersperse y xs = drop 1 $ xs <**> (const y <| singleton id)
 
 instance MonadPlus Seq where
     mzero = empty
diff --git a/changelog.md b/changelog.md
index 1ee6eb5..cb686b3 100644
--- a/changelog.md
+++ b/changelog.md
@@ -13,6 +13,8 @@
 
   * Derive `Generic` and `Generic1` for `Data.Tree.Tree`.
 
+  * Add `intersperse` for sequences.
+
 ## 0.5.6.2  *Dec 2014*
 
   * Bundled with GHC 7.10.1.
diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs
index 64c84fe..f9fb071 100644
--- a/tests/seq-properties.hs
+++ b/tests/seq-properties.hs
@@ -98,6 +98,7 @@ main = defaultMain
        , testProperty "zipWith4" prop_zipWith4
        , testProperty "<*>" prop_ap
        , testProperty "*>" prop_then
+       , testProperty "intersperse" prop_intersperse
        , testProperty ">>=" prop_bind
        ]
 
@@ -609,6 +610,10 @@ prop_then :: Seq A -> Seq B -> Bool
 prop_then xs ys =
     toList' (xs *> ys) ~= (toList xs *> toList ys)
 
+prop_intersperse :: A -> Seq A -> Bool
+prop_intersperse x xs =
+    toList' (intersperse x xs) ~= Data.List.intersperse x (toList xs)
+
 -- Monad operations
 
 prop_bind :: Seq A -> Fun A (Seq B) -> Bool



More information about the ghc-commits mailing list