[Git][ghc/ghc][master] Add Data.List.unsnoc

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu May 25 00:58:50 UTC 2023



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


Commits:
36d5944d by Bodigrim at 2023-05-24T20:58:34-04:00
Add Data.List.unsnoc

See https://github.com/haskell/core-libraries-committee/issues/165 for discussion

- - - - -


7 changed files:

- libraries/base/Data/List.hs
- libraries/base/Data/OldList.hs
- libraries/base/GHC/List.hs
- libraries/base/changelog.md
- + testsuite/tests/lib/base/Unsnoc.hs
- + testsuite/tests/lib/base/Unsnoc.stdout
- testsuite/tests/lib/base/all.T


Changes:

=====================================
libraries/base/Data/List.hs
=====================================
@@ -25,6 +25,7 @@ module Data.List
    , tail
    , init
    , uncons
+   , unsnoc
    , singleton
    , null
    , length


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -26,6 +26,7 @@ module Data.OldList
    , tail
    , init
    , uncons
+   , unsnoc
    , singleton
    , null
    , length


=====================================
libraries/base/GHC/List.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.List (
    -- Other functions
    foldl1', concat, concatMap,
    map, (++), filter, lookup,
-   head, last, tail, init, uncons, (!?), (!!),
+   head, last, tail, init, uncons, unsnoc, (!?), (!!),
    scanl, scanl1, scanl', scanr, scanr1,
    iterate, iterate', repeat, replicate, cycle,
    take, drop, splitAt, takeWhile, dropWhile, span, break, reverse,
@@ -97,11 +97,11 @@ badHead = errorEmptyList "head"
                 head (augment g xs) = g (\x _ -> x) (head xs)
  #-}
 
--- | \(\mathcal{O}(1)\). Decompose a list into its head and tail.
+-- | \(\mathcal{O}(1)\). Decompose a list into its 'head' and 'tail'.
 --
 -- * If the list is empty, returns 'Nothing'.
 -- * If the list is non-empty, returns @'Just' (x, xs)@,
--- where @x@ is the head of the list and @xs@ its tail.
+-- where @x@ is the 'head' of the list and @xs@ its 'tail'.
 --
 -- @since 4.8.0.0
 --
@@ -115,6 +115,41 @@ uncons                  :: [a] -> Maybe (a, [a])
 uncons []               = Nothing
 uncons (x:xs)           = Just (x, xs)
 
+-- | \(\mathcal{O}(n)\). Decompose a list into 'init' and 'last'.
+--
+-- * If the list is empty, returns 'Nothing'.
+-- * If the list is non-empty, returns @'Just' (xs, x)@,
+-- where @xs@ is the 'init'ial part of the list and @x@ is its 'last' element.
+--
+-- @since 4.19.0.0
+--
+-- >>> unsnoc []
+-- Nothing
+-- >>> unsnoc [1]
+-- Just ([],1)
+-- >>> unsnoc [1, 2, 3]
+-- Just ([1,2],3)
+--
+-- Laziness:
+--
+-- >>> fst <$> unsnoc [undefined]
+-- Just []
+-- >>> head . fst <$> unsnoc (1 : undefined)
+-- Just *** Exception: Prelude.undefined
+-- >>> head . fst <$> unsnoc (1 : 2 : undefined)
+-- Just 1
+--
+-- 'unsnoc' is dual to 'uncons': for a finite list @xs@
+--
+-- > unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
+--
+unsnoc :: [a] -> Maybe ([a], a)
+-- The lazy pattern ~(a, b) is important to be productive on infinite lists
+-- and not to be prone to stack overflows.
+-- Expressing the recursion via 'foldr' provides for list fusion.
+unsnoc = foldr (\x -> Just . maybe ([], x) (\(~(a, b)) -> (x : a, b))) Nothing
+{-# INLINABLE unsnoc #-}
+
 -- | \(\mathcal{O}(1)\). Extract the elements after the head of a list, which
 -- must be non-empty.
 --
@@ -143,8 +178,7 @@ tail []                 =  errorEmptyList "tail"
 -- >>> last []
 -- *** Exception: Prelude.last: empty list
 --
--- WARNING: This function is partial. You can use 'reverse' with case-matching,
--- 'uncons' or 'listToMaybe' instead.
+-- WARNING: This function is partial. Consider using 'unsnoc' instead.
 last                    :: HasCallStack => [a] -> a
 #if defined(USE_REPORT_PRELUDE)
 last [x]                =  x
@@ -172,8 +206,7 @@ lastError = errorEmptyList "last"
 -- >>> init []
 -- *** Exception: Prelude.init: empty list
 --
--- WARNING: This function is partial. You can use 'reverse' with case-matching
--- or 'uncons' instead.
+-- WARNING: This function is partial. Consider using 'unsnoc' instead.
 init                    :: HasCallStack => [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
 init [x]                =  []


=====================================
libraries/base/changelog.md
=====================================
@@ -16,6 +16,7 @@
   * Add `Data.Functor.unzip` ([CLC proposal #88](https://github.com/haskell/core-libraries-committee/issues/88))
   * Add `System.Mem.Weak.{get,set}FinalizerExceptionHandler`, which allows the user to set the global handler invoked by when a `Weak` pointer finalizer throws an exception. ([CLC proposal #126](https://github.com/haskell/core-libraries-committee/issues/126))
   * Add `System.Mem.Weak.printToHandleFinalizerExceptionHandler`, which can be used with `setFinalizerExceptionHandler` to print exceptions thrown by finalizers to the given `Handle`. ([CLC proposal #126](https://github.com/haskell/core-libraries-committee/issues/126))
+  * Add `Data.List.unsnoc` ([CLC proposal #165](https://github.com/haskell/core-libraries-committee/issues/165))
   * Implement more members of `instance Foldable (Compose f g)` explicitly.
       ([CLC proposal #57](https://github.com/haskell/core-libraries-committee/issues/57))
   * Add `Eq` and `Ord` instances for `SSymbol`, `SChar`, and `SNat`.


=====================================
testsuite/tests/lib/base/Unsnoc.hs
=====================================
@@ -0,0 +1,14 @@
+{-# OPTIONS_GHC -Wno-x-partial #-}
+
+module Main (main) where 
+
+import Data.List (unsnoc)
+
+main :: IO ()
+main = do
+  print $ unsnoc ([] :: [Int])
+  print $ unsnoc [1]
+  print $ unsnoc [1, 2, 3]
+  print $ fst <$> unsnoc [undefined :: Int]
+  print $ head . fst <$> unsnoc (1 : 2 : undefined)
+  print $ head . fst <$> unsnoc [1..]


=====================================
testsuite/tests/lib/base/Unsnoc.stdout
=====================================
@@ -0,0 +1,6 @@
+Nothing
+Just ([],1)
+Just ([1,2],3)
+Just []
+Just 1
+Just 1


=====================================
testsuite/tests/lib/base/all.T
=====================================
@@ -8,3 +8,4 @@ test('executablePath', [extra_run_opts(config.os), js_broken(22261), when(arch('
 test('T17472', normal, compile_and_run, [''])
 test('T19569b', normal, compile_and_run, [''])
 test('Monoid_ByteArray', normal, compile_and_run, [''])
+test('Unsnoc', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36d5944d13866e8c0d6634c38bb7a2f32fe98512

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36d5944d13866e8c0d6634c38bb7a2f32fe98512
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/20230524/86b21eda/attachment-0001.html>


More information about the ghc-commits mailing list