| 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
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: 2.1 |
| Ord Int16 # | Since: 2.1 |
| Ord Int32 # | Since: 2.1 |
| Ord Int64 # | Since: 2.1 |
| Ord Integer | |
| Ord Natural # | |
| Ord Ordering | |
| Ord Word | |
| Ord Word8 # | Since: 2.1 |
| Ord Word16 # | Since: 2.1 |
| Ord Word32 # | Since: 2.1 |
| Ord Word64 # | Since: 2.1 |
| Ord SomeTypeRep # | |
Methods 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 # | |
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 IOMode # | |
| Ord IntPtr # | |
| Ord WordPtr # | |
| 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 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: 4.7.0.0 |
| Ord SomeSymbol # | Since: 4.7.0.0 |
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 DecidedStrictness # | |
Methods 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 # | |
Methods 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 # | |
Methods 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 # | |
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 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 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 CTimer # | |
| Ord CKey # | |
| Ord CId # | |
| Ord CFsFilCnt # | |
| Ord CFsBlkCnt # | |
| Ord CClockId # | |
| Ord CBlkCnt # | |
| Ord CBlkSize # | |
| 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 # | Since: 4.2.0.0 |
| Ord Version # | Since: 2.1 |
| Ord Unique # | |
| Ord Void # | Since: 4.8.0.0 |
| Ord a => Ord [a] | |
| Ord a => Ord (Maybe a) # | |
| Integral a => Ord (Ratio a) # | Since: 2.0.1 |
| Ord (Ptr a) # | |
| Ord (FunPtr a) # | |
| Ord p => Ord (Par1 p) # | |
| Ord a => Ord (Down a) # | Since: 4.6.0.0 |
| 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) # | Since: 2.1 |
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 (Identity a) # | |
| Ord a => Ord (ZipList a) # | |
| Ord a => Ord (NonEmpty a) # | |
| Ord a => Ord (Option a) # | |
| Ord m => Ord (WrappedMonoid m) # | |
Methods 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 b, Ord a) => Ord (Either a b) # | |
| Ord (V1 k p) # | |
| Ord (U1 k p) # | Since: 4.9.0.0 |
| Ord (TypeRep k a) # | Since: 4.4.0.0 |
| (Ord a, Ord b) => Ord (a, b) | |
| Ord (Proxy k s) # | Since: 4.7.0.0 |
| Ord a => Ord (Arg a b) # | Since: 4.9.0.0 |
| Ord (f p) => Ord (Rec1 k f p) # | |
| Ord (URec k Word p) # | |
Methods compare :: URec k Word p -> URec k Word p -> Ordering # (<) :: URec k Word p -> URec k Word p -> Bool # (<=) :: URec k Word p -> URec k Word p -> Bool # (>) :: URec k Word p -> URec k Word p -> Bool # (>=) :: URec k Word p -> URec k Word p -> Bool # | |
| Ord (URec k Int p) # | |
| Ord (URec k Float p) # | |
Methods compare :: URec k Float p -> URec k Float p -> Ordering # (<) :: URec k Float p -> URec k Float p -> Bool # (<=) :: URec k Float p -> URec k Float p -> Bool # (>) :: URec k Float p -> URec k Float p -> Bool # (>=) :: URec k Float p -> URec k Float p -> Bool # | |
| Ord (URec k Double p) # | |
Methods compare :: URec k Double p -> URec k Double p -> Ordering # (<) :: URec k Double p -> URec k Double p -> Bool # (<=) :: URec k Double p -> URec k Double p -> Bool # (>) :: URec k Double p -> URec k Double p -> Bool # (>=) :: URec k Double p -> URec k Double p -> Bool # max :: URec k Double p -> URec k Double p -> URec k Double p # min :: URec k Double p -> URec k Double p -> URec k Double p # | |
| Ord (URec k Char p) # | |
Methods compare :: URec k Char p -> URec k Char p -> Ordering # (<) :: URec k Char p -> URec k Char p -> Bool # (<=) :: URec k Char p -> URec k Char p -> Bool # (>) :: URec k Char p -> URec k Char p -> Bool # (>=) :: URec k Char p -> URec k Char p -> Bool # | |
| Ord (URec k (Ptr ()) p) # | |
Methods compare :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Ordering # (<) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool # (<=) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool # (>) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool # (>=) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool # max :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> URec k (Ptr ()) p # min :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> URec k (Ptr ()) 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 a => Ord (Const k a b) # | |
| Ord c => Ord (K1 k i c p) # | |
| (Ord (g p), Ord (f p)) => Ord ((:+:) k f g p) # | |
Methods compare :: (k :+: f) g p -> (k :+: f) g p -> Ordering # (<) :: (k :+: f) g p -> (k :+: f) g p -> Bool # (<=) :: (k :+: f) g p -> (k :+: f) g p -> Bool # (>) :: (k :+: f) g p -> (k :+: f) g p -> Bool # (>=) :: (k :+: f) g p -> (k :+: f) g p -> Bool # | |
| (Ord (g p), Ord (f p)) => Ord ((:*:) k f g p) # | |
Methods compare :: (k :*: f) g p -> (k :*: f) g p -> Ordering # (<) :: (k :*: f) g p -> (k :*: f) g p -> Bool # (<=) :: (k :*: f) g p -> (k :*: f) g p -> Bool # (>) :: (k :*: f) g p -> (k :*: f) g p -> Bool # (>=) :: (k :*: f) g p -> (k :*: f) g p -> Bool # | |
| (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
| Ord ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
Methods compare :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Ordering # (<) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool # (<=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool # (>) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool # (>=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool # max :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b # min :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b # | |
| (Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a) # | Since: 4.9.0.0 |
| (Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a) # | Since: 4.9.0.0 |
Methods 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 # max :: Product * f g a -> Product * f g a -> Product * f g a # min :: Product * f g a -> Product * f g a -> Product * f g a # | |
| Ord (f p) => Ord (M1 k i c f p) # | |
| Ord (f (g p)) => Ord ((:.:) k2 k1 f g p) # | |
Methods compare :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Ordering # (<) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool # (<=) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool # (>) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool # (>=) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool # max :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> (k2 :.: k1) f g p # min :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> (k2 :.: k1) f g p # | |
| (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) # | |
| (Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) # | Since: 4.9.0.0 |
Methods 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 # max :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a # min :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a # | |
| (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) # | |
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: Ordthen sortWith by Down x
Provides Show and Read instances (since: 4.7.0.0).
Since: 4.6.0.0
Constructors
| Down a |