linear-base-0.3.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Ord.Linear

Synopsis

Documentation

class Eq a => Ord a where Source #

Linear Orderings

Linear orderings provide a strict order. The laws for (<=) for all \(a,b,c\):

  • reflexivity: \(a \leq a \)
  • antisymmetry: \((a \leq b) \land (b \leq a) \rightarrow (a = b) \)
  • transitivity: \((a \leq b) \land (b \leq c) \rightarrow (a \leq c) \)

and these "agree" with <:

  • x <= y = not (y > x)
  • x >= y = not (y < x)

Unlike in the non-linear setting, a linear compare doesn't follow from <= since it requires calls: one to <= and one to ==. However, from a linear compare it is easy to implement the others. Hence, the minimal complete definition only contains compare.

Minimal complete definition

compare

Methods

compare :: a %1 -> a %1 -> Ordering infix 4 Source #

compare x y returns an Ordering which is one of GT (greater than), EQ (equal), or LT (less than) which should be understood as "x is (compare x y) y".

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

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

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

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

Instances

Instances details
Ord Int16 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Int16 %1 -> Int16 %1 -> Ordering Source #

(<=) :: Int16 %1 -> Int16 %1 -> Bool Source #

(<) :: Int16 %1 -> Int16 %1 -> Bool Source #

(>) :: Int16 %1 -> Int16 %1 -> Bool Source #

(>=) :: Int16 %1 -> Int16 %1 -> Bool Source #

Ord Int32 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Int32 %1 -> Int32 %1 -> Ordering Source #

(<=) :: Int32 %1 -> Int32 %1 -> Bool Source #

(<) :: Int32 %1 -> Int32 %1 -> Bool Source #

(>) :: Int32 %1 -> Int32 %1 -> Bool Source #

(>=) :: Int32 %1 -> Int32 %1 -> Bool Source #

Ord Int64 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Int64 %1 -> Int64 %1 -> Ordering Source #

(<=) :: Int64 %1 -> Int64 %1 -> Bool Source #

(<) :: Int64 %1 -> Int64 %1 -> Bool Source #

(>) :: Int64 %1 -> Int64 %1 -> Bool Source #

(>=) :: Int64 %1 -> Int64 %1 -> Bool Source #

Ord Int8 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Int8 %1 -> Int8 %1 -> Ordering Source #

(<=) :: Int8 %1 -> Int8 %1 -> Bool Source #

(<) :: Int8 %1 -> Int8 %1 -> Bool Source #

(>) :: Int8 %1 -> Int8 %1 -> Bool Source #

(>=) :: Int8 %1 -> Int8 %1 -> Bool Source #

Ord Word16 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Word16 %1 -> Word16 %1 -> Ordering Source #

(<=) :: Word16 %1 -> Word16 %1 -> Bool Source #

(<) :: Word16 %1 -> Word16 %1 -> Bool Source #

(>) :: Word16 %1 -> Word16 %1 -> Bool Source #

(>=) :: Word16 %1 -> Word16 %1 -> Bool Source #

Ord Word32 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Word32 %1 -> Word32 %1 -> Ordering Source #

(<=) :: Word32 %1 -> Word32 %1 -> Bool Source #

(<) :: Word32 %1 -> Word32 %1 -> Bool Source #

(>) :: Word32 %1 -> Word32 %1 -> Bool Source #

(>=) :: Word32 %1 -> Word32 %1 -> Bool Source #

Ord Word64 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Word64 %1 -> Word64 %1 -> Ordering Source #

(<=) :: Word64 %1 -> Word64 %1 -> Bool Source #

(<) :: Word64 %1 -> Word64 %1 -> Bool Source #

(>) :: Word64 %1 -> Word64 %1 -> Bool Source #

(>=) :: Word64 %1 -> Word64 %1 -> Bool Source #

Ord Word8 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Word8 %1 -> Word8 %1 -> Ordering Source #

(<=) :: Word8 %1 -> Word8 %1 -> Bool Source #

(<) :: Word8 %1 -> Word8 %1 -> Bool Source #

(>) :: Word8 %1 -> Word8 %1 -> Bool Source #

(>=) :: Word8 %1 -> Word8 %1 -> Bool Source #

