[Git][ghc/ghc][wip/CLC208] base: Introduce Data.Bounded
Ben Gamari (@bgamari)
gitlab at gitlab.haskell.org
Sat Sep 30 14:18:01 UTC 2023
Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC
Commits:
5d58aa6b by Ben Gamari at 2023-09-30T10:17:51-04:00
base: Introduce Data.Bounded
As proposed in [CLC#208].
[CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208
- - - - -
5 changed files:
- + libraries/base/Data/Bounded.hs
- libraries/base/Data/Enum.hs
- libraries/base/base.cabal
- libraries/base/changelog.md
- testsuite/tests/interface-stability/base-exports.stdout
Changes:
=====================================
libraries/base/Data/Bounded.hs
=====================================
@@ -0,0 +1,22 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : Data.Enum
+-- Copyright : (c) The University of Glasgow, 1992-2002
+-- License : see libraries/base/LICENSE
+--
+-- Maintainer : cvs-ghc at haskell.org
+-- Stability : stable
+-- Portability : non-portable (GHC extensions)
+--
+-- The 'Bounded' classes.
+--
+-----------------------------------------------------------------------------
+
+module Data.Bounded
+ ( Bounded(..)
+ ) where
+
+import GHC.Enum
+
=====================================
libraries/base/Data/Enum.hs
=====================================
@@ -10,13 +10,12 @@
-- Stability : stable
-- Portability : non-portable (GHC extensions)
--
--- The 'Enum' and 'Bounded' classes.
+-- The 'Enum' class.
--
-----------------------------------------------------------------------------
module Data.Enum
- ( Bounded(..)
- , Enum(..)
+ ( Enum(..)
) where
import GHC.Enum
=====================================
libraries/base/base.cabal
=====================================
@@ -121,6 +121,7 @@ Library
Data.Bitraversable
Data.Bits
Data.Bool
+ Data.Bounded
Data.Char
Data.Coerce
Data.Complex
=====================================
libraries/base/changelog.md
=====================================
@@ -5,6 +5,8 @@
* Add a `RULE` to `Prelude.lookup`, allowing it to participate in list fusion ([CLC proposal #174](https://github.com/haskell/core-libraries-committee/issues/175))
* The `Enum Int64` and `Enum Word64` instances now use native operations on 32-bit platforms, increasing performance by up to 1.5x on i386 and up to 5.6x with the JavaScript backend. ([CLC proposal #187](https://github.com/haskell/core-libraries-committee/issues/187))
* Update to [Unicode 15.1.0](https://www.unicode.org/versions/Unicode15.1.0/).
+ * Introduce `Data.Bounded` exporting the `Bounded` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208))
+ * Introduce `Data.Enum` exporting the `Enum` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208))
## 4.19.0.0 *TBA*
* Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -908,11 +908,6 @@ module Data.Either where
module Data.Enum where
-- Safety: Safe-Inferred
- type Bounded :: * -> Constraint
- class Bounded a where
- minBound :: a
- maxBound :: a
- {-# MINIMAL minBound, maxBound #-}
type Enum :: * -> Constraint
class Enum a where
succ :: a -> a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d58aa6be1308a846f2c79ff5da2d529fb9f93f9
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d58aa6be1308a846f2c79ff5da2d529fb9f93f9
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/20230930/d8ed4d3d/attachment-0001.html>
More information about the ghc-commits
mailing list