base-4.8.2.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

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

Methods

compare :: a -> a -> Ordering

(<) :: a -> a -> Bool infix 4

(<=) :: a -> a -> Bool infix 4

(>) :: a -> a -> Bool infix 4

(>=) :: a -> a -> Bool infix 4

max :: a -> a -> a

min :: a -> a -> a

Instances

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering

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

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

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

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

max :: Bool -> Bool -> Bool

min :: Bool -> Bool -> Bool

Ord Char 

Methods

compare :: Char -> Char -> Ordering

(<) :: Char -> Char -> Bool

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

(>) :: Char -> Char -> Bool

(>=) :: Char -> Char -> Bool

max :: Char -> Char -> Char

min :: Char -> Char -> Char

Ord Double 
Ord Float 

Methods

compare :: Float -> Float -> Ordering

(<) :: Float -> Float -> Bool

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

(>) :: Float -> Float -> Bool

(>=) :: Float -> Float -> Bool

max :: Float -> Float -> Float

min :: Float -> Float -> Float

Ord Int 

Methods

compare :: Int -> Int -> Ordering

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

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

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

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

max :: Int -> Int -> Int

min :: Int -> Int -> Int

Ord Int8 

Methods

compare :: Int8 -> Int8 -> Ordering

(<) :: Int8 -> Int8 -> Bool

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

(>) :: Int8 -> Int8 -> Bool

(>=) :: Int8 -> Int8 -> Bool

max :: Int8 -> Int8 -> Int8

min :: Int8 -> Int8 -> Int8

Ord Int16 

Methods

compare :: Int16 -> Int16 -> Ordering

(<) :: Int16 -> Int16 -> Bool

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

(>) :: Int16 -> Int16 -> Bool

(>=) :: Int16 -> Int16 -> Bool

max :: Int16 -> Int16 -> Int16

min :: Int16 -> Int16 -> Int16

Ord Int32 

Methods

compare :: Int32 -> Int32 -> Ordering

(<) :: Int32 -> Int32 -> Bool

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

(>) :: Int32 -> Int32 -> Bool

(>=) :: Int32 -> Int32 -> Bool

max :: Int32 -> Int32 -> Int32

min :: Int32 -> Int32 -> Int32

Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering

(<) :: Int64 -> Int64 -> Bool

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

(>) :: Int64 -> Int64 -> Bool

(>=) :: Int64 -> Int64 -> Bool

max :: Int64 -> Int64 -> Int64

min :: Int64 -> Int64 -> Int64

Ord Integer 
Ord Ordering 
Ord Word 

Methods

compare :: Word -> Word -> Ordering

(<) :: Word -> Word -> Bool

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

(>) :: Word -> Word -> Bool

(>=) :: Word -> Word -> Bool

max :: Word -> Word -> Word

min :: Word -> Word -> Word

Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering

(<) :: Word8 -> Word8 -> Bool

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

(>) :: Word8 -> Word8 -> Bool

(>=) :: Word8 -> Word8 -> Bool

max :: Word8 -> Word8 -> Word8

min :: Word8 -> Word8 -> Word8

Ord Word16 
Ord Word32 
Ord Word64 
Ord TypeRep 
Ord () 

Methods

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

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

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

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

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

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

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

Ord BigNat 
Ord GeneralCategory 
Ord Fingerprint 
Ord TyCon 

Methods

compare :: TyCon -> TyCon -> Ordering

(<) :: TyCon -> TyCon -> Bool

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

(>) :: TyCon -> TyCon -> Bool

(>=) :: TyCon -> TyCon -> Bool

max :: TyCon -> TyCon -> TyCon

min :: TyCon -> TyCon -> TyCon

Ord Associativity 
Ord Fixity 
Ord Arity 

Methods

compare :: Arity -> Arity -> Ordering

(<) :: Arity -> Arity -> Bool

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

(>) :: Arity -> Arity -> Bool

(>=) :: Arity -> Arity -> Bool

max :: Arity -> Arity -> Arity

min :: Arity -> Arity -> Arity

Ord Any 

Methods

compare :: Any -> Any -> Ordering

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

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

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

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

max :: Any -> Any -> Any

min :: Any -> Any -> Any

Ord All 

Methods

compare :: All -> All -> Ordering

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

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

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

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

max :: All -> All -> All

min :: All -> All -> All

Ord ArithException 
Ord ErrorCall 
Ord CUIntMax 
Ord CIntMax 
Ord CUIntPtr 
Ord CIntPtr 
Ord CSUSeconds 
Ord CUSeconds 
Ord CTime 

Methods

compare :: CTime -> CTime -> Ordering

(<) :: CTime -> CTime -> Bool

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

(>) :: CTime -> CTime -> Bool

(>=) :: CTime -> CTime -> Bool

max :: CTime -> CTime -> CTime

min :: CTime -> CTime -> CTime

Ord CClock 
Ord CSigAtomic 
Ord CWchar 
Ord CSize 

Methods

compare :: CSize -> CSize -> Ordering

(<) :: CSize -> CSize -> Bool

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

(>) :: CSize -> CSize -> Bool

