Prelude (original) (raw)

Ord Bool

Instance details

Defined in GHC.Classes

Ord Char

Instance details

Defined in GHC.Classes

Ord Double

Note that due to the presence of NaN, [Double](Prelude.html#t:Double "Prelude")'s [Ord](Prelude.html#t:Ord "Prelude") instance does not satisfy reflexivity.

>>> **0/0 <= (0/0 :: Double)** ****False

Also note that, due to the same, [Ord](Prelude.html#t:Ord "Prelude")'s operator interactions are not respected by [Double](Prelude.html#t:Double "Prelude")'s instance:

>>> **(0/0 :: Double) > 1** ****False >>> **compare (0/0 :: Double) 1** ****GT

Instance details

Defined in GHC.Classes

Ord Float

Note that due to the presence of NaN, [Float](Prelude.html#t:Float "Prelude")'s [Ord](Prelude.html#t:Ord "Prelude") instance does not satisfy reflexivity.

>>> **0/0 <= (0/0 :: Float)** ****False

Also note that, due to the same, [Ord](Prelude.html#t:Ord "Prelude")'s operator interactions are not respected by [Float](Prelude.html#t:Float "Prelude")'s instance:

>>> **(0/0 :: Float) > 1** ****False >>> **compare (0/0 :: Float) 1** ****GT

Instance details

Defined in GHC.Classes

Ord Int

Instance details

Defined in GHC.Classes

Ord Int8 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Ord Int16 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Ord Int32 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Ord Int64 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Ord Integer

Instance details

Defined in GHC.Integer.Type

Ord Natural Source #

Since: 4.8.0.0

Instance details

Defined in GHC.Natural

Ord Ordering

Instance details

Defined in GHC.Classes

Ord Word

Instance details

Defined in GHC.Classes

Ord Word8 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Ord Word16 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Ord Word32 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Ord Word64 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Ord SomeTypeRep Source #

Instance details

Defined in Data.Typeable.Internal

Ord ()

Instance details

Defined in GHC.Classes

Methods

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

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

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

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

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

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

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

Ord TyCon

Instance details

Defined in GHC.Classes

Ord BigNat

Instance details

Defined in GHC.Integer.Type

Ord GeneralCategory Source #

Since: 2.1

Instance details

Defined in GHC.Unicode

Ord Fingerprint Source #

Since: 4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Ord IOMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ord IntPtr Source #

Instance details

Defined in Foreign.Ptr

Ord WordPtr Source #

Instance details

Defined in Foreign.Ptr

Ord CUIntMax Source #

Instance details

Defined in Foreign.C.Types

Ord CIntMax Source #

Instance details

Defined in Foreign.C.Types

Ord CUIntPtr Source #

Instance details

Defined in Foreign.C.Types

Ord CIntPtr Source #

Instance details

Defined in Foreign.C.Types

Ord CSUSeconds Source #

Instance details

Defined in Foreign.C.Types

Ord CUSeconds Source #

Instance details

Defined in Foreign.C.Types

Ord CTime Source #

Instance details

Defined in Foreign.C.Types

Ord CClock Source #

Instance details

Defined in Foreign.C.Types

Ord CSigAtomic Source #

Instance details

Defined in Foreign.C.Types

Ord CWchar Source #

Instance details

Defined in Foreign.C.Types

Ord CSize Source #

Instance details

Defined in Foreign.C.Types

Ord CPtrdiff Source #

Instance details

Defined in Foreign.C.Types

Ord CDouble Source #

Instance details

Defined in Foreign.C.Types

Ord CFloat Source #

Instance details

Defined in Foreign.C.Types

Ord CBool Source #

Instance details

Defined in Foreign.C.Types

Ord CULLong Source #

Instance details

Defined in Foreign.C.Types

Ord CLLong Source #

Instance details

Defined in Foreign.C.Types

Ord CULong Source #

Instance details

Defined in Foreign.C.Types

Ord CLong Source #

Instance details

Defined in Foreign.C.Types

Ord CUInt Source #

Instance details

Defined in Foreign.C.Types

Ord CInt Source #

Instance details

Defined in Foreign.C.Types

Ord CUShort Source #

Instance details

Defined in Foreign.C.Types

Ord CShort Source #

Instance details

Defined in Foreign.C.Types

Ord CUChar Source #

Instance details

Defined in Foreign.C.Types

Ord CSChar Source #

Instance details

Defined in Foreign.C.Types

Ord CChar Source #

Instance details

Defined in Foreign.C.Types

Ord SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

Ord SomeSymbol Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeLits

Ord DecidedStrictness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord SourceStrictness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord SourceUnpackedness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord Associativity Source #

Since: 4.6.0.0

Instance details

Defined in GHC.Generics

Ord Fixity Source #

Since: 4.6.0.0

Instance details

Defined in GHC.Generics

Ord Any Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Ord All Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Ord ArithException Source #

Since: 3.0

Instance details

Defined in GHC.Exception.Type

Ord ErrorCall Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Exception

Ord SeekMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Device

Ord NewlineMode Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord Newline Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord BufferMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord ExitCode Source #

Instance details

Defined in GHC.IO.Exception

Ord ArrayException Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord AsyncException Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord Fd Source #

Instance details

Defined in System.Posix.Types

Ord CTimer Source #

Instance details

Defined in System.Posix.Types

Ord CKey Source #

Instance details

Defined in System.Posix.Types

Ord CId Source #

Instance details

Defined in System.Posix.Types

Ord CFsFilCnt Source #

Instance details

Defined in System.Posix.Types

Ord CFsBlkCnt Source #

Instance details

Defined in System.Posix.Types

Ord CClockId Source #

Instance details

Defined in System.Posix.Types

Ord CBlkCnt Source #

Instance details

Defined in System.Posix.Types

Ord CBlkSize Source #

Instance details

Defined in System.Posix.Types

Ord CRLim Source #

Instance details

Defined in System.Posix.Types

Ord CTcflag Source #

Instance details

Defined in System.Posix.Types

Ord CSpeed Source #

Instance details

Defined in System.Posix.Types

Ord CCc Source #

Instance details

Defined in System.Posix.Types

Ord CUid Source #

Instance details

Defined in System.Posix.Types

Ord CNlink Source #

Instance details

Defined in System.Posix.Types

Ord CGid Source #

Instance details

Defined in System.Posix.Types

Ord CSsize Source #

Instance details

Defined in System.Posix.Types

Ord CPid Source #

Instance details

Defined in System.Posix.Types

Ord COff Source #

Instance details

Defined in System.Posix.Types

Ord CMode Source #

Instance details

Defined in System.Posix.Types

Ord CIno Source #

Instance details

Defined in System.Posix.Types

Ord CDev Source #

Instance details

Defined in System.Posix.Types

Ord ThreadStatus Source #

Since: 4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord BlockReason Source #

Since: 4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadId Source #

Since: 4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord Version Source #

Since: 2.1

Instance details

Defined in Data.Version

Ord ByteOrder Source #

Since: 4.11.0.0

Instance details

Defined in GHC.ByteOrder

Ord Unique Source #

Instance details

Defined in Data.Unique

Ord Void Source #

Since: 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 #

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

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

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

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

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

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

Ord a => Ord (Maybe a) Source #

Since: 2.1

Instance details

Defined in GHC.Maybe

Integral a => Ord (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Ord (Ptr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Ord (FunPtr a) Source #

Instance details

Defined in GHC.Ptr

Ord p => Ord (Par1 p) Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Ord a => Ord (NonEmpty a) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Base

Ord a => Ord (Down a) Source #

Since: 4.6.0.0

Instance details

Defined in Data.Ord

Ord a => Ord (Product a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord (Sum a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord (Dual a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord (Last a) Source #

Since: 2.1

Instance details

Defined in Data.Monoid

Ord a => Ord (First a) Source #

Since: 2.1

Instance details

Defined in Data.Monoid

Ord (ForeignPtr a) Source #

Since: 2.1

Instance details

Defined in GHC.ForeignPtr

Ord a => Ord (Identity a) Source #

Since: 4.8.0.0

Instance details

Defined in Data.Functor.Identity

Ord a => Ord (ZipList a) Source #

Since: 4.7.0.0

Instance details

Defined in Control.Applicative

Ord a => Ord (Option a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord m => Ord (WrappedMonoid m) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord (Last a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord (First a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord (Max a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord (Min a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Ord (Fixed a) Source #

Since: 2.1

Instance details

Defined in Data.Fixed

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

Since: 2.1

Instance details

Defined in Data.Either

Ord (V1 p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord (U1 p) Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Ord (TypeRep a) Source #

Since: 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 #

(<) :: (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 s) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Proxy

Ord a => Ord (Arg a b) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Ord (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord (URec Float p) Source #

Instance details

Defined in GHC.Generics

Ord (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Ord (URec (Ptr ()) p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

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

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

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Ord (Coercion a b) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Type.Coercion

Ord (f a) => Ord (Alt f a) Source #

Since: 4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Ord (f a) => Ord (Ap f a) Source #

Since: 4.12.0.0

Instance details

Defined in Data.Monoid

Ord a => Ord (Const a b) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Const

Ord c => Ord (K1 i c p) Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

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

(<) :: (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 :~~: b) Source #

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

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

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Sum

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

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Product

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

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

(<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

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

(>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Compose

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

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

Instance details

Defined in GHC.Classes

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)

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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