base-4.11.1.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 | (<=)

Methods

compare :: a -> a -> Ordering Source #

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

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

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

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

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances
Ord Bool 
Instance details

Defined in GHC.Classes

Ord Char 
Instance details

Defined in GHC.Classes

Ord Double 
Instance details

Defined in GHC.Classes

Ord Float 
Instance details

Defined in GHC.Classes

Ord Int 
Instance details

Defined in GHC.Classes

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 #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16 #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32 #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64 #

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Integer 
Instance details

Defined in GHC.Integer.Type

Ord Natural # 
Instance details

Defined in GHC.Natural

Ord Ordering 
Instance details

Defined in GHC.Classes

Ord Word 
Instance details

Defined in GHC.Classes

Ord Word8 #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16 #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32 #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64 #

Since: base-2.1

Instance details

Defined in GHC.Word

Ord SomeTypeRep # 
Instance details

Defined in Data.Typeable.Internal

Ord () 
Instance details

Defined in GHC.Classes

Methods

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

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

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

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

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

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

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

Ord TyCon 
Instance details

Defined in GHC.Classes

Ord BigNat 
Instance details

Defined in GHC.Integer.Type

Ord GeneralCategory # 
Instance details

Defined in GHC.Unicode

Ord Fingerprint # 
Instance details

Defined in GHC.Fingerprint.Type

Ord IOMode # 
Instance details

Defined in GHC.IO.IOMode

Ord IntPtr # 
Instance details

Defined in Foreign.Ptr

Ord WordPtr # 
Instance details

Defined in Foreign.Ptr

Ord CUIntMax # 
Instance details

Defined in Foreign.C.Types

Ord CIntMax # 
Instance details

Defined in Foreign.C.Types

Ord CUIntPtr # 
Instance details

Defined in Foreign.C.Types

Ord CIntPtr # 
Instance details

Defined in Foreign.C.Types

Ord CSUSeconds # 
Instance details

Defined in Foreign.C.Types

Ord CUSeconds # 
Instance details

Defined in Foreign.C.Types

Ord CTime # 
Instance details

Defined in Foreign.C.Types

Ord CClock # 
Instance details

Defined in Foreign.C.Types

Ord CSigAtomic # 
Instance details

Defined in Foreign.C.Types

Ord CWchar # 
Instance details

Defined in Foreign.C.Types

Ord CSize # 
Instance details

Defined in Foreign.C.Types

Ord CPtrdiff # 
Instance details

Defined in Foreign.C.Types

Ord CDouble # 
Instance details

Defined in Foreign.C.Types

Ord CFloat # 
Instance details

Defined in Foreign.C.Types

Ord CBool # 
Instance details

Defined in Foreign.C.Types

Ord CULLong # 
Instance details

Defined in Foreign.C.Types

Ord CLLong # 
Instance details

Defined in Foreign.C.Types

Ord CULong # 
Instance details

Defined in Foreign.C.Types

Ord CLong # 
Instance details

Defined in Foreign.C.Types

Ord CUInt # 
Instance details

Defined in Foreign.C.Types

Ord CInt # 
Instance details

Defined in Foreign.C.Types

Ord CUShort # 
Instance details

Defined in Foreign.C.Types

Ord CShort # 
Instance details

Defined in Foreign.C.Types

Ord CUChar # 
Instance details

Defined in Foreign.C.Types

Ord CSChar # 
Instance details

Defined in Foreign.C.Types

Ord CChar # 
Instance details

Defined in Foreign.C.Types

Ord SomeNat #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Ord SomeSymbol #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Ord DecidedStrictness # 
Instance details

Defined in GHC.Generics

Ord SourceStrictness # 
Instance details

Defined in GHC.Generics

Ord SourceUnpackedness # 
Instance details

Defined in GHC.Generics

Ord Associativity # 
Instance details

Defined in GHC.Generics

Ord Fixity # 
Instance details

Defined in GHC.Generics

Ord Any # 
Instance details

Defined in Data.Semigroup.Internal

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 # 
Instance details

Defined in Data.Semigroup.Internal

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 ArithException # 
Instance details

Defined in GHC.Exception

Ord ErrorCall # 
Instance details

Defined in GHC.Exception

Ord SeekMode # 
Instance details

Defined in GHC.IO.Device

Ord NewlineMode # 
Instance details

Defined in GHC.IO.Handle.Types

Ord Newline # 
Instance details

Defined in GHC.IO.Handle.Types

Ord BufferMode # 
Instance details

Defined in GHC.IO.Handle.Types

Ord ExitCode # 
Instance details

Defined in GHC.IO.Exception

Ord ArrayException # 
Instance details