(>=) :: CSize -> CSize -> Bool

max :: CSize -> CSize -> CSize

min :: CSize -> CSize -> CSize

Ord CPtrdiff 
Ord CDouble 
Ord CFloat 
Ord CULLong 
Ord CLLong 
Ord CULong 
Ord CLong 

Methods

compare :: CLong -> CLong -> Ordering

(<) :: CLong -> CLong -> Bool

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

(>) :: CLong -> CLong -> Bool

(>=) :: CLong -> CLong -> Bool

max :: CLong -> CLong -> CLong

min :: CLong -> CLong -> CLong

Ord CUInt 

Methods

compare :: CUInt -> CUInt -> Ordering

(<) :: CUInt -> CUInt -> Bool

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

(>) :: CUInt -> CUInt -> Bool

(>=) :: CUInt -> CUInt -> Bool

max :: CUInt -> CUInt -> CUInt

min :: CUInt -> CUInt -> CUInt

Ord CInt 

Methods

compare :: CInt -> CInt -> Ordering

(<) :: CInt -> CInt -> Bool

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

(>) :: CInt -> CInt -> Bool

(>=) :: CInt -> CInt -> Bool

max :: CInt -> CInt -> CInt

min :: CInt -> CInt -> CInt

Ord CUShort 
Ord CShort 
Ord CUChar 
Ord CSChar 
Ord CChar 

Methods

compare :: CChar -> CChar -> Ordering

(<) :: CChar -> CChar -> Bool

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

(>) :: CChar -> CChar -> Bool

(>=) :: CChar -> CChar -> Bool

max :: CChar -> CChar -> CChar

min :: CChar -> CChar -> 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

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

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

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

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

max :: Fd -> Fd -> Fd

min :: Fd -> Fd -> Fd

Ord CRLim 

Methods

compare :: CRLim -> CRLim -> Ordering

(<) :: CRLim -> CRLim -> Bool

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

(>) :: CRLim -> CRLim -> Bool

(>=) :: CRLim -> CRLim -> Bool

max :: CRLim -> CRLim -> CRLim

min :: CRLim -> CRLim -> CRLim

Ord CTcflag 
Ord CSpeed 
Ord CCc 

Methods

compare :: CCc -> CCc -> Ordering

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

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

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

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

max :: CCc -> CCc -> CCc

min :: CCc -> CCc -> CCc

Ord CUid 

Methods

compare :: CUid -> CUid -> Ordering

(<) :: CUid -> CUid -> Bool

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

(>) :: CUid -> CUid -> Bool

(>=) :: CUid -> CUid -> Bool

max :: CUid -> CUid -> CUid

min :: CUid -> CUid -> CUid

Ord CNlink 
Ord CGid 

Methods

compare :: CGid -> CGid -> Ordering

(<) :: CGid -> CGid -> Bool

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

(>) :: CGid -> CGid -> Bool

(>=) :: CGid -> CGid -> Bool

max :: CGid -> CGid -> CGid

min :: CGid -> CGid -> CGid

Ord CSsize 
Ord CPid 

Methods

compare :: CPid -> CPid -> Ordering

(<) :: CPid -> CPid -> Bool

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

(>) :: CPid -> CPid -> Bool

(>=) :: CPid -> CPid -> Bool

max :: CPid -> CPid -> CPid

min :: CPid -> CPid -> CPid

Ord COff 

Methods

compare :: COff -> COff -> Ordering

(<) :: COff -> COff -> Bool

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

(>) :: COff -> COff -> Bool

(>=) :: COff -> COff -> Bool

max :: COff -> COff -> COff

min :: COff -> COff -> COff

Ord CMode 

Methods

compare :: CMode -> CMode -> Ordering

(<) :: CMode -> CMode -> Bool

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

(>) :: CMode -> CMode -> Bool

(>=) :: CMode -> CMode -> Bool

max :: CMode -> CMode -> CMode

min :: CMode -> CMode -> CMode

Ord CIno 

Methods

compare :: CIno -> CIno -> Ordering

(<) :: CIno -> CIno -> Bool

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

(>) :: CIno -> CIno -> Bool

(>=) :: CIno -> CIno -> Bool

max :: CIno -> CIno -> CIno

min :: CIno -> CIno -> CIno

Ord CDev 

Methods

compare :: CDev -> CDev -> Ordering

(<) :: CDev -> CDev -> Bool

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

(>) :: CDev -> CDev -> Bool

(>=) :: CDev -> CDev -> Bool

max :: CDev -> CDev -> CDev

min :: CDev -> CDev -> CDev

Ord ThreadStatus 
Ord BlockReason 
Ord ThreadId 
Ord IOMode 
Ord Version 
Ord Natural 
Ord SomeSymbol 
Ord SomeNat 
Ord Unique 
Ord Void 

Methods

compare :: Void -> Void -> Ordering

(<) :: Void -> Void -> Bool

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

(>) :: Void -> Void -> Bool

(>=) :: Void -> Void -> Bool

max :: Void -> Void -> Void

min :: Void -> Void -> Void

