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
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.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
compare :: a -> a -> Ordering #
(<) :: a -> a -> Bool infix 4 #
(<=) :: a -> a -> Bool infix 4 #
(>) :: a -> a -> Bool infix 4 #
Instances
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 # | Since: base-2.1 |
Ord Int16 # | Since: base-2.1 |
Ord Int32 # | Since: base-2.1 |
Ord Int64 # | Since: base-2.1 |
Ord Integer | |
Ord Natural # | |
Ord Ordering | |
Defined in GHC.Classes | |
Ord Word | |
Ord Word8 # | Since: base-2.1 |
Ord Word16 # | Since: base-2.1 |
Ord Word32 # | Since: base-2.1 |
Ord Word64 # | Since: base-2.1 |
Ord SomeTypeRep # | |
Defined in Data.Typeable.Internal compare :: SomeTypeRep -> SomeTypeRep -> Ordering # (<) :: SomeTypeRep -> SomeTypeRep -> Bool # (<=) :: SomeTypeRep -> SomeTypeRep -> Bool # (>) :: SomeTypeRep -> SomeTypeRep -> Bool # (>=) :: SomeTypeRep -> SomeTypeRep -> Bool # max :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # min :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # | |
Ord () | |
Ord TyCon | |
Ord BigNat | |
Ord GeneralCategory # | |
Defined in GHC.Unicode compare :: GeneralCategory -> GeneralCategory -> Ordering # (<) :: GeneralCategory -> GeneralCategory -> Bool # (<=) :: GeneralCategory -> GeneralCategory -> Bool # (>) :: GeneralCategory -> GeneralCategory -> Bool # (>=) :: GeneralCategory -> GeneralCategory -> Bool # max :: GeneralCategory -> GeneralCategory -> GeneralCategory # min :: GeneralCategory -> GeneralCategory -> GeneralCategory # | |
Ord Fingerprint # | |
Defined in GHC.Fingerprint.Type compare :: Fingerprint -> Fingerprint -> Ordering # (<) :: Fingerprint -> Fingerprint -> Bool # (<=) :: Fingerprint -> Fingerprint -> Bool # (>) :: Fingerprint -> Fingerprint -> Bool # (>=) :: Fingerprint -> Fingerprint -> Bool # max :: Fingerprint -> Fingerprint -> Fingerprint # min :: Fingerprint -> Fingerprint -> Fingerprint # | |
Ord IOMode # | |
Ord IntPtr # | |
Ord WordPtr # | |
Ord CUIntMax # | |
Defined in Foreign.C.Types | |
Ord CIntMax # | |
Ord CUIntPtr # | |
Defined in Foreign.C.Types | |
Ord CIntPtr # | |
Ord CSUSeconds # | |
Defined in Foreign.C.Types compare :: CSUSeconds -> CSUSeconds -> Ordering # (<) :: CSUSeconds -> CSUSeconds -> Bool # (<=) :: CSUSeconds -> CSUSeconds -> Bool # (>) :: CSUSeconds -> CSUSeconds -> Bool # (>=) :: CSUSeconds -> CSUSeconds -> Bool # max :: CSUSeconds -> CSUSeconds -> CSUSeconds # min :: CSUSeconds -> CSUSeconds -> CSUSeconds # | |
Ord CUSeconds # | |
Defined in Foreign.C.Types | |
Ord CTime # | |
Ord CClock # | |
Ord CSigAtomic # | |
Defined in Foreign.C.Types compare :: CSigAtomic -> CSigAtomic -> Ordering # (<) :: CSigAtomic -> CSigAtomic -> Bool # (<=) :: CSigAtomic -> CSigAtomic -> Bool # (>) :: CSigAtomic -> CSigAtomic -> Bool # (>=) :: CSigAtomic -> CSigAtomic -> Bool # max :: CSigAtomic -> CSigAtomic -> CSigAtomic # min :: CSigAtomic -> CSigAtomic -> CSigAtomic # | |
Ord CWchar # | |
Ord CSize # | |
Ord CPtrdiff # | |
Defined in Foreign.C.Types | |
Ord CDouble # | |
Ord CFloat # | |
Ord CBool # | |
Ord CULLong # | |
Ord CLLong # | |
Ord CULong # | |
Ord CLong # | |
Ord CUInt # | |
Ord CInt # | |
Ord CUShort # | |
Ord CShort # | |
Ord CUChar # | |
Ord CSChar # | |
Ord CChar # | |
Ord SomeNat # | Since: base-4.7.0.0 |
Ord SomeSymbol # | Since: base-4.7.0.0 |
Defined in GHC.TypeLits compare :: SomeSymbol -> SomeSymbol -> Ordering # (<) :: SomeSymbol -> SomeSymbol -> Bool # (<=) :: SomeSymbol -> SomeSymbol -> Bool # (>) :: SomeSymbol -> SomeSymbol -> Bool # (>=) :: SomeSymbol -> SomeSymbol -> Bool # max :: SomeSymbol -> SomeSymbol -> SomeSymbol # min :: SomeSymbol -> SomeSymbol -> SomeSymbol # | |
Ord DecidedStrictness # | |
Defined in GHC.Generics compare :: DecidedStrictness -> DecidedStrictness -> Ordering # (<) :: DecidedStrictness -> DecidedStrictness -> Bool # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool # (>) :: DecidedStrictness -> DecidedStrictness -> Bool # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # | |
Ord SourceStrictness # | |
Defined in GHC.Generics compare :: SourceStrictness -> SourceStrictness -> Ordering # (<) :: SourceStrictness -> SourceStrictness -> Bool # (<=) :: SourceStrictness -> SourceStrictness -> Bool # (>) :: SourceStrictness -> SourceStrictness -> Bool # (>=) :: SourceStrictness -> SourceStrictness -> Bool # max :: SourceStrictness -> SourceStrictness -> SourceStrictness # min :: SourceStrictness -> SourceStrictness -> SourceStrictness # | |
Ord SourceUnpackedness # | |
Defined in GHC.Generics compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # | |
Ord Associativity # | |
Defined in GHC.Generics compare :: Associativity -> Associativity -> Ordering # (<) :: Associativity -> Associativity -> Bool # (<=) :: Associativity -> Associativity -> Bool # (>) :: Associativity -> Associativity -> Bool # (>=) :: Associativity -> Associativity -> Bool # max :: Associativity -> Associativity -> Associativity # min :: Associativity -> Associativity -> Associativity # | |
Ord Fixity # | |
Ord Any # | |
Ord All # | |
Ord ArithException # | |
Defined in GHC.Exception compare :: ArithException -> ArithException -> Ordering # (<) :: ArithException -> ArithException -> Bool # (<=) :: ArithException -> ArithException -> Bool # (>) :: ArithException -> ArithException -> Bool # (>=) :: ArithException -> ArithException -> Bool # max :: ArithException -> ArithException -> ArithException # min :: ArithException -> ArithException -> ArithException # | |
Ord ErrorCall # | |
Defined in GHC.Exception | |
Ord SeekMode # | |
Defined in GHC.IO.Device | |
Ord NewlineMode # | |
Defined in GHC.IO.Handle.Types compare :: NewlineMode -> NewlineMode -> Ordering # (<) :: NewlineMode -> NewlineMode -> Bool # (<=) :: NewlineMode -> NewlineMode -> Bool # (>) :: NewlineMode -> NewlineMode -> Bool # (>=) :: NewlineMode -> NewlineMode -> Bool # max :: NewlineMode -> NewlineMode -> NewlineMode # min :: NewlineMode -> NewlineMode -> NewlineMode # | |
Ord Newline # | |
Ord BufferMode # | |
Defined in GHC.IO.Handle.Types compare :: BufferMode -> BufferMode -> Ordering # (<) :: BufferMode -> BufferMode -> Bool # (<=) :: BufferMode -> BufferMode -> Bool # (>) :: BufferMode -> BufferMode -> Bool # (>=) :: BufferMode -> BufferMode -> Bool # max :: BufferMode -> BufferMode -> BufferMode # min :: BufferMode -> BufferMode -> BufferMode # | |
Ord ExitCode # | |
Defined in GHC.IO.Exception | |
Ord ArrayException # | |
Defined in GHC.IO.Exception compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # | |
Ord AsyncException # | |
Defined in GHC.IO.Exception compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException # | |
Ord Fd # | |
Ord CTimer # | |
Ord CKey # | |
Ord CId # | |
Ord CFsFilCnt # | |
Defined in System.Posix.Types | |
Ord CFsBlkCnt # | |
Defined in System.Posix.Types | |
Ord CClockId # | |
Defined in System.Posix.Types | |
Ord CBlkCnt # | |
Ord CBlkSize # | |
Defined in System.Posix.Types | |
Ord CRLim # | |
Ord CTcflag # | |
Ord CSpeed # | |
Ord CCc # | |
Ord CUid # | |
Ord CNlink # | |
Ord CGid # | |
Ord CSsize # | |
Ord CPid # | |
Ord COff # | |
Ord CMode # | |
Ord CIno # | |
Ord CDev # | |
Ord ThreadStatus # | |
Defined in GHC.Conc.Sync compare :: ThreadStatus -> ThreadStatus -> Ordering # (<) :: ThreadStatus -> ThreadStatus -> Bool # (<=) :: ThreadStatus -> ThreadStatus -> Bool # (>) :: ThreadStatus -> ThreadStatus -> Bool # (>=) :: ThreadStatus -> ThreadStatus -> Bool # max :: ThreadStatus -> ThreadStatus -> ThreadStatus # min :: ThreadStatus -> ThreadStatus -> ThreadStatus # | |
Ord BlockReason # | |
Defined in GHC.Conc.Sync compare :: BlockReason -> BlockReason -> Ordering # (<) :: BlockReason -> BlockReason -> Bool # (<=) :: BlockReason -> BlockReason -> Bool # (>) :: BlockReason -> BlockReason -> Bool # (>=) :: BlockReason -> BlockReason -> Bool # max :: BlockReason -> BlockReason -> BlockReason # min :: BlockReason -> BlockReason -> BlockReason # | |
Ord ThreadId # | Since: base-4.2.0.0 |
Defined in GHC.Conc.Sync | |
Ord Version # | Since: base-2.1 |
Ord ByteOrder # | |
Defined in GHC.ByteOrder | |
Ord Unique # | |
Ord Void # | Since: base-4.8.0.0 |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) # | |
Integral a => Ord (Ratio a) # | Since: base-2.0.1 |
Ord (Ptr a) # | |
Ord (FunPtr a) # | |
Ord p => Ord (Par1 p) # | |
Ord a => Ord (NonEmpty a) # | |
Ord a => Ord (Down a) # | Since: base-4.6.0.0 |
Ord a => Ord (Product a) # | |
Defined in Data.Semigroup.Internal | |
Ord a => Ord (Sum a) # | |
Ord a => Ord (Dual a) # | |
Ord a => Ord (Last a) # | |
Ord a => Ord (First a) # | |
Ord (ForeignPtr a) # | Since: base-2.1 |
Defined in GHC.ForeignPtr compare :: ForeignPtr a -> ForeignPtr a -> Ordering # (<) :: ForeignPtr a -> ForeignPtr a -> Bool # (<=) :: ForeignPtr a -> ForeignPtr a -> Bool # (>) :: ForeignPtr a -> ForeignPtr a -> Bool # (>=) :: ForeignPtr a -> ForeignPtr a -> Bool # max :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a # min :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a # | |
Ord a => Ord (Identity a) # | |
Ord a => Ord (ZipList a) # | |
Defined in Control.Applicative | |
Ord a => Ord (Option a) # | |
Defined in Data.Semigroup | |
Ord m => Ord (WrappedMonoid m) # | |
Defined in Data.Semigroup compare :: WrappedMonoid m -> WrappedMonoid m -> Ordering # (<) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (<=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # max :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # min :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # | |
Ord a => Ord (Last a) # | |
Ord a => Ord (First a) # | |
Ord a => Ord (Max a) # | |
Ord a => Ord (Min a) # | |
Ord (Fixed a) # | |
(Ord a, Ord b) => Ord (Either a b) # | |
Ord (V1 p) # | Since: base-4.9.0.0 |
Ord (U1 p) # | Since: base-4.9.0.0 |
Ord (TypeRep a) # | Since: base-4.4.0.0 |
Defined in Data.Typeable.Internal | |
(Ord a, Ord b) => Ord (a, b) | |
Ord (Proxy s) # | Since: base-4.7.0.0 |
Ord a => Ord (Arg a b) # | Since: base-4.9.0.0 |
Ord (f p) => Ord (Rec1 f p) # | |
Defined in GHC.Generics | |
Ord (URec Word p) # | |
Ord (URec Int p) # | |
Ord (URec Float p) # | |
Defined in GHC.Generics | |
Ord (URec Double p) # | |
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Ord (URec Char p) # | |
Ord (URec (Ptr ()) p) # | |
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Defined in GHC.Classes | |
Ord (a :~: b) # | |
Defined in Data.Type.Equality | |
Ord (Coercion a b) # | |
Defined in Data.Type.Coercion | |
Ord (f a) => Ord (Alt f a) # | |
Ord a => Ord (Const a b) # | |
Defined in Data.Functor.Const | |
Ord c => Ord (K1 i c p) # | |
Defined in GHC.Generics | |
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) # | |
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) # | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
Defined in GHC.Classes | |
Ord (a :~~: b) # | Since: base-4.10.0.0 |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product compare :: Product f g a -> Product f g a -> Ordering # (<) :: Product f g a -> Product f g a -> Bool # (<=) :: Product f g a -> Product f g a -> Bool # (>) :: Product f g a -> Product f g a -> Bool # (>=) :: Product f g a -> Product f g a -> Bool # | |
Ord (f p) => Ord (M1 i c f p) # | |
Ord (f (g p)) => Ord ((f :.: g) p) # | |
(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 # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose compare :: Compose f g a -> Compose f g a -> Ordering # (<) :: Compose f g a -> Compose f g a -> Bool # (<=) :: Compose f g a -> Compose f g a -> Bool # (>) :: Compose f g a -> Compose f g a -> Bool # (>=) :: Compose f g a -> Compose f g a -> Bool # | |
(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 # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # | |
(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 # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # | |
(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 # (<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # 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) # 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) # | |
(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 # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # 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) # 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) # | |
(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 # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # 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) # 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) # | |
(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 # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # 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) # 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) # | |
(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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # |
Instances
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).
If Down
aa
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
Since: base-4.6.0.0
Down a |
Instances
Monad Down Source # | Since: base-4.11.0.0 |
Functor Down Source # | Since: base-4.11.0.0 |
Applicative Down Source # | Since: base-4.11.0.0 |
Eq a => Eq (Down a) Source # | |
Num a => Num (Down a) Source # | Since: base-4.11.0.0 |
Ord a => Ord (Down a) Source # | Since: base-4.6.0.0 |
Read a => Read (Down a) Source # | Since: base-4.7.0.0 |
Show a => Show (Down a) Source # | Since: base-4.7.0.0 |
Semigroup a => Semigroup (Down a) Source # | Since: base-4.11.0.0 |
Monoid a => Monoid (Down a) Source # | Since: base-4.11.0.0 |