base-4.19.1.0: Basic libraries
Copyright(c) The University of Glasgow 2005
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Ord

Description

Orderings

Synopsis

Documentation

class Eq a => Ord a where Source #

The Ord class is used for totally ordered datatypes.

Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.

Ord, as defined by the Haskell report, implements a total order and has the following properties:

Comparability
x <= y || y <= x = True
Transitivity
if x <= y && y <= z = True, then x <= z = True
Reflexivity
x <= x = True
Antisymmetry
if x <= y && y <= x = True, then x == y = True

The following operator interactions are expected to hold:

  1. x >= y = y <= x
  2. x < y = x <= y && x /= y
  3. x > y = y < x
  4. x < y = compare x y == LT
  5. x > y = compare x y == GT
  6. x == y = compare x y == EQ
  7. min x y == if x <= y then x else y = True
  8. max x y == if x >= y then x else y = True

Note that (7.) and (8.) do not require min and max to return either of their arguments. The result is merely required to equal one of the arguments in terms of (==).

Minimal complete definition: either compare or <=. Using compare can be more efficient for complex types.

Minimal complete definition

compare | (<=)

Methods

compare :: a -> a -> Ordering Source #

(<) :: a -> a -> Bool infix 4 Source #

(<=) :: a -> a -> Bool infix 4 Source #

(>) :: a -> a -> Bool infix 4 Source #

(>=) :: a -> a -> Bool infix 4 Source #

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances

Instances details
Ord ByteArray Source #

Non-lexicographic ordering. This compares the lengths of the byte arrays first and uses a lexicographic ordering if the lengths are equal. Subject to change between major versions.

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Ord All Source #

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering Source #

(<) :: All -> All -> Bool Source #

(<=) :: All -> All -> Bool Source #

(>) :: All -> All -> Bool Source #

(>=) :: All -> All -> Bool Source #

max :: All -> All -> All Source #

min :: All -> All -> All Source #

Ord Any Source #

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering Source #

(<) :: Any -> Any -> Bool Source #

(<=) :: Any -> Any -> Bool Source #

(>) :: Any -> Any -> Bool Source #

(>=) :: Any -> Any -> Bool Source #

max :: Any -> Any -> Any Source #

min :: Any -> Any -> Any Source #

Ord SomeTypeRep Source # 
Instance details

Defined in Data.Typeable.Internal

Ord Unique Source # 
Instance details

Defined in Data.Unique

Ord Version Source #

Since: base-2.1

Instance details

Defined in Data.Version

Ord CBool Source # 
Instance details

Defined in Foreign.C.Types

Ord CChar Source # 
Instance details

Defined in Foreign.C.Types

Ord CClock Source # 
Instance details

Defined in Foreign.C.Types

Ord CDouble Source # 
Instance details

Defined in Foreign.C.Types

Ord CFloat Source # 
Instance details

Defined in Foreign.C.Types

Ord CInt Source # 
Instance details

Defined in Foreign.C.Types

Ord CIntMax Source # 
Instance details

Defined in Foreign.C.Types

Ord CIntPtr Source # 
Instance details

Defined in Foreign.C.Types

Ord CLLong Source # 
Instance details

Defined in Foreign.C.Types

Ord CLong Source # 
Instance details

Defined in Foreign.C.Types

Ord CPtrdiff Source # 
Instance details

Defined in Foreign.C.Types

Ord CSChar Source # 
Instance details

Defined in Foreign.C.Types

Ord CSUSeconds Source # 
Instance details

Defined in Foreign.C.Types

Ord CShort Source # 
Instance details

Defined in Foreign.C.Types

Ord CSigAtomic Source # 
Instance details

Defined in Foreign.C.Types

Ord CSize Source # 
Instance details

Defined in Foreign.C.Types

Ord CTime Source # 
Instance details

Defined in Foreign.C.Types

Ord CUChar Source # 
Instance details

Defined in Foreign.C.Types

Ord CUInt Source # 
Instance details

Defined in Foreign.C.Types

Ord CUIntMax Source # 
Instance details

Defined in Foreign.C.Types

Ord CUIntPtr Source # 
Instance details

Defined in Foreign.C.Types

Ord CULLong Source # 
Instance details

Defined in Foreign.C.Types

Ord CULong Source # 
Instance details

Defined in Foreign.C.Types

Ord CUSeconds Source # 
Instance details

Defined in Foreign.C.Types

Ord CUShort Source # 
Instance details

Defined in Foreign.C.Types

Ord CWchar Source # 
Instance details

Defined in Foreign.C.Types

Ord IntPtr Source # 
Instance details

Defined in Foreign.Ptr

Ord WordPtr Source # 
Instance details

Defined in Foreign.Ptr

Ord Void Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Base

Ord ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Ord BlockReason Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadId Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadStatus Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord TimeoutKey Source # 
Instance details

Defined in GHC.Event.TimeOut

Ord ErrorCall Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Exception

Ord ArithException Source #

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Ord Fingerprint Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Ord Associativity Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ord DecidedStrictness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord Fixity Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ord SourceStrictness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord SourceUnpackedness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord SeekMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Ord ArrayException Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord AsyncException Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord ExitCode Source # 
Instance details

