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

Data.Ord.Linear.Internal.Ord

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

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

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, 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
Bounded Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Ordering 
Instance details

Defined in GHC.Classes

Ord Ordering 
Instance details

Defined in GHC.Classes

Read Ordering

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Ordering

Since: base-2.1

Instance details

Defined in GHC.Ix

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 #

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Hashable Ordering 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Consumable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

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

Semigroup Ordering Source # 
Instance details

Defined in Data.Monoid.Linear.Internal.Semigroup

Methods

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

Monoid Ordering Source # 
Instance details

Defined in Data.Monoid.Linear.Internal.Monoid

Dupable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

dupV :: forall (n :: Nat). KnownNat n => Ordering %1 -> V n Ordering Source #

dup2 :: Ordering %1 -> (Ordering, Ordering) Source #

Movable Ordering Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

move :: Ordering %1 -> Ur 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 #

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

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.