base-4.9.0.0: Basic libraries

Copyright(c) The University of Glasgow 2005
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Ord

Description

Orderings

Synopsis

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.

Minimal complete definition

compare | (<=)

Instances

Ord Bool 
Ord Char 
Ord Double 
Ord Float 
Ord Int 

Methods

compare :: Int -> Int -> Ordering Source

(<) :: Int -> Int -> Bool Source

(<=) :: Int -> Int -> Bool Source

(>) :: Int -> Int -> Bool Source

(>=) :: Int -> Int -> Bool Source

max :: Int -> Int -> Int Source

min :: Int -> Int -> Int Source

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 () 

Methods

compare :: () -> () -> Ordering Source

(<) :: () -> () -> Bool Source

(<=) :: () -> () -> Bool Source

(>) :: () -> () -> Bool Source

(>=) :: () -> () -> Bool Source

max :: () -> () -> () Source

min :: () -> () -> () Source

Ord TyCon 
Ord BigNat 
Ord GeneralCategory 
Ord SomeSymbol 
Ord SomeNat 
Ord DecidedStrictness 
Ord SourceStrictness 
Ord SourceUnpackedness 
Ord Associativity 
Ord Fixity 
Ord Any 

Methods

compare :: Any -> Any -> Ordering Source

(<) :: Any -> Any -> Bool Source

(<=) :: Any -> Any -> Bool Source

(>) :: Any -> Any -> Bool Source

(>=) :: Any -> Any -> Bool Source

max :: Any -> Any -> Any Source

min :: Any -> Any -> Any Source

Ord All 

Methods

compare :: All -> All -> Ordering Source

(<) :: All -> All -> Bool Source

(<=) :: All -> All -> Bool Source

(>) :: All -> All -> Bool Source

(>=) :: All -> All -> Bool Source

max :: All -> All -> All Source

min :: All -> All -> All Source

Ord IOMode 
Ord Fingerprint 
Ord ArithException 
Ord ErrorCall 
Ord CUIntMax 
Ord CIntMax 
Ord CUIntPtr 
Ord CIntPtr 
Ord CSUSeconds 
Ord CUSeconds 
Ord CTime 
Ord CClock 
Ord 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 
Ord Newline 
Ord BufferMode 
Ord ExitCode 
Ord ArrayException 
Ord AsyncException 
Ord Fd 

Methods

compare :: Fd -> Fd -> Ordering Source

(<) :: Fd -> Fd -> Bool Source

(<=) :: Fd -> Fd -> Bool Source

(>) :: Fd -> Fd -> Bool Source

(>=) :: Fd -> Fd -> Bool Source

max :: Fd -> Fd -> Fd Source

min :: Fd -> Fd -> Fd Source

Ord CRLim 
Ord CTcflag 
Ord CSpeed 
Ord CCc 

Methods

compare :: CCc -> CCc -> Ordering Source

(<) :: CCc -> CCc -> Bool Source

(<=) :: CCc -> CCc -> Bool Source

(>) :: CCc -> CCc -> Bool Source

(>=) :: CCc -> CCc -> Bool Source

max :: CCc -> CCc -> CCc Source

min :: CCc -> CCc -> CCc Source

Ord CUid 
Ord CNlink 
Ord CGid 
Ord CSsize 
Ord CPid 
Ord COff 
Ord CMode 
Ord CIno 
Ord CDev 
Ord ThreadStatus 
Ord BlockReason 
Ord ThreadId 
Ord Version 
Ord Natural 
Ord Void 
Ord Unique 
Ord a => Ord [a] 

Methods

compare :: [a] -> [a] -> Ordering Source

(<) :: [a] -> [a] -> Bool Source

(<=) :: [a] -> [a] -> Bool Source

(>) :: [a] -> [a] -> Bool Source

(>=) :: [a] -> [a] -> Bool Source

max :: [a] -> [a] -> [a] Source

min :: [a] -> [a] -> [a] Source

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering Source

(<) :: Maybe a -> Maybe a -> Bool Source

(<=) :: Maybe a -> Maybe a -> Bool Source

(>) :: Maybe a -> Maybe a -> Bool Source

(>=) :: Maybe a -> Maybe a -> Bool Source

max :: Maybe a -> Maybe a -> Maybe a Source

min :: Maybe a -> Maybe a -> Maybe a Source

Integral a => Ord (Ratio a) 

Methods

compare :: Ratio a -> Ratio a -> Ordering Source

(<) :: Ratio a -> Ratio a -> Bool Source

(<=) :: Ratio a -> Ratio a -> Bool Source

(>) :: Ratio a -> Ratio a -> Bool Source

(>=) :: Ratio a -> Ratio a -> Bool Source

max :: Ratio a -> Ratio a -> Ratio a Source