Defined in GHC.IO.Exception

Ord AsyncException # 
Instance details

Defined in GHC.IO.Exception

Ord Fd # 
Instance details

Defined in System.Posix.Types

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 CTimer # 
Instance details

Defined in System.Posix.Types

Ord CKey # 
Instance details

Defined in System.Posix.Types

Ord CId # 
Instance details

Defined in System.Posix.Types

Methods

compare :: CId -> CId -> Ordering Source #

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

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

(>) :: CId -> CId -> Bool Source #

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

max :: CId -> CId -> CId Source #

min :: CId -> CId -> CId Source #

Ord CFsFilCnt # 
Instance details

Defined in System.Posix.Types

Ord CFsBlkCnt # 
Instance details

Defined in System.Posix.Types

Ord CClockId # 
Instance details

Defined in System.Posix.Types

Ord CBlkCnt # 
Instance details

Defined in System.Posix.Types

Ord CBlkSize # 
Instance details

Defined in System.Posix.Types

Ord CRLim # 
Instance details

Defined in System.Posix.Types

Ord CTcflag # 
Instance details

Defined in System.Posix.Types

Ord CSpeed # 
Instance details

Defined in System.Posix.Types

Ord CCc # 
Instance details

Defined in System.Posix.Types

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 # 
Instance details

Defined in System.Posix.Types

Ord CNlink # 
Instance details

Defined in System.Posix.Types

Ord CGid # 
Instance details

Defined in System.Posix.Types

Ord CSsize # 
Instance details

Defined in System.Posix.Types

Ord CPid # 
Instance details

Defined in System.Posix.Types

Ord COff # 
Instance details

Defined in System.Posix.Types

Ord CMode # 
Instance details

Defined in System.Posix.Types

Ord CIno # 
Instance details

Defined in System.Posix.Types

Ord CDev # 
Instance details

Defined in System.Posix.Types

Ord ThreadStatus # 
Instance details

Defined in GHC.Conc.Sync

Ord BlockReason # 
Instance details

Defined in GHC.Conc.Sync

Ord ThreadId #

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord Version #

Since: base-2.1

Instance details

Defined in Data.Version

Ord ByteOrder # 
Instance details

Defined in GHC.ByteOrder

Ord Unique # 
Instance details

Defined in Data.Unique

Ord Void #

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Ord a => Ord [a] 
Instance details

Defined in GHC.Classes

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) # 
Instance details

Defined in GHC.Base

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

Since: base-2.0.1

Instance details

Defined in GHC.Real

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) # 
Instance details

Defined in GHC.Ptr

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) # 
Instance details

Defined in GHC.Ptr

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 p => Ord (Par1 p) # 
Instance details

Defined in GHC.Generics

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 (NonEmpty a) # 
Instance details

Defined in GHC.Base

Ord a => Ord (Down a) #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

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 (Product a) # 
Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord (Sum a) # 
Instance details

Defined in Data.Semigroup.Internal

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) # 
Instance details

Defined in Data.Semigroup.Internal

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 a => Ord (Last a) # 
Instance details

Defined in Data.Monoid

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) # 
Instance details

Defined in Data.Monoid

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 (ForeignPtr a) #

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Ord a => Ord (Identity a) # 
Instance details

Defined in Data.Functor.Identity

Ord a => Ord (ZipList a) # 
Instance details

Defined in Control.Applicative

Ord a => Ord (Option a) # 
Instance details

Defined in Data.Semigroup

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) # 
Instance details

Defined in Data.Semigroup

Ord a => Ord (Last a) # 
Instance details

Defined in Data.Semigroup

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) # 
Instance details

Defined in Data.Semigroup

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) # 
Instance details

Defined in Data.Semigroup

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) # 
Instance details

Defined in Data.Semigroup

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 (Fixed a) # 
Instance details

Defined in Data.Fixed

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 b) => Ord (Either a b) # 
Instance details

Defined in Data.Either

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 (V1 p) #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: V1 p -> V1 p -> Ordering Source #

(<) :: V1 p -> V1 p -> Bool Source #

(<=) :: V1 p -> V1 p -> Bool Source #

(>) :: V1 p -> V1 p -> Bool Source #

(>=) :: V1 p -> V1 p -> Bool Source #

max :: V1 p -> V1 p -> V1 p Source #

min :: V1 p -> V1 p -> V1 p Source #

Ord (U1 p) #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

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 (TypeRep a) #

Since: base-4.4.0.0

Instance details

Defined in Data.Typeable.Internal

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

Defined in GHC.Classes

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

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

max :: Proxy s -> Proxy s -> Proxy s Source #

min :: Proxy s -> Proxy s -> Proxy s Source #

