Skip to content
Snippets Groups Projects
Commit 8c72411d authored by Gergő Érdi's avatar Gergő Érdi Committed by Marge Bot
Browse files

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
parent c1e5719a
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
......@@ -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*
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment