alg-0.2.1.0: Algebraic structures

Safe HaskellNone
LanguageHaskell2010

Relation.Binary.Comparison

Documentation

class Preord a where Source #

Methods

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

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

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

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

Instances

Preord Bool Source # 

Methods

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

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

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

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

Preord Integer Source # 
Preord Natural Source # 
Preord Ordering Source # 
Preord () Source # 

Methods

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

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

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

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

Preord a => Preord (Maybe a) Source # 

Methods

(≤) :: Maybe a -> Maybe a -> Bool Source #

(≥) :: Maybe a -> Maybe a -> Bool Source #

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

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

(Preord a, Preord b) => Preord (Lexical (Either a b)) Source # 

Methods

(≤) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

(≥) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

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

(>) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

(PartialOrd a, PartialOrd b) => Preord (Lexical (a, b)) Source # 

Methods

(≤) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #

(≥) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #

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

(>) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #

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

Methods

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

(Preord a, Preord b) => Preord (a, b) Source # 

Methods

(≤) :: (a, b) -> (a, b) -> Bool Source #

(≥) :: (a, b) -> (a, b) -> Bool Source #

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

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

class PartialEq a where Source #

Methods

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

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

Instances

PartialEq Bool Source # 

Methods

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

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

PartialEq Integer Source # 
PartialEq Natural Source # 
PartialEq Ordering Source # 
PartialEq () Source # 

Methods

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

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

PartialEq a => PartialEq (Maybe a) Source # 

Methods

(≡) :: Maybe a -> Maybe a -> Bool Source #

(≢) :: Maybe a -> Maybe a -> Bool Source #

PartialEq a => PartialEq (Lexical a) Source # 

Methods

(≡) :: Lexical a -> Lexical a -> Bool Source #

(≢) :: Lexical a -> Lexical a -> Bool Source #

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

Methods

(≡) :: Either a b -> Either a b -> Bool Source #

(≢) :: Either a b -> Either a b -> Bool Source #

(PartialEq a, PartialEq b) => PartialEq (a, b) Source # 

Methods

(≡) :: (a, b) -> (a, b) -> Bool Source #

(≢) :: (a, b) -> (a, b) -> Bool Source #

class (Preord a, PartialEq a) => Eq a Source #

Instances

Eq Bool Source # 
Eq Integer Source # 
Eq Natural Source # 
Eq Ordering Source # 
Eq () Source # 
Eq a => Eq (Maybe a) Source # 
(Eq a, Eq b) => Eq (Lexical (Either a b)) Source # 
(PartialOrd a, PartialOrd b, Eq a, Eq b) => Eq (Lexical (a, b)) Source # 

class (PartialOrd a, Eq a) => Ord a where Source #

Methods

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

Instances

Ord Bool Source # 

Methods

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

Ord Integer Source # 
Ord Natural Source # 
Ord Ordering Source # 
Ord () Source # 

Methods

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

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

Methods

compare :: Lexical (Either a b) -> Lexical (Either a b) -> Ordering Source #

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

Methods

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

newtype Lexical a Source #

Constructors

Lexical a 

Instances

Semigroup a => Semigroup (Lexical a) Source # 

Methods

(<>) :: Lexical a -> Lexical a -> Lexical a #

sconcat :: NonEmpty (Lexical a) -> Lexical a #

stimes :: Integral b => b -> Lexical a -> Lexical a #

Monoid a => Monoid (Lexical a) Source # 

Methods

mempty :: Lexical a #

mappend :: Lexical a -> Lexical a -> Lexical a #

mconcat :: [Lexical a] -> Lexical a #

Group a => Group (Lexical a) Source # 

Methods

invert :: Lexical a -> Lexical a Source #

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

Methods

compare :: Lexical (Either a b) -> Lexical (Either a b) -> Ordering Source #

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

Methods

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

(PartialOrd a, PartialOrd b) => PartialOrd (Lexical (Either a b)) Source # 
(PartialOrd a, PartialOrd b) => PartialOrd (Lexical (a, b)) Source # 

Methods

tryCompare :: Lexical (a, b) -> Lexical (a, b) -> Maybe Ordering Source #

(Eq a, Eq b) => Eq (Lexical (Either a b)) Source # 
(PartialOrd a, PartialOrd b, Eq a, Eq b) => Eq (Lexical (a, b)) Source # 
PartialEq a => PartialEq (Lexical a) Source # 

Methods

(≡) :: Lexical a -> Lexical a -> Bool Source #

(≢) :: Lexical a -> Lexical a -> Bool Source #

(Preord a, Preord b) => Preord (Lexical (Either a b)) Source # 

Methods

(≤) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

(≥) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

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

(>) :: Lexical (Either a b) -> Lexical (Either a b) -> Bool Source #

(PartialOrd a, PartialOrd b) => Preord (Lexical (a, b)) Source # 

Methods

(≤) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #

(≥) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #

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

(>) :: Lexical (a, b) -> Lexical (a, b) -> Bool Source #