[Git][ghc/ghc][master] CLC Proposal #182: Export List from Data.List

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Oct 19 15:38:34 UTC 2023



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


Commits:
921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00
CLC Proposal #182: Export List from Data.List

Proposal link: https://github.com/haskell/core-libraries-committee/issues/182

- - - - -


7 changed files:

- libraries/base/changelog.md
- libraries/base/src/Data/List.hs
- libraries/ghc-prim/GHC/Types.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -8,6 +8,7 @@
   * Fix `fdIsNonBlocking` to always be `0` for regular files and block devices on unix, regardless of `O_NONBLOCK`
   * Always use `safe` call to `read` for regular files and block devices on unix if the RTS is multi-threaded, regardless of `O_NONBLOCK`.
     ([CLC proposal #166](https://github.com/haskell/core-libraries-committee/issues/166))
+  * Export List from Data.List ([CLC proposal #182](https://github.com/haskell/core-libraries-committee/issues/182)).
 
 ## 4.19.0.0 *TBA*
   * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.


=====================================
libraries/base/src/Data/List.hs
=====================================
@@ -17,9 +17,10 @@
 
 module Data.List
    (
+   List
    -- * Basic functions
 
-     (++)
+   , (++)
    , head
    , last
    , tail
@@ -222,6 +223,7 @@ import Data.OldList hiding ( all, and, any, concat, concatMap, elem, find,
                              length, notElem, null, or, product, sum )
 
 import GHC.Base ( Bool(..), Eq((==)), otherwise )
+import GHC.List (List)
 
 -- | The 'isSubsequenceOf' function takes two lists and returns 'True' if all
 -- the elements of the first list occur, in order, in the second. The


=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -168,15 +168,27 @@ type family Any :: k where { }
 *                                                                      *
 ********************************************************************* -}
 
--- | The builtin list type, usually written in its non-prefix form @[a]@.
+-- | The builtin linked list type.
 --
 -- In Haskell, lists are one of the most important data types as they are
 -- often used analogous to loops in imperative programming languages.
--- These lists are singly linked, which makes it unsuited for operations
--- that require \(\mathcal{O}(1)\) access. Instead, lists are intended to
+-- These lists are singly linked, which makes them unsuited for operations
+-- that require \(\mathcal{O}(1)\) access. Instead, they are intended to
 -- be traversed.
 --
--- Lists are constructed recursively using the right-associative cons-operator
+-- You can use @List a@ or @[a]@ in type signatures:
+--
+-- > length :: [a] -> Int
+--
+-- or
+--
+-- > length :: List a -> Int
+--
+-- They are fully equivalent, and @List a@ will be normalised to @[a]@.
+--
+-- ==== Usage
+--
+-- Lists are constructed recursively using the right-associative constructor operator (or /cons/)
 -- @(:) :: a -> [a] -> [a]@, which prepends an element to a list,
 -- and the empty list @[]@.
 --
@@ -184,6 +196,16 @@ type family Any :: k where { }
 -- (1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
 -- @
 --
+-- Lists can also be constructed using list literals
+-- of the form @[x_1, x_2, ..., x_n]@
+-- which are syntactic sugar and, unless @-XOverloadedLists@ is enabled,
+-- are translated into uses of @(:)@ and @[]@
+--
+-- 'Data.String.String' literals, like @"I 💜 hs"@, are translated into
+-- Lists of characters, @[\'I\', \' \', \'💜\', \' \', \'h\', \'s\']@.
+--
+-- ==== __Implementation__
+--
 -- Internally and in memory, all the above are represented like this,
 -- with arrows being pointers to locations in memory.
 --
@@ -193,14 +215,6 @@ type family Any :: k where { }
 -- >       v              v              v
 -- >       1              2              3
 --
--- As seen above, lists can also be constructed using list literals
--- of the form @[x_1, x_2, ..., x_n]@
--- which are syntactic sugar and, unless @-XOverloadedLists@ is enabled,
--- are translated into uses of @(:)@ and @[]@
---
--- Similarly, 'Data.String.String' literals of the form @"I 💜 hs"@ are translated into
--- Lists of characters, @[\'I\', \' \', \'💜\', \' \', \'h\', \'s\']@.
---
 -- ==== __Examples__
 --
 -- @


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1252,6 +1252,8 @@ module Data.List where
   (!!) :: forall a. GHC.Stack.Types.HasCallStack => [a] -> GHC.Types.Int -> a
   (!?) :: forall a. [a] -> GHC.Types.Int -> GHC.Maybe.Maybe a
   (++) :: forall a. [a] -> [a] -> [a]
+  type List :: * -> *
+  data List a = ...
   (\\) :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
   all :: forall (t :: * -> *) a. Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
   and :: forall (t :: * -> *). Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1252,6 +1252,8 @@ module Data.List where
   (!!) :: forall a. GHC.Stack.Types.HasCallStack => [a] -> GHC.Types.Int -> a
   (!?) :: forall a. [a] -> GHC.Types.Int -> GHC.Maybe.Maybe a
   (++) :: forall a. [a] -> [a] -> [a]
+  type List :: * -> *
+  data List a = ...
   (\\) :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
   all :: forall (t :: * -> *) a. Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
   and :: forall (t :: * -> *). Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1252,6 +1252,8 @@ module Data.List where
   (!!) :: forall a. GHC.Stack.Types.HasCallStack => [a] -> GHC.Types.Int -> a
   (!?) :: forall a. [a] -> GHC.Types.Int -> GHC.Maybe.Maybe a
   (++) :: forall a. [a] -> [a] -> [a]
+  type List :: * -> *
+  data List a = ...
   (\\) :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
   all :: forall (t :: * -> *) a. Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
   and :: forall (t :: * -> *). Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1252,6 +1252,8 @@ module Data.List where
   (!!) :: forall a. GHC.Stack.Types.HasCallStack => [a] -> GHC.Types.Int -> a
   (!?) :: forall a. [a] -> GHC.Types.Int -> GHC.Maybe.Maybe a
   (++) :: forall a. [a] -> [a] -> [a]
+  type List :: * -> *
+  data List a = ...
   (\\) :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
   all :: forall (t :: * -> *) a. Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
   and :: forall (t :: * -> *). Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/921fbf2fb601ff90cd9cbc0fb8fe3b1768a8f1d5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/921fbf2fb601ff90cd9cbc0fb8fe3b1768a8f1d5
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/20231019/4440e637/attachment-0001.html>


More information about the ghc-commits mailing list