min :: Ratio a -> Ratio a -> Ratio a Source

Ord (Ptr a) 

Methods

compare :: Ptr a -> Ptr a -> Ordering Source

(<) :: Ptr a -> Ptr a -> Bool Source

(<=) :: Ptr a -> Ptr a -> Bool Source

(>) :: Ptr a -> Ptr a -> Bool Source

(>=) :: Ptr a -> Ptr a -> Bool Source

max :: Ptr a -> Ptr a -> Ptr a Source

min :: Ptr a -> Ptr a -> Ptr a Source

Ord (FunPtr a) 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering Source

(<) :: FunPtr a -> FunPtr a -> Bool Source

(<=) :: FunPtr a -> FunPtr a -> Bool Source

(>) :: FunPtr a -> FunPtr a -> Bool Source

(>=) :: FunPtr a -> FunPtr a -> Bool Source

max :: FunPtr a -> FunPtr a -> FunPtr a Source

min :: FunPtr a -> FunPtr a -> FunPtr a Source

Ord (U1 p) 

Methods

compare :: U1 p -> U1 p -> Ordering Source

(<) :: U1 p -> U1 p -> Bool Source

(<=) :: U1 p -> U1 p -> Bool Source

(>) :: U1 p -> U1 p -> Bool Source

(>=) :: U1 p -> U1 p -> Bool Source

max :: U1 p -> U1 p -> U1 p Source

min :: U1 p -> U1 p -> U1 p Source

Ord p => Ord (Par1 p) 

Methods

compare :: Par1 p -> Par1 p -> Ordering Source

(<) :: Par1 p -> Par1 p -> Bool Source

(<=) :: Par1 p -> Par1 p -> Bool Source

(>) :: Par1 p -> Par1 p -> Bool Source

(>=) :: Par1 p -> Par1 p -> Bool Source

max :: Par1 p -> Par1 p -> Par1 p Source

min :: Par1 p -> Par1 p -> Par1 p Source

Ord a => Ord (Down a) 

Methods

compare :: Down a -> Down a -> Ordering Source

(<) :: Down a -> Down a -> Bool Source

(<=) :: Down a -> Down a -> Bool Source

(>) :: Down a -> Down a -> Bool Source

(>=) :: Down a -> Down a -> Bool Source

max :: Down a -> Down a -> Down a Source

min :: Down a -> Down a -> Down a Source

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering Source

(<) :: Last a -> Last a -> Bool Source

(<=) :: Last a -> Last a -> Bool Source

(>) :: Last a -> Last a -> Bool Source

(>=) :: Last a -> Last a -> Bool Source

max :: Last a -> Last a -> Last a Source

min :: Last a -> Last a -> Last a Source

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering Source

(<) :: First a -> First a -> Bool Source

(<=) :: First a -> First a -> Bool Source

(>) :: First a -> First a -> Bool Source

(>=) :: First a -> First a -> Bool Source

max :: First a -> First a -> First a Source

min :: First a -> First a -> First a Source

Ord a => Ord (Product a) 
Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering Source

(<) :: Sum a -> Sum a -> Bool Source

(<=) :: Sum a -> Sum a -> Bool Source

(>) :: Sum a -> Sum a -> Bool Source

(>=) :: Sum a -> Sum a -> Bool Source

max :: Sum a -> Sum a -> Sum a Source

min :: Sum a -> Sum a -> Sum a Source

Ord a => Ord (Dual a) 

Methods

compare :: Dual a -> Dual a -> Ordering Source

(<) :: Dual a -> Dual a -> Bool Source

(<=) :: Dual a -> Dual a -> Bool Source

(>) :: Dual a -> Dual a -> Bool Source

(>=) :: Dual a -> Dual a -> Bool Source

max :: Dual a -> Dual a -> Dual a Source

min :: Dual a -> Dual a -> Dual a Source

Ord (ForeignPtr a) 
Ord a => Ord (ZipList a) 
Ord (Fixed a) 

Methods

compare :: Fixed a -> Fixed a -> Ordering Source

(<) :: Fixed a -> Fixed a -> Bool Source

(<=) :: Fixed a -> Fixed a -> Bool Source

(>) :: Fixed a -> Fixed a -> Bool Source

(>=) :: Fixed a -> Fixed a -> Bool Source

max :: Fixed a -> Fixed a -> Fixed a Source

min :: Fixed a -> Fixed a -> Fixed a Source

Ord a => Ord (NonEmpty a) 
Ord a => Ord (Option a) 

Methods

compare :: Option a -> Option a -> Ordering Source

(<) :: Option a -> Option a -> Bool Source

(<=) :: Option a -> Option a -> Bool Source

(>) :: Option a -> Option a -> Bool Source

(>=) :: Option a -> Option a -> Bool Source