Ord Ordering Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Ordering %1 -> Ordering %1 -> Ordering Source #

(<=) :: Ordering %1 -> Ordering %1 -> Bool Source #

(<) :: Ordering %1 -> Ordering %1 -> Bool Source #

(>) :: Ordering %1 -> Ordering %1 -> Bool Source #

(>=) :: Ordering %1 -> Ordering %1 -> Bool Source #

Ord () Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

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

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

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

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

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

Ord Bool Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Bool %1 -> Bool %1 -> Ordering Source #

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

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

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

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

Ord Char Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Char %1 -> Char %1 -> Ordering Source #

(<=) :: Char %1 -> Char %1 -> Bool Source #

(<) :: Char %1 -> Char %1 -> Bool Source #

(>) :: Char %1 -> Char %1 -> Bool Source #

(>=) :: Char %1 -> Char %1 -> Bool Source #

Ord Double Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Double %1 -> Double %1 -> Ordering Source #

(<=) :: Double %1 -> Double %1 -> Bool Source #

(<) :: Double %1 -> Double %1 -> Bool Source #

(>) :: Double %1 -> Double %1 -> Bool Source #

(>=) :: Double %1 -> Double %1 -> Bool Source #

Ord Int Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Int %1 -> Int %1 -> Ordering Source #

(<=) :: Int %1 -> Int %1 -> Bool Source #

(<) :: Int %1 -> Int %1 -> Bool Source #

(>) :: Int %1 -> Int %1 -> Bool Source #

(>=) :: Int %1 -> Int %1 -> Bool Source #

Ord a => Ord (Ur a) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Ur a %1 -> Ur a %1 -> Ordering Source #

(<=) :: Ur a %1 -> Ur a %1 -> Bool Source #

(<) :: Ur a %1 -> Ur a %1 -> Bool Source #

(>) :: Ur a %1 -> Ur a %1 -> Bool Source #

(>=) :: Ur a %1 -> Ur a %1 -> Bool Source #

(Consumable a, Ord a) => Ord (Maybe a) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Maybe a %1 -> Maybe a %1 -> Ordering Source #

(<=) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(<) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(>) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(>=) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(Consumable a, Ord a) => Ord [a] Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: [a] %1 -> [a] %1 -> Ordering Source #

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

(<) :: [a] %1 -> [a] %1 -> Bool Source #

(>) :: [a] %1 -> [a] %1 -> Bool Source #

(>=) :: [a] %1 -> [a] %1 -> Bool Source #

(Consumable a, Consumable b, Ord a, Ord b) => Ord (Either a b) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Either a b %1 -> Either a b %1 -> Ordering Source #

(<=) :: Either a b %1 -> Either a b %1 -> Bool Source #

(<) :: Either a b %1 -> Either a b %1 -> Bool Source #

(>) :: Either a b %1 -> Either a b %1 -> Bool Source #

(>=) :: Either a b %1 -> Either a b %1 -> Bool Source #

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

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: (a, b) %1 -> (a, b) %1 -> Ordering Source #

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

(<) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(>) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(>=) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(Ord a, Ord b, Ord c) => Ord (a, b, c) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

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

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

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

(>) :: (a, b, c) %1 -> (a, b, c) %1 -> Bool Source #

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

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Ordering Source #

(<=) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

(<) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

(>) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

(>=) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

data Ordering #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Bounded Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Ix Ordering

Since: base-2.1

Instance details

Defined in GHC.Ix

Read Ordering

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Eq Ordering 
Instance details

Defined in GHC.Classes

Ord Ordering 
Instance details

Defined in GHC.Classes

Hashable Ordering 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Monoid Ordering Source # 
Instance details

Defined in Data.Monoid.Linear.Internal.Monoid

Semigroup Ordering Source # 
Instance details

Defined in Data.Monoid.Linear.Internal.Semigroup

Methods

(<>) :: Ordering %1 -> Ordering %1 -> Ordering Source #

Eq Ordering Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Ordering %1 -> Ordering %1 -> Bool Source #

(/=) :: Ordering %1 -> Ordering %1 -> Bool Source #

Ord Ordering Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Ord

Methods

compare :: Ordering %1 -> Ordering %1 -> Ordering Source #