Ord a => Ord [a] 

Methods

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

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

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

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

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

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

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

Integral a => Ord (Ratio a) 

Methods

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

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

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

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

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

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

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

Ord (Ptr a) 

Methods

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

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

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

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

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

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

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

Ord (FunPtr a) 

Methods

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

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

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

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

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

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

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

Ord (U1 p) 

Methods

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

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

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

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

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

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

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

Ord p => Ord (Par1 p) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Maybe a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Down a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Last a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (First a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Product a) 

Methods

compare :: Product a -> Product a -> Ordering

(<) :: Product a -> Product a -> Bool

(<=) :: Product a -> Product a -> Bool

(>) :: Product a -> Product a -> Bool

(>=) :: Product a -> Product a -> Bool

max :: Product a -> Product a -> Product a

min :: Product a -> Product a -> Product a

Ord a => Ord (Sum a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Dual a) 

Methods

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

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

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

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

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

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

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

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

Methods

compare :: ZipList a -> ZipList a -> Ordering

(<) :: ZipList a -> ZipList a -> Bool

(<=) :: ZipList a -> ZipList a -> Bool

(>) :: ZipList a -> ZipList a -> Bool

(>=) :: ZipList a -> ZipList a -> Bool

max :: ZipList a -> ZipList a -> ZipList a

min :: ZipList a -> ZipList a -> ZipList a

Ord (Fixed a) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering

(<) :: Identity a -> Identity a -> Bool

(<=) :: Identity a -> Identity a -> Bool

(>) :: Identity a -> Identity a -> Bool

(>=) :: Identity a -> Identity a -> Bool

max :: Identity a -> Identity a -> Identity a

min :: Identity a -> Identity a -> Identity a

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

Methods

compare :: Either a b -> Either a b -> Ordering

(<) :: Either a b -> Either a b -> Bool

(<=) :: Either a b -> Either a b -> Bool

(>) :: Either a b -> Either a b -> Bool

(>=) :: Either a b -> Either a b -> Bool

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Ord (Proxy k s) 

Methods

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

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

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

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

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

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

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

Ord a => Ord (Const a b) 

Methods

compare :: Const a b -> Const a b -> Ordering

(<) :: Const a b -> Const a b -> Bool

(<=) :: Const a b -> Const a b -> Bool

(>) :: Const a b -> Const a b -> Bool

(>=) :: Const a b -> Const a b -> Bool

max :: Const a b -> Const a b -> Const a b

min :: Const a b -> Const a b -> Const a b

Ord c => Ord (K1 i c p) 

Methods

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

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

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

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

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

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

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

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

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering

(<) :: (f :+: g) p -> (f :+: g) p -> Bool

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool

(>) :: (f :+: g) p -> (f :+: g) p -> Bool

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool

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

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

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

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering

(<) :: (f :*: g) p -> (f :*: g) p -> Bool

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool

(>) :: (f :*: g) p -> (f :*: g) p -> Bool

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool

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

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

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

Methods

compare :: (f :.: g) p -> (f :.: g) p -> Ordering

(<) :: (f :.: g) p -> (f :.: g) p -> Bool

(<=) :: (f :.: g) p -> (f :.: g) p -> Bool

(>) :: (f :.: g) p -> (f :.: g) p -> Bool

(>=) :: (f :.: g) p -> (f :.: g) p -> Bool

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

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

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

Methods

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

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

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

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

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

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

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

Ord ((:~:) k a b) 

Methods

compare :: (k :~: a) b -> (k :~: a) b -> Ordering

(<) :: (k :~: a) b -> (k :~: a) b -> Bool

(<=) :: (k :~: a) b -> (k :~: a) b -> Bool

(>) :: (k :~: a) b -> (k :~: a) b -> Bool

(>=) :: (k :~: a) b -> (k :~: a) b -> Bool

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

min :: (k :~: a) b -> (k :~: a) b -> (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

max :: Coercion k a b -> Coercion k a b -> Coercion k a b

min :: Coercion k a b -> Coercion k a b -> Coercion k a b

Ord (f a) => Ord (Alt k f a) 

Methods

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

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

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

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

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

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

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

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

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering

(<) :: M1 i c f p -> M1 i c f p -> Bool

(<=) :: M1 i c f p -> M1 i c f p -> Bool

(>) :: M1 i c f p -> M1 i c f p -> Bool

(>=) :: M1 i c f p -> M1 i c f p -> Bool

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

min :: M1 i c f p -> M1 i c f p -> 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 :: *

Constructors

LT 
EQ 
GT 

Instances

Bounded Ordering Source 
Enum Ordering Source 
Eq Ordering 
Data Ordering Source 

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source

dataCast2 :: Typeable (* -> * -> *) 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 Source 
Show Ordering Source 
Ix Ordering Source 
Generic Ordering Source 

Associated Types

type Rep Ordering :: * -> * Source

Monoid Ordering Source 
type Rep Ordering 
type (==) Ordering a b Source 

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

Methods

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

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

Ord a => Ord (Down a) Source 

Methods

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

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

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

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

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

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

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

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

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