max :: Option a -> Option a -> Option a Source

min :: Option a -> Option a -> Option a Source

Ord m => Ord (WrappedMonoid m) 
Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering Source

(<) :: Last a -> Last a -> Bool Source

(<=) :: Last a -> Last a -> Bool Source

(>) :: Last a -> Last a -> Bool Source

(>=) :: Last a -> Last a -> Bool Source

max :: Last a -> Last a -> Last a Source

min :: Last a -> Last a -> Last a Source

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering Source

(<) :: First a -> First a -> Bool Source

(<=) :: First a -> First a -> Bool Source

(>) :: First a -> First a -> Bool Source

(>=) :: First a -> First a -> Bool Source

max :: First a -> First a -> First a Source

min :: First a -> First a -> First a Source

Ord a => Ord (Max a) 

Methods

compare :: Max a -> Max a -> Ordering Source

(<) :: Max a -> Max a -> Bool Source

(<=) :: Max a -> Max a -> Bool Source

(>) :: Max a -> Max a -> Bool Source

(>=) :: Max a -> Max a -> Bool Source

max :: Max a -> Max a -> Max a Source

min :: Max a -> Max a -> Max a Source

Ord a => Ord (Min a) 

Methods

compare :: Min a -> Min a -> Ordering Source

(<) :: Min a -> Min a -> Bool Source

(<=) :: Min a -> Min a -> Bool Source

(>) :: Min a -> Min a -> Bool Source

(>=) :: Min a -> Min a -> Bool Source

max :: Min a -> Min a -> Min a Source

min :: Min a -> Min a -> Min a Source

Ord a => Ord (Identity a) 
(Ord a, Ord b) => Ord (Either a b) 

Methods

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

max :: Either a b -> Either a b -> Either a b Source

min :: Either a b -> Either a b -> Either a b Source

Ord (f p) => Ord (Rec1 f p) 

Methods

compare :: Rec1 f p -> Rec1 f p -> Ordering Source

(<) :: Rec1 f p -> Rec1 f p -> Bool Source

(<=) :: Rec1 f p -> Rec1 f p -> Bool Source

(>) :: Rec1 f p -> Rec1 f p -> Bool Source

(>=) :: Rec1 f p -> Rec1 f p -> Bool Source

max :: Rec1 f p -> Rec1 f p -> Rec1 f p Source

min :: Rec1 f p -> Rec1 f p -> Rec1 f p Source

Ord (URec Char p) 
Ord (URec Double p) 
Ord (URec Float p) 
Ord (URec Int p) 

Methods

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

max :: URec Int p -> URec Int p -> URec Int p Source

min :: URec Int p -> URec Int p -> URec Int p Source

Ord (URec Word p) 
Ord (URec (Ptr ()) p) 

Methods

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) 

Methods

compare :: (a, b) -> (a, b) -> Ordering Source

(<) :: (a, b) -> (a, b) -> Bool Source

(<=) :: (a, b) -> (a, b) -> Bool Source

(>) :: (a, b) -> (a, b) -> Bool Source

(>=) :: (a, b) -> (a, b) -> Bool Source

max :: (a, b) -> (a, b) -> (a, b) Source

min :: (a, b) -> (a, b) -> (a, b) Source

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering Source

(<) :: Proxy k s -> Proxy k s -> Bool Source

(<=) :: Proxy k s -> Proxy k s -> Bool Source

(>) :: Proxy k s -> Proxy k s -> Bool Source

(>=) :: Proxy k s -> Proxy k s -> Bool Source

max :: Proxy k s -> Proxy k s -> Proxy k s Source

min :: Proxy k s -> Proxy k s -> Proxy k s Source

Ord a => Ord (Arg a b) 

Methods

compare :: Arg a b -> Arg a b -> Ordering Source

(<) :: Arg a b -> Arg a b -> Bool Source

(<=) :: Arg a b -> Arg a b -> Bool Source

(>) :: Arg a b -> Arg a b -> Bool Source

(>=) :: Arg a b -> Arg a b -> Bool Source

max :: Arg a b -> Arg a b -> Arg a b Source

min :: Arg a b -> Arg a b -> Arg a b Source

Ord c => Ord (K1 i c p) 

Methods

compare :: K1 i c p -> K1 i c p -> Ordering Source

(<) :: K1 i c p -> K1 i c p -> Bool Source

(<=) :: K1 i c p -> K1 i c p -> Bool Source

(>) :: K1 i c p -> K1 i c p -> Bool Source

(>=) :: K1 i c p -> K1 i c p -> Bool Source

max :: K1 i c p -> K1 i c p -> K1 i c p Source

min :: K1 i c p -> K1 i c p -> K1 i c p Source

(Ord (f p), Ord (g p)) => Ord ((:+:) f g p) 