Defined in GHC.IO.Exception

Ord BufferMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord Newline Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord NewlineMode Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord IOMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ord Int16 Source #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32 Source #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64 Source #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int8 Source #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord SomeChar Source # 
Instance details

Defined in GHC.TypeLits

Ord SomeSymbol Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Ord SomeNat Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Ord GeneralCategory Source #

Since: base-2.1

Instance details

Defined in GHC.Unicode

Ord Word16 Source #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32 Source #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64 Source #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8 Source #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord CBlkCnt Source # 
Instance details

Defined in System.Posix.Types

Ord CBlkSize Source # 
Instance details

Defined in System.Posix.Types

Ord CCc Source # 
Instance details

Defined in System.Posix.Types

Methods

compare :: CCc -> CCc -> Ordering Source #

(<) :: CCc -> CCc -> Bool Source #

(<=) :: CCc -> CCc -> Bool Source #

(>) :: CCc -> CCc -> Bool Source #

(>=) :: CCc -> CCc -> Bool Source #

max :: CCc -> CCc -> CCc Source #

min :: CCc -> CCc -> CCc Source #

Ord CClockId Source # 
Instance details

Defined in System.Posix.Types

Ord CDev Source # 
Instance details

Defined in System.Posix.Types

Ord CFsBlkCnt Source # 
Instance details

Defined in System.Posix.Types

Ord CFsFilCnt Source # 
Instance details

Defined in System.Posix.Types

Ord CGid Source # 
Instance details

Defined in System.Posix.Types

Ord CId Source # 
Instance details

Defined in System.Posix.Types

Methods

compare :: CId -> CId -> Ordering Source #

(<) :: CId -> CId -> Bool Source #

(<=) :: CId -> CId -> Bool Source #

(>) :: CId -> CId -> Bool Source #

(>=) :: CId -> CId -> Bool Source #

max :: CId -> CId -> CId Source #

min :: CId -> CId -> CId Source #

Ord CIno Source # 
Instance details

Defined in System.Posix.Types

Ord CKey Source # 
Instance details

Defined in System.Posix.Types

Ord CMode Source # 
Instance details

Defined in System.Posix.Types

Ord CNfds Source # 
Instance details

Defined in System.Posix.Types

Ord CNlink Source # 
Instance details

Defined in System.Posix.Types

Ord COff Source # 
Instance details

Defined in System.Posix.Types

Ord CPid Source # 
Instance details

Defined in System.Posix.Types

Ord CRLim Source # 
Instance details

Defined in System.Posix.Types

Ord CSocklen Source # 
Instance details

Defined in System.Posix.Types

Ord CSpeed Source # 
Instance details

Defined in System.Posix.Types

Ord CSsize Source # 
Instance details

Defined in System.Posix.Types

Ord CTcflag Source # 
Instance details

Defined in System.Posix.Types

Ord CTimer Source # 
Instance details

Defined in System.Posix.Types

Ord CUid Source # 
Instance details

Defined in System.Posix.Types

Ord Fd Source # 
Instance details

Defined in System.Posix.Types

Methods

compare :: Fd -> Fd -> Ordering Source #

(<) :: Fd -> Fd -> Bool Source #

(<=) :: Fd -> Fd -> Bool Source #

(>) :: Fd -> Fd -> Bool Source #

(>=) :: Fd -> Fd -> Bool Source #

max :: Fd -> Fd -> Fd Source #

min :: Fd -> Fd -> Fd Source #

Ord BigNat 
Instance details

Defined in GHC.Num.BigNat

Ord Ordering 
Instance details

Defined in GHC.Classes

Ord TyCon 
Instance details

Defined in GHC.Classes

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Ord Natural 
Instance details

Defined in GHC.Num.Natural

Ord () 
Instance details

Defined in GHC.Classes

Methods

compare :: () -> () -> Ordering Source #

(<) :: () -> () -> Bool Source #

(<=) :: () -> () -> Bool Source #

(>) :: () -> () -> Bool Source #

(>=) :: () -> () -> Bool Source #

max :: () -> () -> () Source #

min :: () -> () -> () Source #

Ord Bool 
Instance details

Defined in GHC.Classes

Ord Char 
Instance details

Defined in GHC.Classes

Ord Double

IEEE 754 Double-precision type includes not only numbers, but also positive and negative infinities and a special element called NaN (which can be quiet or signal).

IEEE 754-2008, section 5.11 requires that if at least one of arguments of <=, <, >, >= is NaN then the result of the comparison is False, and instance Ord Double complies with this requirement. This violates the reflexivity: both NaN <= NaN and NaN >= NaN are False.

IEEE 754-2008, section 5.10 defines totalOrder predicate. Unfortunately, compare on Doubles violates the IEEE standard and does not define a total order. More specifically, both compare NaN x and compare x NaN always return GT.

Thus, users must be extremely cautious when using instance Ord Double. For instance, one should avoid ordered containers with keys represented by Double, because data loss and corruption may happen. An IEEE-compliant compare is available in fp-ieee package as TotallyOrdered newtype.

