[Git][ghc/ghc][master] 2 commits: Add inits1 and tails1 to Data.List.NonEmpty

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Aug 26 00:06:24 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
d387f687 by Harry Garrood at 2022-08-25T20:06:10-04:00
Add inits1 and tails1 to Data.List.NonEmpty

See https://github.com/haskell/core-libraries-committee/issues/67

- - - - -
8603c921 by Harry Garrood at 2022-08-25T20:06:10-04:00
Add since annotations and changelog entries

- - - - -


4 changed files:

- libraries/base/Data/List/NonEmpty.hs
- libraries/base/changelog.md
- libraries/base/tests/all.T
- + libraries/base/tests/inits1tails1.hs


Changes:

=====================================
libraries/base/Data/List/NonEmpty.hs
=====================================
@@ -47,7 +47,9 @@ module Data.List.NonEmpty (
    , sort        -- :: NonEmpty a -> NonEmpty a
    , reverse     -- :: NonEmpty a -> NonEmpty a
    , inits       -- :: Foldable f => f a -> NonEmpty a
+   , inits1      -- :: NonEmpty a -> NonEmpty (NonEmpty a)
    , tails       -- :: Foldable f => f a -> NonEmpty a
+   , tails1      -- :: NonEmpty a -> NonEmpty (NonEmpty a)
    , append      -- :: NonEmpty a -> NonEmpty a -> NonEmpty a
    , appendList  -- :: NonEmpty a -> [a] -> NonEmpty a
    , prependList -- :: [a] -> NonEmpty a -> NonEmpty a
@@ -215,15 +217,62 @@ map :: (a -> b) -> NonEmpty a -> NonEmpty b
 map f ~(a :| as) = f a :| fmap f as
 
 -- | The 'inits' function takes a stream @xs@ and returns all the
--- finite prefixes of @xs at .
+-- finite prefixes of @xs@, starting with the shortest. The result is
+-- 'NonEmpty' because the result always contains the empty list as the first
+-- element.
+--
+-- > inits [1,2,3] == [] :| [[1], [1,2], [1,2,3]]
+-- > inits [1] == [] :| [[1]]
+-- > inits [] == [] :| []
 inits :: Foldable f => f a -> NonEmpty [a]
 inits = fromList . List.inits . Foldable.toList
 
+-- | The 'inits1' function takes a 'NonEmpty' stream @xs@ and returns all the
+-- 'NonEmpty' finite prefixes of @xs@, starting with the shortest.
+--
+-- > inits1 (1 :| [2,3]) == (1 :| []) :| [1 :| [2], 1 :| [2,3]]
+-- > inits1 (1 :| []) == (1 :| []) :| []
+--
+-- @since 4.18
+inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
+inits1 =
+  -- fromList is an unsafe function, but this usage should be safe, since:
+  -- * `inits xs = [[], ..., init (init xs), init xs, xs]`
+  -- * If `xs` is nonempty, it follows that `inits xs` contains at least one nonempty
+  --   list, since `last (inits xs) = xs`.
+  -- * The only empty element of `inits xs` is the first one (by the definition of `inits`)
+  -- * Therefore, if we take all but the first element of `inits xs` i.e.
+  --   `tail (inits xs)`, we have a nonempty list of nonempty lists
+  fromList . Prelude.map fromList . List.tail . List.inits . Foldable.toList
+
 -- | The 'tails' function takes a stream @xs@ and returns all the
--- suffixes of @xs at .
+-- suffixes of @xs@, starting with the longest. The result is 'NonEmpty'
+-- because the result always contains the empty list as the last element.
+--
+-- > tails [1,2,3] == [1,2,3] :| [[2,3], [3], []]
+-- > tails [1] == [1] :| [[]]
+-- > tails [] == [] :| []
 tails   :: Foldable f => f a -> NonEmpty [a]
 tails = fromList . List.tails . Foldable.toList
 
+-- | The 'tails1' function takes a 'NonEmpty' stream @xs@ and returns all the
+-- non-empty suffixes of @xs@, starting with the longest.
+--
+-- > tails1 (1 :| [2,3]) == (1 :| [2,3]) :| [2 :| [3], 3 :| []]
+-- > tails1 (1 :| []) == (1 :| []) :| []
+--
+-- @since 4.18
+tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
+tails1 =
+  -- fromList is an unsafe function, but this usage should be safe, since:
+  -- * `tails xs = [xs, tail xs, tail (tail xs), ..., []]`
+  -- * If `xs` is nonempty, it follows that `tails xs` contains at least one nonempty
+  --   list, since `head (tails xs) = xs`.
+  -- * The only empty element of `tails xs` is the last one (by the definition of `tails`)
+  -- * Therefore, if we take all but the last element of `tails xs` i.e.
+  --   `init (tails xs)`, we have a nonempty list of nonempty lists
+  fromList . Prelude.map fromList . List.init . List.tails . Foldable.toList
+
 -- | @'insert' x xs@ inserts @x@ into the last position in @xs@ where it
 -- is still less than or equal to the next element. In particular, if the
 -- list is sorted beforehand, the result will also be sorted.


=====================================
libraries/base/changelog.md
=====================================
@@ -21,6 +21,7 @@
     function.
   * `GHC.Conc.Sync.threadLabel` was added, allowing the user to query the label
     of a given `ThreadId`.
+  * Add `inits1` and `tails1` to `Data.List.NonEmpty`.
 
 ## 4.17.0.0 *August 2022*
 


=====================================
libraries/base/tests/all.T
=====================================
@@ -274,3 +274,4 @@ test('T19719', normal, compile_and_run, [''])
 test('T20107', extra_run_opts('+RTS -M50M'), compile_and_run, ['-package bytestring'])
 test('trace', normal, compile_and_run, [''])
 test('listThreads', normal, compile_and_run, [''])
+test('inits1tails1', normal, compile_and_run, [''])


=====================================
libraries/base/tests/inits1tails1.hs
=====================================
@@ -0,0 +1,48 @@
+{-# LANGUAGE RankNTypes #-}
+module Main (main) where
+
+import Data.List qualified as List
+import Data.List.NonEmpty (NonEmpty(..))
+import Data.List.NonEmpty qualified as NEL
+
+-- The inits implementation added in 7.10 uses a queue rotated around
+-- powers of 2, starting the rotation only at size 255, so we want to check
+-- around powers of 2 and around the switch.
+ranges :: [Int]
+ranges = [1..20] ++ [252..259] ++ [508..515]
+
+nonEmptyUpTo :: Int -> NonEmpty Int
+nonEmptyUpTo n | n >= 1 = NEL.fromList [1..n]
+nonEmptyUpTo n = error $ "nonEmptyUpTo: invalid argument: " ++ show n
+
+simple :: (forall a . NonEmpty a -> [[a]]) -> [[[Int]]]
+simple impl = [impl (nonEmptyUpTo n) | n <- ranges]
+
+nonEmptyInits1 :: NonEmpty a -> [[a]]
+nonEmptyInits1 = map NEL.toList . NEL.toList . NEL.inits1
+
+-- inits1 should be the same as inits on nonempty lists, except that the first
+-- element should not be included
+alternativeInits1 :: NonEmpty a -> [[a]]
+alternativeInits1 = tail . List.inits . NEL.toList
+
+nonEmptyTails1 :: NonEmpty a -> [[a]]
+nonEmptyTails1 = map NEL.toList . NEL.toList . NEL.tails1
+
+-- tails1 should be the same as tails on nonempty lists, except that the last
+-- element should not be included
+alternativeTails1 :: NonEmpty a -> [[a]]
+alternativeTails1 = init . List.tails . NEL.toList
+
+-- We want inits1 (xs <> undefined) = inits1 xs <> undefined
+-- (there's no similar property for tails1 because that function starts with the
+-- longest suffix)
+lazinessInits1 :: Bool
+lazinessInits1 = [take n (nonEmptyInits1 (nonEmptyUpTo n <> undefined)) | n <- ranges]
+                  == simple nonEmptyInits1
+
+main :: IO ()
+main | simple nonEmptyInits1 /= simple alternativeInits1 = error "inits1 failed simple test"
+     | simple nonEmptyTails1 /= simple alternativeTails1 = error "tails1 failed simple test"
+     | not lazinessInits1 = error "inits1 failed laziness test"
+     | otherwise = return ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46924b75c78c2fcb92cba91796bc22986c796ed3...8603c92113c49557f8632675a01f3b3874b819d1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46924b75c78c2fcb92cba91796bc22986c796ed3...8603c92113c49557f8632675a01f3b3874b819d1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220825/a4921d4d/attachment-0001.html>


More information about the ghc-commits mailing list