Skip to content
Commits on Source (2)
......@@ -156,4 +156,3 @@ instance (MonadFix f, MonadFix g) => MonadFix (f :*: g) where
-- | @since 4.12.0.0
instance MonadFix Down where
mfix f = Down (fix (getDown . f))
where getDown (Down x) = x
......@@ -7,7 +7,7 @@
-- Module : Data.Ord
-- Copyright : (c) The University of Glasgow 2005
-- License : BSD-style (see the file libraries/base/LICENSE)
--
--
-- Maintainer : libraries@haskell.org
-- Stability : stable
-- Portability : portable
......@@ -23,12 +23,18 @@ module Data.Ord (
comparing,
) where
import Data.Bits (Bits, FiniteBits)
import Foreign.Storable (Storable)
import GHC.Arr (Ix)
import GHC.Base
import GHC.Show
import GHC.Read
import GHC.Enum (Bounded, Enum)
import GHC.Float (Floating, RealFloat)
import GHC.Num
import GHC.Read
import GHC.Real (Fractional, Integral, Real, RealFrac)
import GHC.Show
-- |
-- |
-- > comparing p x y = compare (p x) (p y)
--
-- Useful combinator for use in conjunction with the @xxxBy@ family
......@@ -46,16 +52,44 @@ comparing p x y = compare (p x) (p y)
-- as in: @then sortWith by 'Down' x@
--
-- @since 4.6.0.0
newtype Down a = Down a
newtype Down a = Down
{ getDown :: a -- ^ @since 4.14.0.0
}
deriving
( Eq -- ^ @since 4.6.0.0
, Show -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
, Num -- ^ @since 4.11.0.0
, Semigroup -- ^ @since 4.11.0.0
, Monoid -- ^ @since 4.11.0.0
, Bits -- ^ @since 4.14.0.0
, Bounded -- ^ @since 4.14.0.0
, Enum -- ^ @since 4.14.0.0
, FiniteBits -- ^ @since 4.14.0.0
, Floating -- ^ @since 4.14.0.0
, Fractional -- ^ @since 4.14.0.0
, Integral -- ^ @since 4.14.0.0
, Ix -- ^ @since 4.14.0.0
, Real -- ^ @since 4.14.0.0
, RealFrac -- ^ @since 4.14.0.0
, RealFloat -- ^ @since 4.14.0.0
, Storable -- ^ @since 4.14.0.0
)
-- | This instance would be equivalent to the derived instances of the
-- 'Down' newtype if the 'getDown' field were removed
--
-- @since 4.7.0.0
instance (Read a) => Read (Down a) where
readsPrec d = readParen (d > 10) $ \ r ->
[(Down x,t) | ("Down",s) <- lex r, (x,t) <- readsPrec 11 s]
-- | This instance would be equivalent to the derived instances of the
-- 'Down' newtype if the 'getDown' field were removed
--
-- @since 4.7.0.0
instance (Show a) => Show (Down a) where
showsPrec d (Down x) = showParen (d > 10) $
showString "Down " . showsPrec 11 x
-- | @since 4.6.0.0
instance Ord a => Ord (Down a) where
compare (Down x) (Down y) = y `compare` x
......
......@@ -5,6 +5,12 @@
* Add a `TestEquality` instance for the `Compose` newtype.
* `Data.Ord.Down` now has a field name, `getDown`
* Add `Bits`, `Bounded`, `Enum`, `FiniteBits`, `Floating`, `Fractional`,
`Integral`, `Ix`, `Real`, `RealFrac`, `RealFloat` and `Storable` instances
to `Data.Ord.Down`.
* Fix the `integer-gmp` variant of `isValidNatural`: Previously it would fail
to detect values `<= maxBound::Word` that were incorrectly encoded using
the `NatJ#` constructor.
......