Moving further, the behaviour of min and max with regards to NaN is also non-compliant. IEEE 754-2008, section 5.3.1 defines that quiet NaN should be treated as a missing data by minNum and maxNum functions, for example, minNum(NaN, 1) = minNum(1, NaN) = 1. Some languages such as Java deviate from the standard implementing minNum(NaN, 1) = minNum(1, NaN) = NaN. However, min / max in base are even worse: min NaN 1 is 1, but min 1 NaN is NaN.

IEEE 754-2008 compliant min / max can be found in ieee754 package under minNum / maxNum names. Implementations compliant with minimumNumber / maximumNumber from a newer IEEE 754-2019, section 9.6 are available from fp-ieee package.

Instance details

Defined in GHC.Classes

Ord Float

See instance Ord Double for discussion of deviations from IEEE 754 standard.

Instance details

Defined in GHC.Classes

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering Source #

(<) :: Int -> Int -> Bool Source #

(<=) :: Int -> Int -> Bool Source #

(>) :: Int -> Int -> Bool Source #

(>=) :: Int -> Int -> Bool Source #

max :: Int -> Int -> Int Source #

min :: Int -> Int -> Int Source #

Ord Word 
Instance details

Defined in GHC.Classes

Ord a => Ord (ZipList a) Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Ord a => Ord (Identity a) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Ord a => Ord (First a) Source #

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: First a -> First a -> Ordering Source #

(<) :: First a -> First a -> Bool Source #

(<=) :: First a -> First a -> Bool Source #

(>) :: First a -> First a -> Bool Source #

(>=) :: First a -> First a -> Bool Source #

max :: First a -> First a -> First a Source #

min :: First a -> First a -> First a Source #

Ord a => Ord (Last a) Source #

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: Last a -> Last a -> Ordering Source #

(<) :: Last a -> Last a -> Bool Source #

(<=) :: Last a -> Last a -> Bool Source #

(>) :: Last a -> Last a -> Bool Source #

(>=) :: Last a -> Last a -> Bool Source #

max :: Last a -> Last a -> Last a Source #

min :: Last a -> Last a -> Last a Source #