Methods

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

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source

(Ord (f p), Ord (g p)) => Ord ((:*:) f g p) 

Methods

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

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source

Ord (f (g p)) => Ord ((:.:) f g p) 

Methods

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

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source

(Ord a, Ord b, Ord c) => Ord (a, b, c) 

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering Source

(<) :: (a, b, c) -> (a, b, c) -> Bool Source

(<=) :: (a, b, c) -> (a, b, c) -> Bool Source

(>) :: (a, b, c) -> (a, b, c) -> Bool Source

(>=) :: (a, b, c) -> (a, b, c) -> Bool Source

max :: (a, b, c) -> (a, b, c) -> (a, b, c) Source

min :: (a, b, c) -> (a, b, c) -> (a, b, c) Source

Ord ((:~:) k a b) 

Methods

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

max :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b Source

min :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b Source

Ord (Coercion k a b) 

Methods

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) 

Methods

compare :: Alt k f a -> Alt k f a -> Ordering Source

(<) :: Alt k f a -> Alt k f a -> Bool Source

(<=) :: Alt k f a -> Alt k f a -> Bool Source

(>) :: Alt k f a -> Alt k f a -> Bool Source

(>=) :: Alt k f a -> Alt k f a -> Bool Source

max :: Alt k f a -> Alt k f a -> Alt k f a Source

min :: Alt k f a -> Alt k f a -> Alt k f a Source

Ord a => Ord (Const k a b) 

Methods

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

max :: Const k a b -> Const k a b -> Const k a b Source

min :: Const k a b -> Const k a b -> Const k a b Source

Ord (f p) => Ord (M1 i c f p) 

Methods

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

max :: M1 i c f p -> M1 i c f p -> M1 i c f p Source

min :: M1 i c f p -> M1 i c f p -> M1 i c f p Source

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 

Methods

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 (TYPE Lifted) f g a) 

Methods

compare :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Ordering Source

(<) :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Bool Source

(<=) :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Bool Source

(>) :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Bool Source

(>=) :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Bool Source

max :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a Source

min :: Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a -> Product (TYPE Lifted) f g a Source

(Ord1 f, Ord1 g, Ord a) => Ord (Sum (TYPE Lifted) f g a) 

Methods

compare :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Ordering Source

(<) :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Bool Source

(<=) :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Bool Source

(>) :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Bool Source

(>=) :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Bool Source

max :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a Source

min :: Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a -> Sum (TYPE Lifted) f g a Source

(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 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 (TYPE Lifted) (TYPE Lifted) 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 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) 

Methods

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) 

Methods

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) 

Methods

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) 

Methods

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) 

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 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) 

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 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) 

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 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) 

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 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) 

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 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

data Ordering :: TYPE Lifted Source

Constructors

LT 
EQ 
GT 

Instances

Bounded Ordering 
Enum Ordering 
Eq Ordering 
Data Ordering 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source

toConstr :: Ordering -> Constr Source

dataTypeOf :: Ordering -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) Source

gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source

Ord Ordering 
Read Ordering 
Show Ordering 
Ix Ordering 
Generic Ordering 

Associated Types

type Rep Ordering :: * -> * Source

Semigroup Ordering 
Monoid Ordering 
type Rep Ordering = D1 (MetaData "Ordering" "GHC.Types" "ghc-prim" False) ((:+:) (C1 (MetaCons "LT" PrefixI False) U1) ((:+:) (C1 (MetaCons "EQ" PrefixI False) U1) (C1 (MetaCons "GT" PrefixI False) U1))) 
type (==) Ordering a b 

newtype Down a Source

The Down type allows you to reverse sort order conveniently. A value of type Down a contains a value of type a (represented as Down a). If a has an Ord 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: then sortWith by Down x

Provides Show and Read instances (since: 4.7.0.0).

Since: 4.6.0.0

Constructors

Down a 

Instances

Eq a => Eq (Down a) 

Methods

(==) :: Down a -> Down a -> Bool Source

(/=) :: Down a -> Down a -> Bool Source

Ord a => Ord (Down a) 

Methods

compare :: Down a -> Down a -> Ordering Source

(<) :: Down a -> Down a -> Bool Source

(<=) :: Down a -> Down a -> Bool Source

(>) :: Down a -> Down a -> Bool Source

(>=) :: Down a -> Down a -> Bool Source

max :: Down a -> Down a -> Down a Source

min :: Down a -> Down a -> Down a Source

Read a => Read (Down a) 
Show a => Show (Down a) 

comparing :: Ord a => (b -> a) -> b -> b -> Ordering Source

comparing p x y = compare (p x) (p y)

Useful combinator for use in conjunction with the xxxBy family of functions from Data.List, for example:

  ... sortBy (comparing fst) ...