Copyright | (c) The University of Glasgow 2005 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Orderings
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
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
The following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
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.
compare :: a -> a -> Ordering Source #
(<) :: a -> a -> Bool infix 4 Source #
(<=) :: a -> a -> Bool infix 4 Source #
(>) :: a -> a -> Bool infix 4 Source #
Instances
Ord BigNat | |
Defined in GHC.Num.BigNat | |
Ord Void Source # | @since base-4.8.0.0 |
Ord ByteOrder Source # | @since base-4.11.0.0 |
Defined in GHC.Internal.ByteOrder | |
Ord ClosureType Source # | |
Defined in GHC.Internal.ClosureTypes compare :: ClosureType -> ClosureType -> Ordering Source # (<) :: ClosureType -> ClosureType -> Bool Source # (<=) :: ClosureType -> ClosureType -> Bool Source # (>) :: ClosureType -> ClosureType -> Bool Source # (>=) :: ClosureType -> ClosureType -> Bool Source # max :: ClosureType -> ClosureType -> ClosureType Source # min :: ClosureType -> ClosureType -> ClosureType Source # | |
Ord BlockReason Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync compare :: BlockReason -> BlockReason -> Ordering Source # (<) :: BlockReason -> BlockReason -> Bool Source # (<=) :: BlockReason -> BlockReason -> Bool Source # (>) :: BlockReason -> BlockReason -> Bool Source # (>=) :: BlockReason -> BlockReason -> Bool Source # max :: BlockReason -> BlockReason -> BlockReason Source # min :: BlockReason -> BlockReason -> BlockReason Source # | |
Ord ThreadId Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.Conc.Sync | |
Ord ThreadStatus Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync compare :: ThreadStatus -> ThreadStatus -> Ordering Source # (<) :: ThreadStatus -> ThreadStatus -> Bool Source # (<=) :: ThreadStatus -> ThreadStatus -> Bool Source # (>) :: ThreadStatus -> ThreadStatus -> Bool Source # (>=) :: ThreadStatus -> ThreadStatus -> Bool Source # max :: ThreadStatus -> ThreadStatus -> ThreadStatus Source # min :: ThreadStatus -> ThreadStatus -> ThreadStatus Source # | |
Ord All Source # | @since base-2.01 |
Ord Any Source # | @since base-2.01 |
Ord SomeTypeRep Source # | |
Defined in GHC.Internal.Data.Typeable.Internal compare :: SomeTypeRep -> SomeTypeRep -> Ordering Source # (<) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (<=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (>) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (>=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # max :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep Source # min :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep Source # | |
Ord Unique Source # | |
Defined in GHC.Internal.Data.Unique | |
Ord Version Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Version | |
Ord TimeoutKey Source # | |
Defined in GHC.Internal.Event.TimeOut compare :: TimeoutKey -> TimeoutKey -> Ordering Source # (<) :: TimeoutKey -> TimeoutKey -> Bool Source # (<=) :: TimeoutKey -> TimeoutKey -> Bool Source # (>) :: TimeoutKey -> TimeoutKey -> Bool Source # (>=) :: TimeoutKey -> TimeoutKey -> Bool Source # max :: TimeoutKey -> TimeoutKey -> TimeoutKey Source # min :: TimeoutKey -> TimeoutKey -> TimeoutKey Source # | |
Ord ErrorCall Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Exception | |
Ord ArithException Source # | @since base-3.0 |
Defined in GHC.Internal.Exception.Type compare :: ArithException -> ArithException -> Ordering Source # (<) :: ArithException -> ArithException -> Bool Source # (<=) :: ArithException -> ArithException -> Bool Source # (>) :: ArithException -> ArithException -> Bool Source # (>=) :: ArithException -> ArithException -> Bool Source # max :: ArithException -> ArithException -> ArithException Source # min :: ArithException -> ArithException -> ArithException Source # | |
Ord Fingerprint Source # | @since base-4.4.0.0 |
Defined in GHC.Internal.Fingerprint.Type compare :: Fingerprint -> Fingerprint -> Ordering Source # (<) :: Fingerprint -> Fingerprint -> Bool Source # (<=) :: Fingerprint -> Fingerprint -> Bool Source # (>) :: Fingerprint -> Fingerprint -> Bool Source # (>=) :: Fingerprint -> Fingerprint -> Bool Source # max :: Fingerprint -> Fingerprint -> Fingerprint Source # min :: Fingerprint -> Fingerprint -> Fingerprint Source # | |
Ord CBool Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CClock Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CDouble Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CFloat Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CInt Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CIntMax Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CIntPtr Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CLLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CPtrdiff Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types compare :: CSUSeconds -> CSUSeconds -> Ordering Source # (<) :: CSUSeconds -> CSUSeconds -> Bool Source # (<=) :: CSUSeconds -> CSUSeconds -> Bool Source # (>) :: CSUSeconds -> CSUSeconds -> Bool Source # (>=) :: CSUSeconds -> CSUSeconds -> Bool Source # max :: CSUSeconds -> CSUSeconds -> CSUSeconds Source # min :: CSUSeconds -> CSUSeconds -> CSUSeconds Source # | |
Ord CShort Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSigAtomic Source # | |
Defined in GHC.Internal.Foreign.C.Types compare :: CSigAtomic -> CSigAtomic -> Ordering Source # (<) :: CSigAtomic -> CSigAtomic -> Bool Source # (<=) :: CSigAtomic -> CSigAtomic -> Bool Source # (>) :: CSigAtomic -> CSigAtomic -> Bool Source # (>=) :: CSigAtomic -> CSigAtomic -> Bool Source # max :: CSigAtomic -> CSigAtomic -> CSigAtomic Source # min :: CSigAtomic -> CSigAtomic -> CSigAtomic Source # | |
Ord CSize Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CTime Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUInt Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUIntMax Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUIntPtr Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CULLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CULong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUShort Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CWchar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord IntPtr Source # | |
Defined in GHC.Internal.Foreign.Ptr | |
Ord WordPtr Source # | |
Defined in GHC.Internal.Foreign.Ptr | |
Ord Associativity Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Generics compare :: Associativity -> Associativity -> Ordering Source # (<) :: Associativity -> Associativity -> Bool Source # (<=) :: Associativity -> Associativity -> Bool Source # (>) :: Associativity -> Associativity -> Bool Source # (>=) :: Associativity -> Associativity -> Bool Source # max :: Associativity -> Associativity -> Associativity Source # min :: Associativity -> Associativity -> Associativity Source # | |
Ord DecidedStrictness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: DecidedStrictness -> DecidedStrictness -> Ordering Source # (<) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # | |
Ord Fixity Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Generics | |
Ord SourceStrictness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: SourceStrictness -> SourceStrictness -> Ordering Source # (<) :: SourceStrictness -> SourceStrictness -> Bool Source # (<=) :: SourceStrictness -> SourceStrictness -> Bool Source # (>) :: SourceStrictness -> SourceStrictness -> Bool Source # (>=) :: SourceStrictness -> SourceStrictness -> Bool Source # max :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # min :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # | |
Ord SourceUnpackedness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering Source # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # | |
Ord SeekMode Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Device | |
Ord ArrayException Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception compare :: ArrayException -> ArrayException -> Ordering Source # (<) :: ArrayException -> ArrayException -> Bool Source # (<=) :: ArrayException -> ArrayException -> Bool Source # (>) :: ArrayException -> ArrayException -> Bool Source # (>=) :: ArrayException -> ArrayException -> Bool Source # max :: ArrayException -> ArrayException -> ArrayException Source # min :: ArrayException -> ArrayException -> ArrayException Source # | |
Ord AsyncException Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception compare :: AsyncException -> AsyncException -> Ordering Source # (<) :: AsyncException -> AsyncException -> Bool Source # (<=) :: AsyncException -> AsyncException -> Bool Source # (>) :: AsyncException -> AsyncException -> Bool Source # (>=) :: AsyncException -> AsyncException -> Bool Source # max :: AsyncException -> AsyncException -> AsyncException Source # min :: AsyncException -> AsyncException -> AsyncException Source # | |
Ord ExitCode Source # | |
Defined in GHC.Internal.IO.Exception | |
Ord BufferMode Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: BufferMode -> BufferMode -> Ordering Source # (<) :: BufferMode -> BufferMode -> Bool Source # (<=) :: BufferMode -> BufferMode -> Bool Source # (>) :: BufferMode -> BufferMode -> Bool Source # (>=) :: BufferMode -> BufferMode -> Bool Source # max :: BufferMode -> BufferMode -> BufferMode Source # min :: BufferMode -> BufferMode -> BufferMode Source # | |
Ord Newline Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Ord NewlineMode Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: NewlineMode -> NewlineMode -> Ordering Source # (<) :: NewlineMode -> NewlineMode -> Bool Source # (<=) :: NewlineMode -> NewlineMode -> Bool Source # (>) :: NewlineMode -> NewlineMode -> Bool Source # (>=) :: NewlineMode -> NewlineMode -> Bool Source # max :: NewlineMode -> NewlineMode -> NewlineMode Source # min :: NewlineMode -> NewlineMode -> NewlineMode Source # | |
Ord IOMode Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.IOMode | |
Ord Int16 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int32 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int64 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int8 Source # | @since base-2.01 |
Ord CBlkCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CBlkSize Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CCc Source # | |
Ord CClockId Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CDev Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CFsBlkCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CFsFilCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CGid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CId Source # | |
Ord CIno Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CKey Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CMode Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CNfds Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CNlink Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord COff Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CPid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CRLim Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSocklen Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSpeed Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSsize Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CTcflag Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CTimer Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CUid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord Fd Source # | |
Ord SomeChar Source # | |
Defined in GHC.Internal.TypeLits | |
Ord SomeSymbol Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.TypeLits compare :: SomeSymbol -> SomeSymbol -> Ordering Source # (<) :: SomeSymbol -> SomeSymbol -> Bool Source # (<=) :: SomeSymbol -> SomeSymbol -> Bool Source # (>) :: SomeSymbol -> SomeSymbol -> Bool Source # (>=) :: SomeSymbol -> SomeSymbol -> Bool Source # max :: SomeSymbol -> SomeSymbol -> SomeSymbol Source # min :: SomeSymbol -> SomeSymbol -> SomeSymbol Source # | |
Ord SomeNat Source # | @since base-4.7.0.0 |
Ord GeneralCategory Source # | @since base-2.01 |
Defined in GHC.Internal.Unicode compare :: GeneralCategory -> GeneralCategory -> Ordering Source # (<) :: GeneralCategory -> GeneralCategory -> Bool Source # (<=) :: GeneralCategory -> GeneralCategory -> Bool Source # (>) :: GeneralCategory -> GeneralCategory -> Bool Source # (>=) :: GeneralCategory -> GeneralCategory -> Bool Source # max :: GeneralCategory -> GeneralCategory -> GeneralCategory Source # min :: GeneralCategory -> GeneralCategory -> GeneralCategory Source # | |
Ord Word16 Source # | @since base-2.01 |
Defined in GHC.Internal.Word | |
Ord Word32 Source # | @since base-2.01 |
Defined in GHC.Internal.Word | |
Ord Word64 Source # | @since base-2.01 |
Defined in GHC.Internal.Word | |
Ord Word8 Source # | @since base-2.01 |
Defined in GHC.Internal.Word | |
Ord Ordering | |
Defined in GHC.Classes | |
Ord TyCon | |
Defined in GHC.Classes | |
Ord Integer | |
Ord Natural | |
Ord () | |
Ord Bool | |
Ord Char | |
Ord Double | IEEE 754 IEEE 754-2008, section 5.11 requires that if at least one of arguments of
IEEE 754-2008, section 5.10 defines Thus, users must be extremely cautious when using Moving further, the behaviour of IEEE 754-2008 compliant |
Defined in GHC.Classes | |
Ord Float | See |
Defined in GHC.Classes | |
Ord Int | |
Ord Word | |
Ord a => Ord (NonEmpty a) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Base compare :: NonEmpty a -> NonEmpty a -> Ordering Source # (<) :: NonEmpty a -> NonEmpty a -> Bool Source # (<=) :: NonEmpty a -> NonEmpty a -> Bool Source # (>) :: NonEmpty a -> NonEmpty a -> Bool Source # (>=) :: NonEmpty a -> NonEmpty a -> Bool Source # | |
Ord a => Ord (Identity a) Source # | @since base-4.8.0.0 |
Defined in GHC.Internal.Data.Functor.Identity compare :: Identity a -> Identity a -> Ordering Source # (<) :: Identity a -> Identity a -> Bool Source # (<=) :: Identity a -> Identity a -> Bool Source # (>) :: Identity a -> Identity a -> Bool Source # (>=) :: Identity a -> Identity a -> Bool Source # | |
Ord a => Ord (First a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Monoid | |
Ord a => Ord (Last a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Monoid | |
Ord a => Ord (Down a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Data.Ord | |
Ord a => Ord (Dual a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Product a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Sum a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord (ConstPtr a) Source # | |
Defined in GHC.Internal.Foreign.C.ConstPtr compare :: ConstPtr a -> ConstPtr a -> Ordering Source # (<) :: ConstPtr a -> ConstPtr a -> Bool Source # (<=) :: ConstPtr a -> ConstPtr a -> Bool Source # (>) :: ConstPtr a -> ConstPtr a -> Bool Source # (>=) :: ConstPtr a -> ConstPtr a -> Bool Source # | |
Ord (ForeignPtr a) Source # | @since base-2.01 |
Defined in GHC.Internal.ForeignPtr compare :: ForeignPtr a -> ForeignPtr a -> Ordering Source # (<) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (<=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # max :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # min :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # | |
Ord a => Ord (ZipList a) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Functor.ZipList | |
Ord p => Ord (Par1 p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
Ord (FunPtr a) Source # | |
Defined in GHC.Internal.Ptr | |
Ord (Ptr a) Source # | @since base-2.01 |
Defined in GHC.Internal.Ptr | |
Integral a => Ord (Ratio a) Source # | @since base-2.0.1 |
Ord (SChar c) Source # | @since base-4.19.0.0 |
Ord (SSymbol s) Source # | @since base-4.19.0.0 |
Defined in GHC.Internal.TypeLits | |
Ord (SNat n) Source # | @since base-4.19.0.0 |
Defined in GHC.Internal.TypeNats | |
Ord a => Ord (Maybe a) Source # | @since base-2.01 |
Ord a => Ord (Solo a) | |
Defined in GHC.Classes | |
Ord a => Ord [a] | |
(Ix i, Ord e) => Ord (Array i e) Source # | @since base-2.01 |
Defined in GHC.Internal.Arr | |
(Ord a, Ord b) => Ord (Either a b) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Either 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 # | |
Ord (Proxy s) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Proxy | |
Ord (TypeRep a) Source # | @since base-4.4.0.0 |
Defined in GHC.Internal.Data.Typeable.Internal | |
Ord (U1 p) Source # | @since base-4.7.0.0 |
Ord (V1 p) Source # | @since base-4.9.0.0 |
(Ord a, Ord b) => Ord (a, b) | |
Defined in GHC.Classes | |
Ord a => Ord (Const a b) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Data.Functor.Const | |
Ord (f a) => Ord (Ap f a) Source # | @since base-4.12.0.0 |
Defined in GHC.Internal.Data.Monoid | |
Ord (f a) => Ord (Alt f a) Source # | @since base-4.8.0.0 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord (Coercion a b) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Coercion 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 |
Defined in GHC.Internal.Data.Type.Equality | |
(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) Source # | @since base-4.18.0.0 |
Defined in GHC.Internal.Generics compare :: Generically1 f a -> Generically1 f a -> Ordering Source # (<) :: Generically1 f a -> Generically1 f a -> Bool Source # (<=) :: Generically1 f a -> Generically1 f a -> Bool Source # (>) :: Generically1 f a -> Generically1 f a -> Bool Source # (>=) :: Generically1 f a -> Generically1 f a -> Bool Source # max :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # min :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # | |
Ord (f p) => Ord (Rec1 f p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
Ord (URec (Ptr ()) p) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics 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 |
Defined in GHC.Internal.Generics 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 # | |
Ord (URec Double p) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |
Ord (URec Float p) Source # | |
Defined in GHC.Internal.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |
Ord (URec Int p) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics 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 # | |
Ord (URec Word p) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics 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 # | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Defined in GHC.Classes | |
Ord (a :~~: b) Source # | @since base-4.10.0.0 |
Defined in GHC.Internal.Data.Type.Equality 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 # | |
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics 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 # | |
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics 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 # | |
Ord c => Ord (K1 i c p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
Defined in GHC.Classes 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 p)) => Ord ((f :.: g) p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics 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 # | |
Ord (f p) => Ord (M1 i c f p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics 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 # | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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) | |
Defined in GHC.Classes 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 # |
Instances
Monoid Ordering Source # | @since base-2.01 |
Semigroup Ordering Source # | @since base-4.9.0.0 |
Data Ordering Source # | @since base-4.0.0.0 |
Defined in GHC.Internal.Data.Data 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 # | |
Bounded Ordering Source # | @since base-2.01 |
Enum Ordering Source # | @since base-2.01 |
Defined in GHC.Internal.Enum succ :: Ordering -> Ordering Source # pred :: Ordering -> Ordering Source # toEnum :: Int -> Ordering Source # fromEnum :: Ordering -> Int Source # enumFrom :: Ordering -> [Ordering] Source # enumFromThen :: Ordering -> Ordering -> [Ordering] Source # enumFromTo :: Ordering -> Ordering -> [Ordering] Source # enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source # | |
Generic Ordering Source # | |
Defined in GHC.Internal.Generics | |
Ix Ordering Source # | @since base-2.01 |
Defined in GHC.Internal.Ix | |
Read Ordering Source # | @since base-2.01 |
Show Ordering Source # | @since base-2.01 |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
type Rep Ordering Source # | @since base-4.6.0.0 |
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).Down
a
If a
has an
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: Ord
then sortWith by
.Down
x
>>>
compare True False
GT
>>>
compare (Down True) (Down False)
LT
If a
has a
instance then the wrapped instance also respects
the reversed ordering by exchanging the values of Bounded
and
minBound
.maxBound
>>>
minBound :: Int
-9223372036854775808
>>>
minBound :: Down Int
Down 9223372036854775807
All other instances of
behave as they do for Down
aa
.
@since base-4.6.0.0
Instances
Applicative Down Source # | @since base-4.11.0.0 | ||||
Functor Down Source # | @since base-4.11.0.0 | ||||
Monad Down Source # | @since base-4.11.0.0 | ||||
MonadFix Down Source # | @since base-4.12.0.0 | ||||
Foldable Down Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 # | |||||
Traversable Down Source # | @since base-4.12.0.0 | ||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monoid a => Monoid (Down a) Source # | @since base-4.11.0.0 | ||||
Semigroup a => Semigroup (Down a) Source # | @since base-4.11.0.0 | ||||
Bits a => Bits (Down a) Source # | @since base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord (.&.) :: 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 # 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 # | |||||
FiniteBits a => FiniteBits (Down a) Source # | @since base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord finiteBitSize :: Down a -> Int Source # countLeadingZeros :: Down a -> Int Source # countTrailingZeros :: Down a -> Int Source # | |||||
Data a => Data (Down a) Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded a => Bounded (Down a) Source # | Swaps @since base-4.14.0.0 | ||||
(Enum a, Bounded a, Eq a) => Enum (Down a) Source # | Swaps @since base-4.18.0.0 | ||||
Defined in GHC.Internal.Data.Ord 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 | ||||
Defined in GHC.Internal.Data.Ord 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 # | |||||
RealFloat a => RealFloat (Down a) Source # | @since base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord floatRadix :: Down a -> Integer Source # floatDigits :: Down a -> Int Source # floatRange :: Down a -> (Int, Int) Source # decodeFloat :: Down a -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Down a Source # exponent :: Down a -> Int Source # significand :: Down a -> Down a Source # scaleFloat :: Int -> Down a -> Down a Source # isNaN :: Down a -> Bool Source # isInfinite :: Down a -> Bool Source # isDenormalized :: Down a -> Bool Source # isNegativeZero :: Down a -> Bool Source # | |||||
Storable a => Storable (Down a) Source # | @since base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord 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 # | |||||
Generic (Down a) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Ix a => Ix (Down a) Source # | @since base-4.14.0.0 | ||||
Num a => Num (Down a) Source # | @since base-4.11.0.0 | ||||
Defined in GHC.Internal.Data.Ord | |||||
Read a => Read (Down a) Source # | This instance would be equivalent to the derived instances of the
@since base-4.7.0.0 | ||||
Fractional a => Fractional (Down a) Source # | @since base-4.14.0.0 | ||||
Real a => Real (Down a) Source # | @since base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord toRational :: Down a -> Rational Source # | |||||
RealFrac a => RealFrac (Down a) Source # | @since base-4.14.0.0 | ||||
Show a => Show (Down a) Source # | This instance would be equivalent to the derived instances of the
@since base-4.7.0.0 | ||||
Eq a => Eq (Down a) Source # | @since base-4.6.0.0 | ||||
Ord a => Ord (Down a) Source # | @since base-4.6.0.0 | ||||
Defined in GHC.Internal.Data.Ord | |||||
type Rep1 Down Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (Down a) Source # | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics |
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'
@since base-4.16.0.0