[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Rename cycleN to cycleTaking (1dbe8b3)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:42:52 UTC 2017


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

On branches: 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/1dbe8b3af0cbe08eb8d22b34dc9db4b09f09cece

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

commit 1dbe8b3af0cbe08eb8d22b34dc9db4b09f09cece
Author: David Feuer <David.Feuer at gmail.com>
Date:   Mon May 30 00:03:11 2016 -0400

    Rename cycleN to cycleTaking
    
    Make cycleTaking more tolerant of edge cases to match
    list equivalent. Add QuickCheck property.


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

1dbe8b3af0cbe08eb8d22b34dc9db4b09f09cece
 Data/Sequence.hs        | 20 ++++++++++----------
 changelog.md            |  2 +-
 tests/seq-properties.hs |  5 +++++
 3 files changed, 16 insertions(+), 11 deletions(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 6a00472..335df84 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -102,7 +102,7 @@ module Data.Sequence (
     replicate,      -- :: Int -> a -> Seq a
     replicateA,     -- :: Applicative f => Int -> f a -> f (Seq a)
     replicateM,     -- :: Monad m => Int -> m a -> m (Seq a)
-    cycleN,         -- :: Int -> Seq a -> Seq a
+    cycleTaking,    -- :: Int -> Seq a -> Seq a
     -- ** Iterative construction
     iterateN,       -- :: Int -> (a -> a) -> a -> Seq a
     unfoldr,        -- :: (b -> Maybe (a, b)) -> b -> Seq a
@@ -1043,21 +1043,21 @@ replicateM n x
   | n >= 0      = unwrapMonad (replicateA n (WrapMonad x))
   | otherwise   = error "replicateM takes a nonnegative integer argument"
 
--- | /O(log(k))/ incremental. @'cycleN' k xs@ forms a sequence of length @k@ by
--- repeatedly concatenating @xs@ with itself. @xs@ must not be empty and
--- @k@ must not be negative.
+-- | /O(log(k))/ incremental. @'cycleTaking' k xs@ forms a sequence of length @k@ by
+-- repeatedly concatenating @xs@ with itself. @xs@ may only be empty if
+-- @k@ is 0.
 --
--- prop> cycleN k = fromList . take k . cycle . toList
+-- prop> cycleTaking k = fromList . take k . cycle . toList
 
 -- If you wish to concatenate a non-empty sequence @xs@ with itself precisely
--- @k@ times, you can use @cycleN (k * length xs)@ or just
+-- @k@ times, you can use @cycleTaking (k * length xs)@ or just
 -- @replicate k () *> xs at .
 --
 -- @since 0.5.8
-cycleN :: Int -> Seq a -> Seq a
-cycleN n !_xs | n < 0 = error "cycleN takes a non-negative argument"
-cycleN _n xs  | null xs = error "cycleN takes a non-empty sequence"
-cycleN n xs = cycleNTimes reps xs >< take final xs
+cycleTaking :: Int -> Seq a -> Seq a
+cycleTaking n !_xs | n <= 0 = empty
+cycleTaking _n xs  | null xs = error "cycleTaking cannot take a positive number of elements from an empty cycle."
+cycleTaking n xs = cycleNTimes reps xs >< take final xs
   where
     (reps, final) = n `quotRem` length xs
 
diff --git a/changelog.md b/changelog.md
index 8ce2061..6a83c08 100644
--- a/changelog.md
+++ b/changelog.md
@@ -22,7 +22,7 @@
 
   * Add `Empty`, `:<|`, and `:|>` pattern synonyms for `Data.Sequence`.
 
-  * Add (!?), `lookup`, `chunksOf`, `cycleN`, `insertAt`, `intersperse`,
+  * Add (!?), `lookup`, `chunksOf`, `cycleTaking`, `insertAt`, `intersperse`,
     `foldMapWithIndex`, and `traverseWithIndex` for `Data.Sequence`.
 
   * Make `splitAt` in `Data.Sequence` strict in its arguments. Previously,
diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs
index 2b9745b..c24c7e8 100644
--- a/tests/seq-properties.hs
+++ b/tests/seq-properties.hs
@@ -103,6 +103,7 @@ main = defaultMain
        , testProperty "zipWith4" prop_zipWith4
        , testProperty "<*>" prop_ap
        , testProperty "*>" prop_then
+       , testProperty "cycleTaking" prop_cycleTaking
        , testProperty "intersperse" prop_intersperse
        , testProperty ">>=" prop_bind
        ]
@@ -649,6 +650,10 @@ prop_intersperse :: A -> Seq A -> Bool
 prop_intersperse x xs =
     toList' (intersperse x xs) ~= Data.List.intersperse x (toList xs)
 
+prop_cycleTaking :: Int -> Seq A -> Property
+prop_cycleTaking n xs =
+    (n <= 0 || not (null xs)) ==> toList' (cycleTaking n xs) ~= Data.List.take n (Data.List.cycle (toList xs))
+
 -- Monad operations
 
 prop_bind :: Seq A -> Fun A (Seq B) -> Bool



More information about the ghc-commits mailing list