[Git][ghc/ghc][master] Add `Enum (Down a)` instance that swaps `succ` and `pred`

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Oct 17 23:20:22 UTC 2022



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


Commits:
8c72411d by Gergo ERDI at 2022-10-17T19:20:04-04:00
Add `Enum (Down a)` instance that swaps `succ` and `pred`

See https://github.com/haskell/core-libraries-committee/issues/51 for
discussion. The key points driving the implementation are the following
two ideas:

* For the `Int` type, `comparing (complement @Int)` behaves exactly as
  an order-swapping `compare @Int`.
* `enumFrom @(Down a)` can be implemented in terms of `enumFromThen @a`,
  if only the corner case of starting at the very end is handled specially

- - - - -


2 changed files:

- libraries/base/Data/Ord.hs
- libraries/base/changelog.md


Changes:

=====================================
libraries/base/Data/Ord.hs
=====================================
@@ -24,11 +24,11 @@ module Data.Ord (
    clamp,
  ) where
 
-import Data.Bits (Bits, FiniteBits)
+import Data.Bits (Bits, FiniteBits, complement)
 import Foreign.Storable (Storable)
 import GHC.Ix (Ix)
 import GHC.Base
-import GHC.Enum (Bounded(..))
+import GHC.Enum (Bounded(..), Enum(..))
 import GHC.Float (Floating, RealFloat)
 import GHC.Num
 import GHC.Read
@@ -146,6 +146,26 @@ instance Bounded a => Bounded (Down a) where
     minBound = Down maxBound
     maxBound = Down minBound
 
+-- | Swaps @'succ'@ and @'pred'@ of the underlying type.
+--
+-- @since 4.18.0.0
+instance (Enum a, Bounded a, Eq a) => Enum (Down a) where
+    succ = fmap pred
+    pred = fmap succ
+
+    -- Here we use the fact that 'comparing (complement @Int)' behaves
+    -- as an order-swapping `compare @Int`.
+    fromEnum = complement . fromEnum . getDown
+    toEnum = Down . toEnum . complement
+
+    enumFrom (Down x)
+        | x == minBound
+        = [Down x] -- We can't rely on 'enumFromThen _ (pred @a minBound)` behaving nicely,
+                   -- since 'enumFromThen _' might be strict and 'pred minBound' might throw
+        | otherwise
+        = coerce $ enumFromThen x (pred x)
+    enumFromThen (Down x) (Down y) = coerce $ enumFromThen x y
+
 -- | @since 4.11.0.0
 instance Functor Down where
     fmap = coerce


=====================================
libraries/base/changelog.md
=====================================
@@ -47,6 +47,9 @@
     that are used in these methods and provide an API to interact with these
     types, per
     [CLC proposal #85](https://github.com/haskell/core-libraries-committee/issues/85).
+  * The `Enum` instance of `Down a` now enumerates values in the opposite
+    order as the `Enum a` instance, per
+    [CLC proposal #51](https://github.com/haskell/core-libraries-committee/issues/51).
 
 ## 4.17.0.0 *August 2022*
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8c72411d9504963069fb1ae736a2470cb9ae1250

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8c72411d9504963069fb1ae736a2470cb9ae1250
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/20221017/75b3ba3d/attachment-0001.html>


More information about the ghc-commits mailing list