Ord a => Ord (Arg a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

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 (f p) => Ord (Rec1 f p) # 
Instance details

Defined in GHC.Generics

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 Word p) # 
Instance details

Defined in GHC.Generics

Methods

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 #

max :: URec Word p -> URec Word p -> URec Word p Source #

min :: URec Word p -> URec Word p -> URec Word p Source #

Ord (URec Int p) # 
Instance details

Defined in GHC.Generics

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 Float p) # 
Instance details

Defined in GHC.Generics

Ord (URec Double p) # 
Instance details

Defined in GHC.Generics

Ord (URec Char p) # 
Instance details

Defined in GHC.Generics

Methods

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 #

max :: URec Char p -> URec Char p -> URec Char p Source #

min :: URec Char p -> URec Char p -> URec Char p Source #

Ord (URec (Ptr ()) p) # 
Instance details

Defined in GHC.Generics

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 c) => Ord (a, b, c) 
Instance details

Defined in GHC.Classes

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 (a :~: b) # 
Instance details

Defined in Data.Type.Equality

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 (Coercion a b) # 
Instance details

Defined in Data.Type.Coercion

Methods

compare :: Coercion a b -> Coercion a b -> Ordering Source #

(<) :: Coercion a b -> Coercion a b -> Bool Source #

(<=) :: Coercion a b -> Coercion a b -> Bool Source #

(>) :: Coercion a b -> Coercion a b -> Bool Source #

(>=) :: Coercion a b -> Coercion a b -> Bool Source #

max :: Coercion a b -> Coercion a b -> Coercion a b Source #

min :: Coercion a b -> Coercion a b -> Coercion a b Source #

Ord (f a) => Ord (Alt f a) # 
Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

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

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

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

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

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

Ord a => Ord (Const a b) # 
Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

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

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

Ord c => Ord (K1 i c p) # 
Instance details

Defined in GHC.Generics

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) # 
Instance details

Defined in GHC.Generics

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) # 
Instance details

Defined in GHC.Generics

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 d) => Ord (a, b, c, d) 
Instance details

Defined in GHC.Classes

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 #

Ord (a :~~: b) #

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

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 #

(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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 #

max :: Sum f g a -> Sum f g a -> Sum f g a Source #

min :: Sum f g a -> Sum f g a -> Sum f g a Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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 #

Ord (f p) => Ord (M1 i c f p) # 
Instance details

Defined in GHC.Generics

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 (f (g p)) => Ord ((f :.: g) p) # 
Instance details

Defined in GHC.Generics

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 d, Ord e) => Ord (a, b, c, d, e) 
Instance details

Defined in GHC.Classes

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 f g a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Defined in GHC.Classes

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

Constructors

LT 
EQ 
GT 
Instances
Bounded Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Ordering 
Instance details

Defined in GHC.Classes

Data Ordering Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

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

Defined in GHC.Classes

Read Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering Source # 
Instance details

Defined in GHC.Show

Ix Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Arr

Generic Ordering Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: * -> * Source #

Semigroup Ordering Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monoid Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Base

type Rep Ordering Source # 
Instance details

Defined in GHC.Generics

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

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

Since: base-4.6.0.0

Constructors

Down a 
Instances
Monad Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(>>=) :: Down a -> (a -> Down b) -> Down b Source #

(>>) :: Down a -> Down b -> Down b Source #

return :: a -> Down a Source #

fail :: String -> Down a Source #

Functor Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

fmap :: (a -> b) -> Down a -> Down b Source #

(<$) :: a -> Down b -> Down a Source #

Applicative Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

pure :: a -> Down a Source #

(<*>) :: Down (a -> b) -> Down a -> Down b Source #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c Source #

(*>) :: Down a -> Down b -> Down b Source #

(<*) :: Down a -> Down b -> Down a Source #

Eq a => Eq (Down a) Source # 
Instance details

Defined in Data.Ord

Methods

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

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

Num a => Num (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(+) :: Down a -> Down a -> Down a Source #

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

(*) :: Down a -> Down a -> Down a Source #

negate :: Down a -> Down a Source #

abs :: Down a -> Down a Source #

signum :: Down a -> Down a Source #

fromInteger :: Integer -> Down a Source #

Ord a => Ord (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

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

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Show a => Show (Down a) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS Source #

show :: Down a -> String Source #

showList :: [Down a] -> ShowS Source #

Semigroup a => Semigroup (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

sconcat :: NonEmpty (Down a) -> Down a Source #

stimes :: Integral b => b -> Down a -> Down a Source #

Monoid a => Monoid (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a Source #

mappend :: Down a -> Down a -> Down a Source #

mconcat :: [Down a] -> 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) ...