Ord a => Ord (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

compare :: Down a -> Down a -> Ordering Source #

(<) :: Down a -> Down a -> Bool Source #

(<=) :: Down a -> Down a -> Bool Source #

(>) :: Down a -> Down a -> Bool Source #

(>=) :: Down a -> Down a -> Bool Source #

max :: Down a -> Down a -> Down a Source #

min :: Down a -> Down a -> Down a Source #

Ord a => Ord (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: First a -> First a -> Ordering Source #

(<) :: First a -> First a -> Bool Source #

(<=) :: First a -> First a -> Bool Source #

(>) :: First a -> First a -> Bool Source #

(>=) :: First a -> First a -> Bool Source #

max :: First a -> First a -> First a Source #

min :: First a -> First a -> First a Source #

Ord a => Ord (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Last a -> Last a -> Ordering Source #

(<) :: Last a -> Last a -> Bool Source #

(<=) :: Last a -> Last a -> Bool Source #

(>) :: Last a -> Last a -> Bool Source #

(>=) :: Last a -> Last a -> Bool Source #

max :: Last a -> Last a -> Last a Source #

min :: Last a -> Last a -> Last a Source #

Ord a => Ord (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Max a -> Max a -> Ordering Source #

(<) :: Max a -> Max a -> Bool Source #

(<=) :: Max a -> Max a -> Bool Source #

(>) :: Max a -> Max a -> Bool Source #

(>=) :: Max a -> Max a -> Bool Source #

max :: Max a -> Max a -> Max a Source #

min :: Max a -> Max a -> Max a Source #

Ord a => Ord (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Min a -> Min a -> Ordering Source #

(<) :: Min a -> Min a -> Bool Source #

(<=) :: Min a -> Min a -> Bool Source #

(>) :: Min a -> Min a -> Bool Source #

(>=) :: Min a -> Min a -> Bool Source #

max :: Min a -> Min a -> Min a Source #

min :: Min a -> Min a -> Min a Source #

Ord m => Ord (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord (Dual a) Source #

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> Ordering Source #

(<) :: Dual a -> Dual a -> Bool Source #

(<=) :: Dual a -> Dual a -> Bool Source #

(>) :: Dual a -> Dual a -> Bool Source #

(>=) :: Dual a -> Dual a -> Bool Source #

max :: Dual a -> Dual a -> Dual a Source #

min :: Dual a -> Dual a -> Dual a Source #

Ord a => Ord (Product a) Source #

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord (Sum a) Source #

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering Source #

(<) :: Sum a -> Sum a -> Bool Source #

(<=) :: Sum a -> Sum a -> Bool Source #

(>) :: Sum a -> Sum a -> Bool Source #

(>=) :: Sum a -> Sum a -> Bool Source #

max :: Sum a -> Sum a -> Sum a Source #

min :: Sum a -> Sum a -> Sum a Source #

Ord (ConstPtr a) Source # 
Instance details

Defined in Foreign.C.ConstPtr

Ord a => Ord (NonEmpty a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Ord (ForeignPtr a) Source #

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Ord p => Ord (Par1 p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: Par1 p -> Par1 p -> Ordering Source #

(<) :: Par1 p -> Par1 p -> Bool Source #

(<=) :: Par1 p -> Par1 p -> Bool Source #

(>) :: Par1 p -> Par1 p -> Bool Source #

(>=) :: Par1 p -> Par1 p -> Bool Source #

max :: Par1 p -> Par1 p -> Par1 p Source #

min :: Par1 p -> Par1 p -> Par1 p Source #

Ord (FunPtr a) Source # 
Instance details

Defined in GHC.Ptr

Methods

compare :: FunPtr a -> FunPtr a -> Ordering Source #

(<) :: FunPtr a -> FunPtr a -> Bool Source #

(<=) :: FunPtr a -> FunPtr a -> Bool Source #

(>) :: FunPtr a -> FunPtr a -> Bool Source #

(>=) :: FunPtr a -> FunPtr a -> Bool Source #

max :: FunPtr a -> FunPtr a -> FunPtr a Source #

min :: FunPtr a -> FunPtr a -> FunPtr a Source #

Ord (Ptr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering Source #

(<) :: Ptr a -> Ptr a -> Bool Source #

(<=) :: Ptr a -> Ptr a -> Bool Source #

(>) :: Ptr a -> Ptr a -> Bool Source #

(>=) :: Ptr a -> Ptr a -> Bool Source #

max :: Ptr a -> Ptr a -> Ptr a Source #

min :: Ptr a -> Ptr a -> Ptr a Source #

Integral a => Ord (Ratio a) Source #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

compare :: Ratio a -> Ratio a -> Ordering Source #

(<) :: Ratio a -> Ratio a -> Bool Source #

(<=) :: Ratio a -> Ratio a -> Bool Source #

(>) :: Ratio a -> Ratio a -> Bool Source #

(>=) :: Ratio a -> Ratio a -> Bool Source #

max :: Ratio a -> Ratio a -> Ratio a Source #

min :: Ratio a -> Ratio a -> Ratio a Source #

Ord (SChar c) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.TypeLits

Methods

compare :: SChar c -> SChar c -> Ordering Source #

(<) :: SChar c -> SChar c -> Bool Source #

(<=) :: SChar c -> SChar c -> Bool Source #

(>) :: SChar c -> SChar c -> Bool Source #

(>=) :: SChar c -> SChar c -> Bool Source #

max :: SChar c -> SChar c -> SChar c Source #

min :: SChar c -> SChar c -> SChar c Source #

Ord (SSymbol s) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.TypeLits

Ord (SNat n) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.TypeNats

Methods

compare :: SNat n -> SNat n -> Ordering Source #

(<) :: SNat n -> SNat n -> Bool Source #

(<=) :: SNat n -> SNat n -> Bool Source #

(>) :: SNat n -> SNat n -> Bool Source #

(>=) :: SNat n -> SNat n -> Bool Source #

max :: SNat n -> SNat n -> SNat n Source #

min :: SNat n -> SNat n -> SNat n Source #

Ord a => Ord (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering Source #

(<) :: Maybe a -> Maybe a -> Bool Source #

(<=) :: Maybe a -> Maybe a -> Bool Source #

(>) :: Maybe a -> Maybe a -> Bool Source #

(>=) :: Maybe a -> Maybe a -> Bool Source #

max :: Maybe a -> Maybe a -> Maybe a Source #

min :: Maybe a -> Maybe a -> Maybe a Source #

Ord a => Ord (Solo a) 
Instance details

Defined in GHC.Classes

Methods

compare :: Solo a -> Solo a -> Ordering Source #

(<) :: Solo a -> Solo a -> Bool Source #

(<=) :: Solo a -> Solo a -> Bool Source #

(>) :: Solo a -> Solo a -> Bool Source #

(>=) :: Solo a -> Solo a -> Bool Source #

max :: Solo a -> Solo a -> Solo a Source #

min :: Solo a -> Solo a -> Solo a Source #

Ord a => Ord [a] 
Instance details

Defined in GHC.Classes

Methods

compare :: [a] -> [a] -> Ordering Source #

(<) :: [a] -> [a] -> Bool Source #

(<=) :: [a] -> [a] -> Bool Source #

(>) :: [a] -> [a] -> Bool Source #

(>=) :: [a] -> [a] -> Bool Source #

max :: [a] -> [a] -> [a] Source #

min :: [a] -> [a] -> [a] Source #

(Ord a, Ord b) => Ord (Either a b) Source #

Since: base-2.1

Instance details

Defined in Data.Either

Methods

compare :: Either a b -> Either a b -> Ordering Source #

(<) :: Either a b -> Either a b -> Bool Source #

(<=) :: Either a b -> Either a b -> Bool Source #

(>) :: Either a b -> Either a b -> Bool Source #

(>=) :: Either a b -> Either a b -> Bool Source #

max :: Either a b -> Either a b -> Either a b Source #

min :: Either a b -> Either a b -> Either a b Source #

Ord (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

compare :: Fixed a -> Fixed a -> Ordering Source #

(<) :: Fixed a -> Fixed a -> Bool Source #

(<=) :: Fixed a -> Fixed a -> Bool Source #

(>) :: Fixed a -> Fixed a -> Bool Source #

(>=) :: Fixed a -> Fixed a -> Bool Source #

max :: Fixed a -> Fixed a -> Fixed a Source #

min :: Fixed a -> Fixed a -> Fixed a Source #

Ord (Proxy s) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering Source #

(<) :: Proxy s -> Proxy s -> Bool Source #

(<=) :: Proxy s -> Proxy s -> Bool Source #

(>) :: Proxy s -> Proxy s -> Bool Source #

(>=) :: Proxy s -> Proxy s -> Bool Source #

max :: Proxy s -> Proxy s -> Proxy s Source #

min :: Proxy s -> Proxy s -> Proxy s Source #

Ord a => Ord (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Arg a b -> Arg a b -> Ordering Source #

(<) :: Arg a b -> Arg a b -> Bool Source #

(<=) :: Arg a b -> Arg a b -> Bool Source #

(>) :: Arg a b -> Arg a b -> Bool Source #

(>=) :: Arg a b -> Arg a b -> Bool Source #

max :: Arg a b -> Arg a b -> Arg a b Source #

min :: Arg a b -> Arg a b -> Arg a b Source #

Ord (TypeRep a) Source #

Since: base-4.4.0.0

Instance details

Defined in Data.Typeable.Internal

(Ix i, Ord e) => Ord (Array i e) Source #

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

compare :: Array i e -> Array i e -> Ordering Source #

(<) :: Array i e -> Array i e -> Bool Source #

(<=) :: Array i e -> Array i e -> Bool Source #

(>) :: Array i e -> Array i e -> Bool Source #

(>=) :: Array i e -> Array i e -> Bool Source #

max :: Array i e -> Array i e -> Array i e Source #

min :: Array i e -> Array i e -> Array i e Source #

Ord (U1 p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: U1 p -> U1 p -> Ordering Source #

(<) :: U1 p -> U1 p -> Bool Source #

(<=) :: U1 p -> U1 p -> Bool Source #

(>) :: U1 p -> U1 p -> Bool Source #

(>=) :: U1 p -> U1 p -> Bool Source #

max :: U1 p -> U1 p -> U1 p Source #

min :: U1 p -> U1 p -> U1 p Source #

Ord (V1 p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: V1 p -> V1 p -> Ordering Source #

(<) :: V1 p -> V1 p -> Bool Source #

(<=) :: V1 p -> V1 p -> Bool Source #

(>) :: V1 p -> V1 p -> Bool Source #

(>=) :: V1 p -> V1 p -> Bool Source #

max :: V1 p -> V1 p -> V1 p Source #

min :: V1 p -> V1 p -> V1 p Source #

(Ord a, Ord b) => Ord (a, b) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b) -> (a, b) -> Ordering Source #

(<) :: (a, b) -> (a, b) -> Bool Source #

(<=) :: (a, b) -> (a, b) -> Bool Source #

(>) :: (a, b) -> (a, b) -> Bool Source #

(>=) :: (a, b) -> (a, b) -> Bool Source #

max :: (a, b) -> (a, b) -> (a, b) Source #

min :: (a, b) -> (a, b) -> (a, b) Source #

Ord a => Ord (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

compare :: Const a b -> Const a b -> Ordering Source #

(<) :: Const a b -> Const a b -> Bool Source #

(<=) :: Const a b -> Const a b -> Bool Source #

(>) :: Const a b -> Const a b -> Bool Source #

(>=) :: Const a b -> Const a b -> Bool Source #

max :: Const a b -> Const a b -> Const a b Source #

min :: Const a b -> Const a b -> Const a b Source #

Ord (f a) => Ord (Ap f a) Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

compare :: Ap f a -> Ap f a -> Ordering Source #

(<) :: Ap f a -> Ap f a -> Bool Source #

(<=) :: Ap f a -> Ap f a -> Bool Source #

(>) :: Ap f a -> Ap f a -> Bool Source #

(>=) :: Ap f a -> Ap f a -> Bool Source #

max :: Ap f a -> Ap f a -> Ap f a Source #

min :: Ap f a -> Ap f a -> Ap f a Source #

Ord (f a) => Ord (Alt f a) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> Ordering Source #

(<) :: Alt f a -> Alt f a -> Bool Source #

(<=) :: Alt f a -> Alt f a -> Bool Source #

(>) :: Alt f a -> Alt f a -> Bool Source #

(>=) :: Alt f a -> Alt f a -> Bool Source #

max :: Alt f a -> Alt f a -> Alt f a Source #

min :: Alt f a -> Alt f a -> Alt f a Source #

Ord (Coercion a b) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Methods

compare :: Coercion a b -> Coercion a b -> Ordering Source #

(<) :: Coercion a b -> Coercion a b -> Bool Source #

(<=) :: Coercion a b -> Coercion a b -> Bool Source #

(>) :: Coercion a b -> Coercion a b -> Bool Source #

(>=) :: Coercion a b -> Coercion a b -> Bool Source #

max :: Coercion a b -> Coercion a b -> Coercion a b Source #

min :: Coercion a b -> Coercion a b -> Coercion a b Source #

Ord (a :~: b) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

compare :: (a :~: b) -> (a :~: b) -> Ordering Source #

(<) :: (a :~: b) -> (a :~: b) -> Bool Source #

(<=) :: (a :~: b) -> (a :~: b) -> Bool Source #

(>) :: (a :~: b) -> (a :~: b) -> Bool Source #

(>=) :: (a :~: b) -> (a :~: b) -> Bool Source #

max :: (a :~: b) -> (a :~: b) -> a :~: b Source #

min :: (a :~: b) -> (a :~: b) -> a :~: b Source #

(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Generics

Ord (f p) => Ord (Rec1 f p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: Rec1 f p -> Rec1 f p -> Ordering Source #

(<) :: Rec1 f p -> Rec1 f p -> Bool Source #

(<=) :: Rec1 f p -> Rec1 f p -> Bool Source #

(>) :: Rec1 f p -> Rec1 f p -> Bool Source #

(>=) :: Rec1 f p -> Rec1 f p -> Bool Source #

max :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

min :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

Ord (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

Ord (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Char p -> URec Char p -> Ordering Source #

(<) :: URec Char p -> URec Char p -> Bool Source #

(<=) :: URec Char p -> URec Char p -> Bool Source #

(>) :: URec Char p -> URec Char p -> Bool Source #

(>=) :: URec Char p -> URec Char p -> Bool Source #

max :: URec Char p -> URec Char p -> URec Char p Source #

min :: URec Char p -> URec Char p -> URec Char p Source #

Ord (URec Double p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Ord (URec Int p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Int p -> URec Int p -> Ordering Source #

(<) :: URec Int p -> URec Int p -> Bool Source #

(<=) :: URec Int p -> URec Int p -> Bool Source #

(>) :: URec Int p -> URec Int p -> Bool Source #

(>=) :: URec Int p -> URec Int p -> Bool Source #

max :: URec Int p -> URec Int p -> URec Int p Source #

min :: URec Int p -> URec Int p -> URec Int p Source #

Ord (URec Word p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering Source #

(<) :: URec Word p -> URec Word p -> Bool Source #

(<=) :: URec Word p -> URec Word p -> Bool Source #

(>) :: URec Word p -> URec Word p -> Bool Source #

(>=) :: URec Word p -> URec Word p -> Bool Source #

max :: URec Word p -> URec Word p -> URec Word p Source #

min :: URec Word p -> URec Word p -> URec Word p Source #

(Ord a, Ord b, Ord c) => Ord (a, b, c) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering Source #

(<) :: (a, b, c) -> (a, b, c) -> Bool Source #

(<=) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>=) :: (a, b, c) -> (a, b, c) -> Bool Source #

max :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

min :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

(Ord (f a), Ord (g a)) => Ord (Product f g a) Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Product

Methods

compare :: Product f g a -> Product f g a -> Ordering Source #

(<) :: Product f g a -> Product f g a -> Bool Source #

(<=) :: Product f g a -> Product f g a -> Bool Source #

(>) :: Product f g a -> Product f g a -> Bool Source #

(>=) :: Product f g a -> Product f g a -> Bool Source #

max :: Product f g a -> Product f g a -> Product f g a Source #

min :: Product f g a -> Product f g a -> Product f g a Source #

(Ord (f a), Ord (g a)) => Ord (Sum f g a) Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Sum

Methods

compare :: Sum f g a -> Sum f g a -> Ordering Source #

(<) :: Sum f g a -> Sum f g a -> Bool Source #

(<=) :: Sum f g a -> Sum f g a -> Bool Source #

(>) :: Sum f g a -> Sum f g a -> Bool Source #

(>=) :: Sum f g a -> Sum f g a -> Bool Source #

max :: Sum f g a -> Sum f g a -> Sum f g a Source #

min :: Sum f g a -> Sum f g a -> Sum f g a Source #

Ord (a :~~: b) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

compare :: (a :~~: b) -> (a :~~: b) -> Ordering Source #

(<) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(<=) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(>) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(>=) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

max :: (a :~~: b) -> (a :~~: b) -> a :~~: b Source #

min :: (a :~~: b) -> (a :~~: b) -> a :~~: b Source #

(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering Source #

(<) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(>) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering Source #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

Ord c => Ord (K1 i c p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: K1 i c p -> K1 i c p -> Ordering Source #

(<) :: K1 i c p -> K1 i c p -> Bool Source #

(<=) :: K1 i c p -> K1 i c p -> Bool Source #

(>) :: K1 i c p -> K1 i c p -> Bool Source #

(>=) :: K1 i c p -> K1 i c p -> Bool Source #

max :: K1 i c p -> K1 i c p -> K1 i c p Source #

min :: K1 i c p -> K1 i c p -> K1 i c p Source #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering Source #

(<) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(>) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

Ord (f (g a)) => Ord (Compose f g a) Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Compose

Methods

compare :: Compose f g a -> Compose f g a -> Ordering Source #

(<) :: Compose f g a -> Compose f g a -> Bool Source #

(<=) :: Compose f g a -> Compose f g a -> Bool Source #

(>) :: Compose f g a -> Compose f g a -> Bool Source #

(>=) :: Compose f g a -> Compose f g a -> Bool Source #

max :: Compose f g a -> Compose f g a -> Compose f g a Source #

min :: Compose f g a -> Compose f g a -> Compose f g a Source #

Ord (f (g p)) => Ord ((f :.: g) p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :.: g) p -> (f :.: g) p -> Ordering Source #

(<) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(<=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(>) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(>=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

Ord (f p) => Ord (M1 i c f p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering Source #

(<) :: M1 i c f p -> M1 i c f p -> Bool Source #

(<=) :: M1 i c f p -> M1 i c f p -> Bool Source #

(>) :: M1 i c f p -> M1 i c f p -> Bool Source #

(>=) :: M1 i c f p -> M1 i c f p -> Bool Source #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

min :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering Source #

(<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering Source #

(<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

data Ordering Source #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Data Ordering Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source #

toConstr :: Ordering -> Constr Source #

dataTypeOf :: Ordering -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) Source #

gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

Monoid Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Semigroup Ordering Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Bounded Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Generic Ordering Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))
Ix Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Read Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Eq Ordering 
Instance details

Defined in GHC.Classes

Ord Ordering 
Instance details

Defined in GHC.Classes

type Rep Ordering Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype Down a Source #

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: base-4.6.0.0

Constructors

Down 

Fields

Instances

Instances details
MonadFix Down Source #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Down a) -> Down a Source #

MonadZip Down Source #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Down a -> Down b -> Down (a, b) Source #

mzipWith :: (a -> b -> c) -> Down a -> Down b -> Down c Source #

munzip :: Down (a, b) -> (Down a, Down b) Source #

Foldable Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Down m -> m Source #

foldMap :: Monoid m => (a -> m) -> Down a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Down a -> m Source #

foldr :: (a -> b -> b) -> b -> Down a -> b Source #

foldr' :: (a -> b -> b) -> b -> Down a -> b Source #

foldl :: (b -> a -> b) -> b -> Down a -> b Source #

foldl' :: (b -> a -> b) -> b -> Down a -> b Source #

foldr1 :: (a -> a -> a) -> Down a -> a Source #

foldl1 :: (a -> a -> a) -> Down a -> a Source #

toList :: Down a -> [a] Source #

null :: Down a -> Bool Source #

length :: Down a -> Int Source #

elem :: Eq a => a -> Down a -> Bool Source #

maximum :: Ord a => Down a -> a Source #

minimum :: Ord a => Down a -> a Source #

sum :: Num a => Down a -> a Source #

product :: Num a => Down a -> a Source #

Foldable1 Down Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Down m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Down a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Down a -> m Source #

toNonEmpty :: Down a -> NonEmpty a Source #

maximum :: Ord a => Down a -> a Source #

minimum :: Ord a => Down a -> a Source #

head :: Down a -> a Source #

last :: Down a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Down a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Down a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Down a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Down a -> b Source #

Eq1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Down a -> Down b -> Bool Source #

Ord1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Down a -> Down b -> Ordering Source #

Read1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] Source #

Show1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Down a] -> ShowS Source #

Traversable Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Down a -> f (Down b) Source #

sequenceA :: Applicative f => Down (f a) -> f (Down a) Source #

mapM :: Monad m => (a -> m b) -> Down a -> m (Down b) Source #

sequence :: Monad m => Down (m a) -> m (Down a) Source #

Applicative Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

pure :: a -> Down a Source #

(<*>) :: Down (a -> b) -> Down a -> Down b Source #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c Source #

(*>) :: Down a -> Down b -> Down b Source #

(<*) :: Down a -> Down b -> Down a Source #

Functor Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

fmap :: (a -> b) -> Down a -> Down b Source #

(<$) :: a -> Down b -> Down a Source #

Monad Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(>>=) :: Down a -> (a -> Down b) -> Down b Source #

(>>) :: Down a -> Down b -> Down b Source #

return :: a -> Down a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Down a -> Rep1 Down a Source #

to1 :: Rep1 Down a -> Down a Source #

Data a => Data (Down a) Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Down a -> c (Down a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Down a) Source #

toConstr :: Down a -> Constr Source #

dataTypeOf :: Down a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Down a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Down a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Down a -> Down a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Down a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Down a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source #

Storable a => Storable (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int Source #

alignment :: Down a -> Int Source #

peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) Source #

pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Down a) Source #

pokeByteOff :: Ptr b -> Int -> Down a -> IO () Source #

peek :: Ptr (Down a) -> IO (Down a) Source #

poke :: Ptr (Down a) -> Down a -> IO () Source #

Monoid a => Monoid (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a Source #

mappend :: Down a -> Down a -> Down a Source #

mconcat :: [Down a] -> Down a Source #

Semigroup a => Semigroup (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(<>) :: Down a -> Down a -> Down a Source #

sconcat :: NonEmpty (Down a) -> Down a Source #

stimes :: Integral b => b -> Down a -> Down a Source #

Bits a => Bits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(.&.) :: Down a -> Down a -> Down a Source #

(.|.) :: Down a -> Down a -> Down a Source #

xor :: Down a -> Down a -> Down a Source #

complement :: Down a -> Down a Source #

shift :: Down a -> Int -> Down a Source #

rotate :: Down a -> Int -> Down a Source #

zeroBits :: Down a Source #

bit :: Int -> Down a Source #

setBit :: Down a -> Int -> Down a Source #

clearBit :: Down a -> Int -> Down a Source #

complementBit :: Down a -> Int -> Down a Source #

testBit :: Down a -> Int -> Bool Source #

bitSizeMaybe :: Down a -> Maybe Int Source #

bitSize :: Down a -> Int Source #

isSigned :: Down a -> Bool Source #

shiftL :: Down a -> Int -> Down a Source #

unsafeShiftL :: Down a -> Int -> Down a Source #

shiftR :: Down a -> Int -> Down a Source #

unsafeShiftR :: Down a -> Int -> Down a Source #

rotateL :: Down a -> Int -> Down a Source #

rotateR :: Down a -> Int -> Down a Source #

popCount :: Down a -> Int Source #

FiniteBits a => FiniteBits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Bounded a => Bounded (Down a) Source #

Swaps minBound and maxBound of the underlying type.

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

(Enum a, Bounded a, Eq a) => Enum (Down a) Source #

Swaps succ and pred of the underlying type.

Since: base-4.18.0.0

Instance details

Defined in Data.Ord

Methods

succ :: Down a -> Down a Source #

pred :: Down a -> Down a Source #

toEnum :: Int -> Down a Source #

fromEnum :: Down a -> Int Source #

enumFrom :: Down a -> [Down a] Source #

enumFromThen :: Down a -> Down a -> [Down a] Source #

enumFromTo :: Down a -> Down a -> [Down a] Source #

enumFromThenTo :: Down a -> Down a -> Down a -> [Down a] Source #

Floating a => Floating (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

pi :: Down a Source #

exp :: Down a -> Down a Source #

log :: Down a -> Down a Source #

sqrt :: Down a -> Down a Source #

(**) :: Down a -> Down a -> Down a Source #

logBase :: Down a -> Down a -> Down a Source #

sin :: Down a -> Down a Source #

cos :: Down a -> Down a Source #

tan :: Down a -> Down a Source #

asin :: Down a -> Down a Source #

acos :: Down a -> Down a Source #

atan :: Down a -> Down a Source #

sinh :: Down a -> Down a Source #

cosh :: Down a -> Down a Source #

tanh :: Down a -> Down a Source #

asinh :: Down a -> Down a Source #

acosh :: Down a -> Down a Source #

atanh :: Down a -> Down a Source #

log1p :: Down a -> Down a Source #

expm1 :: Down a -> Down a Source #

log1pexp :: Down a -> Down a Source #

log1mexp :: Down a -> Down a Source #

RealFloat a => RealFloat (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Generic (Down a) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep (Down a) = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Down a -> Rep (Down a) x Source #

to :: Rep (Down a) x -> Down a Source #

Ix a => Ix (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

range :: (Down a, Down a) -> [Down a] Source #

index :: (Down a, Down a) -> Down a -> Int Source #

unsafeIndex :: (Down a, Down a) -> Down a -> Int Source #

inRange :: (Down a, Down a) -> Down a -> Bool Source #

rangeSize :: (Down a, Down a) -> Int Source #

unsafeRangeSize :: (Down a, Down a) -> Int Source #

Num a => Num (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(+) :: Down a -> Down a -> Down a Source #

(-) :: Down a -> Down a -> Down a Source #

(*) :: Down a -> Down a -> Down a Source #

negate :: Down a -> Down a Source #

abs :: Down a -> Down a Source #

signum :: Down a -> Down a Source #

fromInteger :: Integer -> Down a Source #

Read a => Read (Down a) Source #

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Fractional a => Fractional (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(/) :: Down a -> Down a -> Down a Source #

recip :: Down a -> Down a Source #

fromRational :: Rational -> Down a Source #

Real a => Real (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

RealFrac a => RealFrac (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

properFraction :: Integral b => Down a -> (b, Down a) Source #

truncate :: Integral b => Down a -> b Source #

round :: Integral b => Down a -> b Source #

ceiling :: Integral b => Down a -> b Source #

floor :: Integral b => Down a -> b Source #

Show a => Show (Down a) Source #

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS Source #

show :: Down a -> String Source #

showList :: [Down a] -> ShowS Source #

Eq a => Eq (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

(==) :: Down a -> Down a -> Bool Source #

(/=) :: Down a -> Down a -> Bool Source #

Ord a => Ord (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

compare :: Down a -> Down a -> Ordering Source #

(<) :: Down a -> Down a -> Bool Source #

(<=) :: Down a -> Down a -> Bool Source #

(>) :: Down a -> Down a -> Bool Source #

(>=) :: Down a -> Down a -> Bool Source #

max :: Down a -> Down a -> Down a Source #

min :: Down a -> Down a -> Down a Source #

type Rep1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Down a) Source #

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep (Down a) = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

comparing :: Ord a => (b -> a) -> b -> b -> Ordering Source #

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) ...

clamp :: Ord a => (a, a) -> a -> a Source #

clamp (low, high) a = min high (max a low)

Function for ensuring 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'