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 |
Data.Ord
Description
Orderings
Synopsis
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.
Methods
(<=) :: a -> a -> Bool infix 4
(>=) :: a -> a -> Bool infix 4
max :: a -> a -> a
min :: a -> a -> a
Instances
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | |
Ord Int16 | |
Ord Int32 | |
Ord Int64 | |
Ord Integer | |
Ord Ordering | |
Ord Word | |
Ord Word8 | |
Ord Word16 | |
Ord Word32 | |
Ord Word64 | |
Ord TypeRep | |
Ord () | |
Ord BigNat | |
Ord GeneralCategory | |
Methods 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 | |
Methods 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 TyCon | |
Ord Associativity | |
Methods 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 Arity | |
Ord Any | |
Ord All | |
Ord ArithException | |
Methods 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 | |
Ord CUIntMax | |
Ord CIntMax | |
Ord CUIntPtr | |
Ord CIntPtr | |
Ord CSUSeconds | |
Methods 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 | |
Ord CTime | |
Ord CClock | |
Ord CSigAtomic | |
Methods 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 | |
Ord CDouble | |
Ord CFloat | |
Ord CULLong | |
Ord CLLong | |
Ord CULong | |
Ord CLong | |
Ord CUInt | |
Ord CInt | |
Ord CUShort | |
Ord CShort | |
Ord CUChar | |
Ord CSChar | |
Ord CChar | |
Ord IntPtr | |
Ord WordPtr | |
Ord SeekMode | |
Ord NewlineMode | |
Methods 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 | |
Methods 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 | |
Ord ArrayException | |
Methods 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 | |
Methods 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 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 | |
Methods 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 | |
Methods 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 | |
Ord IOMode | |
Ord Version | |
Ord Natural | |
Ord SomeSymbol | |
Methods 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 SomeNat | |
Ord Unique | |
Ord Void | |
Ord a => Ord [a] | |
Integral a => Ord (Ratio a) | |
Ord (Ptr a) | |
Ord (FunPtr a) | |
Ord (U1 p) | |
Ord p => Ord (Par1 p) | |
Ord a => Ord (Maybe a) | |
Ord a => Ord (Down a) | |
Ord a => Ord (Last a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Product a) | |
Ord a => Ord (Sum a) | |
Ord a => Ord (Dual a) | |
Ord (ForeignPtr a) | |
Methods 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 (ZipList a) | |
Ord (Fixed a) | |
Ord a => Ord (Identity a) | |
(Ord a, Ord b) => Ord (Either a b) | |
Ord (f p) => Ord (Rec1 f p) | |
(Ord a, Ord b) => Ord (a, b) | |
Ord (Proxy k s) | |
Ord a => Ord (Const a b) | |
Ord c => Ord (K1 i c p) | |
(Ord (f p), Ord (g p)) => Ord ((:+:) f g p) | |
(Ord (f p), Ord (g p)) => Ord ((:*:) f g p) | |
Ord (f (g p)) => Ord ((:.:) f g p) | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Ord ((:~:) k a b) | |
Ord (Coercion k a b) | |
Methods compare :: Coercion k a b -> Coercion k a b -> Ordering (<) :: Coercion k a b -> Coercion k a b -> Bool (<=) :: Coercion k a b -> Coercion k a b -> Bool (>) :: Coercion k a b -> Coercion k a b -> Bool (>=) :: Coercion k a b -> Coercion k a b -> Bool | |
Ord (f a) => Ord (Alt k f a) | |
Ord (f p) => Ord (M1 i c f p) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
Methods compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering (<) :: (a, b, c, d) -> (a, b, c, d) -> Bool (<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool (>) :: (a, b, c, d) -> (a, b, c, d) -> Bool (>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
Methods 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) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
Methods 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) | |
Methods 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) | |
Methods 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) | |
Methods 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) | |
Methods 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) | |
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 (<) :: (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) | |
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 (<) :: (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) | |
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 (<) :: (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) | |
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 (<) :: (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) | |
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 (<) :: (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) |
data Ordering :: *
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
Provides Show
and Read
instances (since: 4.7.0.0).
Since: 4.6.0.0
Constructors
Down a |