(<=) :: Ordering %1 -> Ordering %1 -> Bool Source #

(<) :: Ordering %1 -> Ordering %1 -> Bool Source #

(>) :: Ordering %1 -> Ordering %1 -> Bool Source #

(>=) :: Ordering %1 -> Ordering %1 -> Bool Source #

Consumable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Linear.Internal.Consumable

Methods

consume :: Ordering %1 -> () Source #

Dupable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Linear.Internal.Dupable

Movable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Linear.Internal.Movable

Methods

move :: Ordering %1 -> Ur Ordering Source #

type Rep Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))
type Rep Ordering 
Instance details

Defined in Generics.Linear.Instances.Base

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

min :: (Dupable a, Ord a) => a %1 -> a %1 -> a Source #

min x y returns the smaller input, or y in case of a tie.

max :: (Dupable a, Ord a) => a %1 -> a %1 -> a Source #

max x y returns the larger input, or y in case of a tie.

class Eq a where Source #

Testing equality on values.

The laws are that (==) and (/=) are compatible and (==) is an equivalence relation. So, for all x, y, z,

  • x == x always
  • x == y implies y == x
  • x == y and y == z implies x == z
  • (x == y)not (x /= y)

Minimal complete definition

(==) | (/=)

Methods

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

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

Instances

Instances details
Eq Int16 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int16 %1 -> Int16 %1 -> Bool Source #

(/=) :: Int16 %1 -> Int16 %1 -> Bool Source #

Eq Int32 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int32 %1 -> Int32 %1 -> Bool Source #

(/=) :: Int32 %1 -> Int32 %1 -> Bool Source #

Eq Int64 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int64 %1 -> Int64 %1 -> Bool Source #

(/=) :: Int64 %1 -> Int64 %1 -> Bool Source #

Eq Int8 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int8 %1 -> Int8 %1 -> Bool Source #

(/=) :: Int8 %1 -> Int8 %1 -> Bool Source #

Eq Word16 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Word16 %1 -> Word16 %1 -> Bool Source #

(/=) :: Word16 %1 -> Word16 %1 -> Bool Source #

Eq Word32 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Word32 %1 -> Word32 %1 -> Bool Source #

(/=) :: Word32 %1 -> Word32 %1 -> Bool Source #

Eq Word64 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Word64 %1 -> Word64 %1 -> Bool Source #

(/=) :: Word64 %1 -> Word64 %1 -> Bool Source #

Eq Word8 Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Word8 %1 -> Word8 %1 -> Bool Source #

(/=) :: Word8 %1 -> Word8 %1 -> Bool Source #

Eq Ordering Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Ordering %1 -> Ordering %1 -> Bool Source #

(/=) :: Ordering %1 -> Ordering %1 -> Bool Source #

Eq () Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

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

(/=) :: () %1 -> () %1 -> Bool Source #

Eq Bool Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

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

(/=) :: Bool %1 -> Bool %1 -> Bool Source #

Eq Char Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Char %1 -> Char %1 -> Bool Source #

(/=) :: Char %1 -> Char %1 -> Bool Source #

Eq Double Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Double %1 -> Double %1 -> Bool Source #

(/=) :: Double %1 -> Double %1 -> Bool Source #

Eq Int Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int %1 -> Int %1 -> Bool Source #

(/=) :: Int %1 -> Int %1 -> Bool Source #

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

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Ur a %1 -> Ur a %1 -> Bool Source #

(/=) :: Ur a %1 -> Ur a %1 -> Bool Source #

(Consumable a, Eq a) => Eq (Maybe a) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(/=) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(Consumable a, Eq a) => Eq [a] Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: [a] %1 -> [a] %1 -> Bool Source #

(/=) :: [a] %1 -> [a] %1 -> Bool Source #

(Consumable a, Consumable b, Eq a, Eq b) => Eq (Either a b) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Either a b %1 -> Either a b %1 -> Bool Source #

(/=) :: Either a b %1 -> Either a b %1 -> Bool Source #

(Eq a, Eq b) => Eq (a, b) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(/=) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(Eq a, Eq b, Eq c) => Eq (a, b, c) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

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

(/=) :: (a, b, c) %1 -> (a, b, c) %1 -> Bool Source #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

(/=) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #