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.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
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 TyCon | |
Ord BigNat | |
Ord GeneralCategory # | |
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 IOMode # | |
Ord SomeSymbol # | |
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 # | |
Ord Fingerprint # | |
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 ArithException # | |
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 ErrorCall # | |
Ord DecidedStrictness # | |
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 SourceStrictness # | |
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 # | |
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 Associativity # | |
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 Fixity # | |
Ord Any # | |
Ord All # | |
Ord SeekMode # | |
Ord CUIntMax # | |
Ord CIntMax # | |
Ord CUIntPtr # | |
Ord CIntPtr # | |
Ord CSUSeconds # | |
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 CUSeconds # | |
Ord CTime # | |
Ord CClock # | |
Ord CSigAtomic # | |
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 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 NewlineMode # | |
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 Newline # | |
Ord BufferMode # | |
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 ExitCode # | |
Ord ArrayException # | |
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 # | |
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 ThreadStatus # | |
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 BlockReason # | |
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 # | |
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 Unique # | |
Ord Version # | |
Ord Void # | |
Ord Natural # | |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) # | |
Integral a => Ord (Ratio a) # | |
Ord (Ptr a) # | |
Ord (FunPtr a) # | |
Ord (V1 p) # | |
Ord (U1 p) # | |
Ord p => Ord (Par1 p) # | |
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) # | |
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) # | |
Ord (Fixed a) # | |
Ord a => Ord (NonEmpty a) # | |
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 (Option a) # | |
Ord m => Ord (WrappedMonoid m) # | |
compare :: WrappedMonoid m -> WrappedMonoid m -> Ordering Source # (<) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (<=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (>) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (>=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # max :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # min :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # | |
Ord a => Ord (Last a) # | |
Ord a => Ord (First a) # | |
Ord a => Ord (Max a) # | |
Ord a => Ord (Min a) # | |
Ord a => Ord (Identity a) # | |
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 b) => Ord (Either a b) # | |
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 (f p) => Ord (Rec1 f p) # | |
Ord (URec Char p) # | |
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) # | |
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) # | |
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) # | |
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) # | |
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 (URec (Ptr ()) p) # | |
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 a, Ord b) => Ord (a, b) | |
Ord (Proxy k s) # | |
Ord a => Ord (Arg a b) # | |
Ord c => Ord (K1 i c p) # | |
(Ord (f p), Ord (g p)) => Ord ((:+:) f g p) # | |
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) # | |
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 (g p)) => Ord ((:.:) f g p) # | |
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 a, Ord b, Ord c) => Ord (a, b, c) | |
Ord ((:~:) k a b) # | |
compare :: (k :~: a) b -> (k :~: a) b -> Ordering Source # (<) :: (k :~: a) b -> (k :~: a) b -> Bool Source # (<=) :: (k :~: a) b -> (k :~: a) b -> Bool Source # (>) :: (k :~: a) b -> (k :~: a) b -> Bool Source # (>=) :: (k :~: a) b -> (k :~: a) b -> Bool Source # | |
Ord (Coercion k a b) # | |
compare :: Coercion k a b -> Coercion k a b -> Ordering Source # (<) :: Coercion k a b -> Coercion k a b -> Bool Source # (<=) :: Coercion k a b -> Coercion k a b -> Bool Source # (>) :: Coercion k a b -> Coercion k a b -> Bool Source # (>=) :: Coercion k a b -> Coercion k a b -> Bool Source # max :: Coercion k a b -> Coercion k a b -> Coercion k a b Source # min :: Coercion k a b -> Coercion k a b -> Coercion k a b Source # | |
Ord (f a) => Ord (Alt k f a) # | |
Ord a => Ord (Const k a b) # | |
compare :: Const k a b -> Const k a b -> Ordering Source # (<) :: Const k a b -> Const k a b -> Bool Source # (<=) :: Const k a b -> Const k a b -> Bool Source # (>) :: Const k a b -> Const k a b -> Bool Source # (>=) :: Const k a b -> Const k a b -> Bool Source # | |
Ord (f p) => Ord (M1 i c f p) # | |
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 (a, b, c, d) | |
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 # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a) # | |
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 # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a) # | |
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 # | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
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 # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) # | |
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 a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
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) | |
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) | |
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) | |
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) | |
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) | |
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) | |
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) | |
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) | |
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) | |
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 # |
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
Down a |