{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE GeneralizedNewtypeDeriving #-}------------------------------------------------------------------------------- |-- 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---- Orderings-------------------------------------------------------------------------------moduleData.Ord(Ord (..),Ordering (..),Down (..),comparing ,clamp ,)whereimportData.Bits (Bits ,FiniteBits )importForeign.Storable (Storable )importGHC.Ix (Ix )importGHC.Base importGHC.Enum (Bounded (..))importGHC.Float (Floating ,RealFloat )importGHC.Num importGHC.Read importGHC.Real (Fractional ,Real ,RealFrac )importGHC.Show -- $setup-- >>> import Prelude-- |-- > comparing p x y = compare (p x) (p y)---- Useful combinator for use in conjunction with the @xxxBy@ family-- of functions from "Data.List", for example:---- > ... sortBy (comparing fst) ...comparing ::(Ord a )=>(b ->a )->b ->b ->Ordering comparing :: forall a b. Ord a => (b -> a) -> b -> b -> Ordering comparing b -> a p b x b y =forall a. Ord a => a -> a -> Ordering compare (b -> a p b x )(b -> a p b y )-- |-- > clamp (low, high) a = min high (max a low)---- Function for ensursing the value @a@ is within the inclusive bounds given by-- @low@ and @high@. If it is, @a@ is returned unchanged. The result-- is otherwise @low@ if @a <= low@, or @high@ if @high <= a@.---- When clamp is used at Double and Float, it has NaN propagating semantics in-- its second argument. That is, @clamp (l,h) NaN = NaN@, but @clamp (NaN, NaN)-- x = x@.---- >>> clamp (0, 10) 2-- 2---- >>> clamp ('a', 'm') 'x'-- 'm'clamp ::(Ord a )=>(a ,a )->a ->a clamp :: forall a. Ord a => (a, a) -> a -> a clamp (a low ,a high )a a =forall a. Ord a => a -> a -> a min a high (forall a. Ord a => a -> a -> a max a a a low )-- | The 'Down' type allows you to reverse sort order conveniently. A value of type-- @'Down' a@ contains a value of type @a@ (represented as @'Down' a@).---- If @a@ has an @'Ord'@ instance associated with it then comparing two-- values thus wrapped will give you the opposite of their normal sort order.-- This is particularly useful when sorting in generalised list comprehensions,-- as in: @then sortWith by 'Down' x@.---- >>> compare True False-- GT---- >>> compare (Down True) (Down False)-- LT---- If @a@ has a @'Bounded'@ instance then the wrapped instance also respects-- the reversed ordering by exchanging the values of @'minBound'@ and-- @'maxBound'@.---- >>> minBound :: Int-- -9223372036854775808---- >>> minBound :: Down Int-- Down 9223372036854775807---- All other instances of @'Down' a@ behave as they do for @a@.---- @since 4.6.0.0newtypeDown a =Down {forall a. Down a -> a getDown ::a -- ^ @since 4.14.0.0}deriving(Down a -> Down a -> Bool forall a. Eq a => Down a -> Down a -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Down a -> Down a -> Bool $c/= :: forall a. Eq a => Down a -> Down a -> Bool == :: Down a -> Down a -> Bool $c== :: forall a. Eq a => Down a -> Down a -> Bool Eq -- ^ @since 4.6.0.0,Integer -> Down a Down a -> Down a Down a -> Down a -> Down a forall a. Num a => Integer -> Down a forall a. Num a => Down a -> Down a forall a. Num a => Down a -> Down a -> Down a forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> Down a $cfromInteger :: forall a. Num a => Integer -> Down a signum :: Down a -> Down a $csignum :: forall a. Num a => Down a -> Down a abs :: Down a -> Down a $cabs :: forall a. Num a => Down a -> Down a negate :: Down a -> Down a $cnegate :: forall a. Num a => Down a -> Down a * :: Down a -> Down a -> Down a $c* :: forall a. Num a => Down a -> Down a -> Down a - :: Down a -> Down a -> Down a $c- :: forall a. Num a => Down a -> Down a -> Down a + :: Down a -> Down a -> Down a $c+ :: forall a. Num a => Down a -> Down a -> Down a Num -- ^ @since 4.11.0.0,NonEmpty (Down a) -> Down a Down a -> Down a -> Down a forall b. Integral b => b -> Down a -> Down a forall a. Semigroup a => NonEmpty (Down a) -> Down a forall a. Semigroup a => Down a -> Down a -> Down a forall a b. (Semigroup a, Integral b) => b -> Down a -> Down a forall a. (a -> a -> a) -> (NonEmpty a -> a) -> (forall b. Integral b => b -> a -> a) -> Semigroup a stimes :: forall b. Integral b => b -> Down a -> Down a $cstimes :: forall a b. (Semigroup a, Integral b) => b -> Down a -> Down a sconcat :: NonEmpty (Down a) -> Down a $csconcat :: forall a. Semigroup a => NonEmpty (Down a) -> Down a <> :: Down a -> Down a -> Down a $c<> :: forall a. Semigroup a => Down a -> Down a -> Down a Semigroup -- ^ @since 4.11.0.0,Down a [Down a] -> Down a Down a -> Down a -> Down a forall a. Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a forall {a}. Monoid a => Semigroup (Down a) forall a. Monoid a => Down a forall a. Monoid a => [Down a] -> Down a forall a. Monoid a => Down a -> Down a -> Down a mconcat :: [Down a] -> Down a $cmconcat :: forall a. Monoid a => [Down a] -> Down a mappend :: Down a -> Down a -> Down a $cmappend :: forall a. Monoid a => Down a -> Down a -> Down a mempty :: Down a $cmempty :: forall a. Monoid a => Down a Monoid -- ^ @since 4.11.0.0,Down a Int -> Down a Down a -> Bool Down a -> Int Down a -> Maybe Int Down a -> Down a Down a -> Int -> Bool Down a -> Int -> Down a Down a -> Down a -> Down a forall a. Eq a -> (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> a -> (Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> Bool) -> (a -> Maybe Int) -> (a -> Int) -> (a -> Bool) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int) -> Bits a forall {a}. Bits a => Eq (Down a) forall a. Bits a => Down a forall a. Bits a => Int -> Down a forall a. Bits a => Down a -> Bool forall a. Bits a => Down a -> Int forall a. Bits a => Down a -> Maybe Int forall a. Bits a => Down a -> Down a forall a. Bits a => Down a -> Int -> Bool forall a. Bits a => Down a -> Int -> Down a forall a. Bits a => Down a -> Down a -> Down a popCount :: Down a -> Int $cpopCount :: forall a. Bits a => Down a -> Int rotateR :: Down a -> Int -> Down a $crotateR :: forall a. Bits a => Down a -> Int -> Down a rotateL :: Down a -> Int -> Down a $crotateL :: forall a. Bits a => Down a -> Int -> Down a unsafeShiftR :: Down a -> Int -> Down a $cunsafeShiftR :: forall a. Bits a => Down a -> Int -> Down a shiftR :: Down a -> Int -> Down a $cshiftR :: forall a. Bits a => Down a -> Int -> Down a unsafeShiftL :: Down a -> Int -> Down a $cunsafeShiftL :: forall a. Bits a => Down a -> Int -> Down a shiftL :: Down a -> Int -> Down a $cshiftL :: forall a. Bits a => Down a -> Int -> Down a isSigned :: Down a -> Bool $cisSigned :: forall a. Bits a => Down a -> Bool bitSize :: Down a -> Int $cbitSize :: forall a. Bits a => Down a -> Int bitSizeMaybe :: Down a -> Maybe Int $cbitSizeMaybe :: forall a. Bits a => Down a -> Maybe Int testBit :: Down a -> Int -> Bool $ctestBit :: forall a. Bits a => Down a -> Int -> Bool complementBit :: Down a -> Int -> Down a $ccomplementBit :: forall a. Bits a => Down a -> Int -> Down a clearBit :: Down a -> Int -> Down a $cclearBit :: forall a. Bits a => Down a -> Int -> Down a setBit :: Down a -> Int -> Down a $csetBit :: forall a. Bits a => Down a -> Int -> Down a bit :: Int -> Down a $cbit :: forall a. Bits a => Int -> Down a zeroBits :: Down a $czeroBits :: forall a. Bits a => Down a rotate :: Down a -> Int -> Down a $crotate :: forall a. Bits a => Down a -> Int -> Down a shift :: Down a -> Int -> Down a $cshift :: forall a. Bits a => Down a -> Int -> Down a complement :: Down a -> Down a $ccomplement :: forall a. Bits a => Down a -> Down a xor :: Down a -> Down a -> Down a $cxor :: forall a. Bits a => Down a -> Down a -> Down a .|. :: Down a -> Down a -> Down a $c.|. :: forall a. Bits a => Down a -> Down a -> Down a .&. :: Down a -> Down a -> Down a $c.&. :: forall a. Bits a => Down a -> Down a -> Down a Bits -- ^ @since 4.14.0.0,Down a -> Int forall b. Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b forall {a}. FiniteBits a => Bits (Down a) forall a. FiniteBits a => Down a -> Int countTrailingZeros :: Down a -> Int $ccountTrailingZeros :: forall a. FiniteBits a => Down a -> Int countLeadingZeros :: Down a -> Int $ccountLeadingZeros :: forall a. FiniteBits a => Down a -> Int finiteBitSize :: Down a -> Int $cfiniteBitSize :: forall a. FiniteBits a => Down a -> Int FiniteBits -- ^ @since 4.14.0.0,Down a Down a -> Down a Down a -> Down a -> Down a forall {a}. Floating a => Fractional (Down a) forall a. Floating a => Down a forall a. Floating a => Down a -> Down a forall a. Floating a => Down a -> Down a -> Down a forall a. Fractional a -> a -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> Floating a log1mexp :: Down a -> Down a $clog1mexp :: forall a. Floating a => Down a -> Down a log1pexp :: Down a -> Down a $clog1pexp :: forall a. Floating a => Down a -> Down a expm1 :: Down a -> Down a $cexpm1 :: forall a. Floating a => Down a -> Down a log1p :: Down a -> Down a $clog1p :: forall a. Floating a => Down a -> Down a atanh :: Down a -> Down a $catanh :: forall a. Floating a => Down a -> Down a acosh :: Down a -> Down a $cacosh :: forall a. Floating a => Down a -> Down a asinh :: Down a -> Down a $casinh :: forall a. Floating a => Down a -> Down a tanh :: Down a -> Down a $ctanh :: forall a. Floating a => Down a -> Down a cosh :: Down a -> Down a $ccosh :: forall a. Floating a => Down a -> Down a sinh :: Down a -> Down a $csinh :: forall a. Floating a => Down a -> Down a atan :: Down a -> Down a $catan :: forall a. Floating a => Down a -> Down a acos :: Down a -> Down a $cacos :: forall a. Floating a => Down a -> Down a asin :: Down a -> Down a $casin :: forall a. Floating a => Down a -> Down a tan :: Down a -> Down a $ctan :: forall a. Floating a => Down a -> Down a cos :: Down a -> Down a $ccos :: forall a. Floating a => Down a -> Down a sin :: Down a -> Down a $csin :: forall a. Floating a => Down a -> Down a logBase :: Down a -> Down a -> Down a $clogBase :: forall a. Floating a => Down a -> Down a -> Down a ** :: Down a -> Down a -> Down a $c** :: forall a. Floating a => Down a -> Down a -> Down a sqrt :: Down a -> Down a $csqrt :: forall a. Floating a => Down a -> Down a log :: Down a -> Down a $clog :: forall a. Floating a => Down a -> Down a exp :: Down a -> Down a $cexp :: forall a. Floating a => Down a -> Down a pi :: Down a $cpi :: forall a. Floating a => Down a Floating -- ^ @since 4.14.0.0,Rational -> Down a Down a -> Down a Down a -> Down a -> Down a forall {a}. Fractional a => Num (Down a) forall a. Fractional a => Rational -> Down a forall a. Fractional a => Down a -> Down a forall a. Fractional a => Down a -> Down a -> Down a forall a. Num a -> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a fromRational :: Rational -> Down a $cfromRational :: forall a. Fractional a => Rational -> Down a recip :: Down a -> Down a $crecip :: forall a. Fractional a => Down a -> Down a / :: Down a -> Down a -> Down a $c/ :: forall a. Fractional a => Down a -> Down a -> Down a Fractional -- ^ @since 4.14.0.0,(Down a, Down a) -> Int (Down a, Down a) -> [Down a] (Down a, Down a) -> Down a -> Bool (Down a, Down a) -> Down a -> Int forall a. Ord a -> ((a, a) -> [a]) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Bool) -> ((a, a) -> Int) -> ((a, a) -> Int) -> Ix a forall {a}. Ix a => Ord (Down a) forall a. Ix a => (Down a, Down a) -> Int forall a. Ix a => (Down a, Down a) -> [Down a] forall a. Ix a => (Down a, Down a) -> Down a -> Bool forall a. Ix a => (Down a, Down a) -> Down a -> Int unsafeRangeSize :: (Down a, Down a) -> Int $cunsafeRangeSize :: forall a. Ix a => (Down a, Down a) -> Int rangeSize :: (Down a, Down a) -> Int $crangeSize :: forall a. Ix a => (Down a, Down a) -> Int inRange :: (Down a, Down a) -> Down a -> Bool $cinRange :: forall a. Ix a => (Down a, Down a) -> Down a -> Bool unsafeIndex :: (Down a, Down a) -> Down a -> Int $cunsafeIndex :: forall a. Ix a => (Down a, Down a) -> Down a -> Int index :: (Down a, Down a) -> Down a -> Int $cindex :: forall a. Ix a => (Down a, Down a) -> Down a -> Int range :: (Down a, Down a) -> [Down a] $crange :: forall a. Ix a => (Down a, Down a) -> [Down a] Ix -- ^ @since 4.14.0.0,Down a -> Rational forall a. Num a -> Ord a -> (a -> Rational) -> Real a forall {a}. Real a => Num (Down a) forall {a}. Real a => Ord (Down a) forall a. Real a => Down a -> Rational toRational :: Down a -> Rational $ctoRational :: forall a. Real a => Down a -> Rational Real -- ^ @since 4.14.0.0,forall b. Integral b => Down a -> b forall b. Integral b => Down a -> (b, Down a) forall a. Real a -> Fractional a -> (forall b. Integral b => a -> (b, a)) -> (forall b. Integral b => a -> b) -> (forall b. Integral b => a -> b) -> (forall b. Integral b => a -> b) -> (forall b. Integral b => a -> b) -> RealFrac a forall {a}. RealFrac a => Fractional (Down a) forall {a}. RealFrac a => Real (Down a) forall a b. (RealFrac a, Integral b) => Down a -> b forall a b. (RealFrac a, Integral b) => Down a -> (b, Down a) floor :: forall b. Integral b => Down a -> b $cfloor :: forall a b. (RealFrac a, Integral b) => Down a -> b ceiling :: forall b. Integral b => Down a -> b $cceiling :: forall a b. (RealFrac a, Integral b) => Down a -> b round :: forall b. Integral b => Down a -> b $cround :: forall a b. (RealFrac a, Integral b) => Down a -> b truncate :: forall b. Integral b => Down a -> b $ctruncate :: forall a b. (RealFrac a, Integral b) => Down a -> b properFraction :: forall b. Integral b => Down a -> (b, Down a) $cproperFraction :: forall a b. (RealFrac a, Integral b) => Down a -> (b, Down a) RealFrac -- ^ @since 4.14.0.0,Int -> Down a -> Down a Integer -> Int -> Down a Down a -> Bool Down a -> Int Down a -> Integer Down a -> (Int, Int) Down a -> (Integer, Int) Down a -> Down a Down a -> Down a -> Down a forall {a}. RealFloat a => Floating (Down a) forall {a}. RealFloat a => RealFrac (Down a) forall a. RealFloat a => Int -> Down a -> Down a forall a. RealFloat a => Integer -> Int -> Down a forall a. RealFloat a => Down a -> Bool forall a. RealFloat a => Down a -> Int forall a. RealFloat a => Down a -> Integer forall a. RealFloat a => Down a -> (Int, Int) forall a. RealFloat a => Down a -> (Integer, Int) forall a. RealFloat a => Down a -> Down a forall a. RealFloat a => Down a -> Down a -> Down a forall a. RealFrac a -> Floating a -> (a -> Integer) -> (a -> Int) -> (a -> (Int, Int)) -> (a -> (Integer, Int)) -> (Integer -> Int -> a) -> (a -> Int) -> (a -> a) -> (Int -> a -> a) -> (a -> Bool) -> (a -> Bool) -> (a -> Bool) -> (a -> Bool) -> (a -> Bool) -> (a -> a -> a) -> RealFloat a atan2 :: Down a -> Down a -> Down a $catan2 :: forall a. RealFloat a => Down a -> Down a -> Down a isIEEE :: Down a -> Bool $cisIEEE :: forall a. RealFloat a => Down a -> Bool isNegativeZero :: Down a -> Bool $cisNegativeZero :: forall a. RealFloat a => Down a -> Bool isDenormalized :: Down a -> Bool $cisDenormalized :: forall a. RealFloat a => Down a -> Bool isInfinite :: Down a -> Bool $cisInfinite :: forall a. RealFloat a => Down a -> Bool isNaN :: Down a -> Bool $cisNaN :: forall a. RealFloat a => Down a -> Bool scaleFloat :: Int -> Down a -> Down a $cscaleFloat :: forall a. RealFloat a => Int -> Down a -> Down a significand :: Down a -> Down a $csignificand :: forall a. RealFloat a => Down a -> Down a exponent :: Down a -> Int $cexponent :: forall a. RealFloat a => Down a -> Int encodeFloat :: Integer -> Int -> Down a $cencodeFloat :: forall a. RealFloat a => Integer -> Int -> Down a decodeFloat :: Down a -> (Integer, Int) $cdecodeFloat :: forall a. RealFloat a => Down a -> (Integer, Int) floatRange :: Down a -> (Int, Int) $cfloatRange :: forall a. RealFloat a => Down a -> (Int, Int) floatDigits :: Down a -> Int $cfloatDigits :: forall a. RealFloat a => Down a -> Int floatRadix :: Down a -> Integer $cfloatRadix :: forall a. RealFloat a => Down a -> Integer RealFloat -- ^ @since 4.14.0.0,Ptr (Down a) -> IO (Down a) Ptr (Down a) -> Int -> IO (Down a) Ptr (Down a) -> Int -> Down a -> IO () Ptr (Down a) -> Down a -> IO () Down a -> Int forall b. Ptr b -> Int -> IO (Down a) forall b. Ptr b -> Int -> Down a -> IO () forall a. Storable a => Ptr (Down a) -> IO (Down a) forall a. Storable a => Ptr (Down a) -> Int -> IO (Down a) forall a. Storable a => Ptr (Down a) -> Int -> Down a -> IO () forall a. Storable a => Ptr (Down a) -> Down a -> IO () forall a. Storable a => Down a -> Int forall a b. Storable a => Ptr b -> Int -> IO (Down a) forall a b. Storable a => Ptr b -> Int -> Down a -> IO () forall a. (a -> Int) -> (a -> Int) -> (Ptr a -> Int -> IO a) -> (Ptr a -> Int -> a -> IO ()) -> (forall b. Ptr b -> Int -> IO a) -> (forall b. Ptr b -> Int -> a -> IO ()) -> (Ptr a -> IO a) -> (Ptr a -> a -> IO ()) -> Storable a poke :: Ptr (Down a) -> Down a -> IO () $cpoke :: forall a. Storable a => Ptr (Down a) -> Down a -> IO () peek :: Ptr (Down a) -> IO (Down a) $cpeek :: forall a. Storable a => Ptr (Down a) -> IO (Down a) pokeByteOff :: forall b. Ptr b -> Int -> Down a -> IO () $cpokeByteOff :: forall a b. Storable a => Ptr b -> Int -> Down a -> IO () peekByteOff :: forall b. Ptr b -> Int -> IO (Down a) $cpeekByteOff :: forall a b. Storable a => Ptr b -> Int -> IO (Down a) pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () $cpokeElemOff :: forall a. Storable a => Ptr (Down a) -> Int -> Down a -> IO () peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) $cpeekElemOff :: forall a. Storable a => Ptr (Down a) -> Int -> IO (Down a) alignment :: Down a -> Int $calignment :: forall a. Storable a => Down a -> Int sizeOf :: Down a -> Int $csizeOf :: forall a. Storable a => Down a -> Int 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.0instance(Read a )=>Read (Down a )wherereadsPrec :: Int -> ReadS (Down a) readsPrec Int d =forall a. Bool -> ReadS a -> ReadS a readParen (Int d forall a. Ord a => a -> a -> Bool > Int 10)forall a b. (a -> b) -> a -> b $ \String r ->[(forall a. a -> Down a Down a x ,String t )|(String "Down",String s )<-ReadS String lex String r ,(a x ,String t )<-forall a. Read a => Int -> ReadS a readsPrec Int 11String s ]-- | This instance would be equivalent to the derived instances of the-- 'Down' newtype if the 'getDown' field were removed---- @since 4.7.0.0instance(Show a )=>Show (Down a )whereshowsPrec :: Int -> Down a -> ShowS showsPrec Int d (Down a x )=Bool -> ShowS -> ShowS showParen (Int d forall a. Ord a => a -> a -> Bool > Int 10)forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "Down "forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Show a => Int -> a -> ShowS showsPrec Int 11a x -- | @since 4.6.0.0instanceOrd a =>Ord (Down a )wherecompare :: Down a -> Down a -> Ordering compare (Down a x )(Down a y )=a y forall a. Ord a => a -> a -> Ordering `compare` a x -- | Swaps @'minBound'@ and @'maxBound'@ of the underlying type.---- @since 4.14.0.0instanceBounded a =>Bounded (Down a )whereminBound :: Down a minBound =forall a. a -> Down a Down forall a. Bounded a => a maxBound maxBound :: Down a maxBound =forall a. a -> Down a Down forall a. Bounded a => a minBound -- | @since 4.11.0.0instanceFunctor Down wherefmap :: forall a b. (a -> b) -> Down a -> Down b fmap =coerce :: forall a b. Coercible a b => a -> b coerce -- | @since 4.11.0.0instanceApplicative Down wherepure :: forall a. a -> Down a pure =forall a. a -> Down a Down <*> :: forall a b. Down (a -> b) -> Down a -> Down b (<*>) =coerce :: forall a b. Coercible a b => a -> b coerce -- | @since 4.11.0.0instanceMonad Down whereDown a a >>= :: forall a b. Down a -> (a -> Down b) -> Down b >>= a -> Down b k =a -> Down b k a a