semilattices-0.0.0.1: Semilattices

Safe HaskellNone
LanguageHaskell2010

Data.Semilattice.Join

Description

Join semilattices, related to Lower and Upper.

Synopsis

Documentation

class Join s where Source #

A join semilattice is an idempotent commutative semigroup.

Minimal complete definition

(\/)

Methods

(\/) :: s -> s -> s infixr 6 Source #

The join operation.

Laws:

Idempotence:

x \/ x = x

Associativity:

a \/ (b \/ c) = (a \/ b) \/ c

Commutativity:

a \/ b = b \/ a

Additionally, if s has a Lower bound, then lowerBound must be its identity:

lowerBound \/ a = a
a \/ lowerBound = a

If s has an Upper bound, then upperBound must be its absorbing element:

upperBound \/ a = upperBound
a \/ upperBound = upperBound

Instances

Join Bool Source #

Boolean disjunction forms a semilattice.

Idempotence:

x \/ x == (x :: Bool)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: Bool)

Commutativity:

a \/ b == b \/ (a :: Bool)

Identity:

lowerBound \/ a == (a :: Bool)

Absorption:

upperBound \/ a == (upperBound :: Bool)

Methods

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

Join Ordering Source #

Orderings form a semilattice.

Idempotence:

x \/ x == (x :: Ordering)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: Ordering)

Commutativity:

a \/ b == b \/ (a :: Ordering)

Identity:

lowerBound \/ a == (a :: Ordering)

Absorption:

upperBound \/ a == (upperBound :: Ordering)
Join () Source # 

Methods

(\/) :: () -> () -> () Source #

Join IntSet Source #

IntSet union forms a semilattice.

Idempotence:

x \/ x == (x :: IntSet)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: IntSet)

Commutativity:

a \/ b == b \/ (a :: IntSet)

Identity:

lowerBound \/ a == (a :: IntSet)

Methods

(\/) :: IntSet -> IntSet -> IntSet Source #

Ord a => Join (Max a) Source #

The least upperBound bound gives rise to a join semilattice.

Idempotence:

x \/ x == (x :: Max Int)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: Max Int)

Commutativity:

a \/ b == b \/ (a :: Max Int)

Identity:

lowerBound \/ a == (a :: Max Int)

Absorption:

upperBound \/ a == (upperBound :: Max Int)

Methods

(\/) :: Max a -> Max a -> Max a Source #

Join a => Join (IntMap a) Source #

IntMap union with Joinable values forms a semilattice.

Idempotence:

x \/ x == (x :: IntMap (Set Char))

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: IntMap (Set Char))

Commutativity:

a \/ b == b \/ (a :: IntMap (Set Char))

Identity:

lowerBound \/ a == (a :: IntMap (Set Char))

Methods

(\/) :: IntMap a -> IntMap a -> IntMap a Source #

Ord a => Join (Set a) Source #

Set union forms a semilattice.

Idempotence:

x \/ x == (x :: Set Char)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: Set Char)

Commutativity:

a \/ b == b \/ (a :: Set Char)

Identity:

lowerBound \/ a == (a :: Set Char)

Methods

(\/) :: Set a -> Set a -> Set a Source #

(Eq a, Hashable a) => Join (HashSet a) Source #

HashSet union forms a semilattice.

Idempotence:

x \/ x == (x :: HashSet Char)

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: HashSet Char)

Commutativity:

a \/ b == b \/ (a :: HashSet Char)

Identity:

lowerBound \/ a == (a :: HashSet Char)

Methods

(\/) :: HashSet a -> HashSet a -> HashSet a Source #

Join a => Join (LessThan a) Source # 

Methods

(\/) :: LessThan a -> LessThan a -> LessThan a Source #

Join a => Join (Joining a) Source # 

Methods

(\/) :: Joining a -> Joining a -> Joining a Source #

Meet a => Join (Tumble a) Source # 

Methods

(\/) :: Tumble a -> Tumble a -> Tumble a Source #

Ord a => Join (Order a) Source #

Total Orderings give rise to a join semilattice satisfying:

Idempotence:

Order x \/ Order x == Order x

Associativity:

Order a \/ (Order b \/ Order c) == (Order a \/ Order b) \/ Order c

Commutativity:

Order a \/ Order b == Order b \/ Order a

Identity:

lowerBound \/ Order a == Order (a :: Int)

Absorption:

upperBound \/ Order a == (upperBound :: Order Int)

Distributivity:

Order a \/ Order b /\ Order c == (Order a \/ Order b) /\ (Order a \/ Order c)

Methods

(\/) :: Order a -> Order a -> Order a Source #

Join b => Join (a -> b) Source #

Functions with semilattice codomains form a semilattice.

Idempotence:

\ (Fn x) -> x \/ x ~= (x :: Int -> Bool)

Associativity:

\ (Fn a) (Fn b) (Fn c) -> a \/ (b \/ c) ~= (a \/ b) \/ (c :: Int -> Bool)

Commutativity:

\ (Fn a) (Fn b) -> a \/ b ~= b \/ (a :: Int -> Bool)

Identity:

\ (Fn a) -> lowerBound \/ a ~= (a :: Int -> Bool)

Absorption:

\ (Fn a) -> upperBound \/ a ~= (upperBound :: Int -> Bool)

Methods

(\/) :: (a -> b) -> (a -> b) -> a -> b Source #

(Ord k, Join a) => Join (Map k a) Source #

Map union with Joinable values forms a semilattice.

Idempotence:

x \/ x == (x :: Map Char (Set Char))

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: Map Char (Set Char))

Commutativity:

a \/ b == b \/ (a :: Map Char (Set Char))

Identity:

lowerBound \/ a == (a :: Map Char (Set Char))

Methods

(\/) :: Map k a -> Map k a -> Map k a Source #

(Eq k, Hashable k, Join a) => Join (HashMap k a) Source #

HashMap union with Joinable values forms a semilattice.

Idempotence:

x \/ x == (x :: HashMap Char (Set Char))

Associativity:

a \/ (b \/ c) == (a \/ b) \/ (c :: HashMap Char (Set Char))

Commutativity:

a \/ b == b \/ (a :: HashMap Char (Set Char))

Identity:

lowerBound \/ a == (a :: HashMap Char (Set Char))

Methods

(\/) :: HashMap k a -> HashMap k a -> HashMap k a Source #

newtype Joining a Source #

A Semigroup for any Join semilattice.

If the semilattice has a Lower bound, there is additionally a Monoid instance.

Constructors

Joining 

Fields

Instances

Functor Joining Source # 

Methods

fmap :: (a -> b) -> Joining a -> Joining b #

(<$) :: a -> Joining b -> Joining a #

Foldable Joining Source # 

Methods

fold :: Monoid m => Joining m -> m #

foldMap :: Monoid m => (a -> m) -> Joining a -> m #

foldr :: (a -> b -> b) -> b -> Joining a -> b #

foldr' :: (a -> b -> b) -> b -> Joining a -> b #

foldl :: (b -> a -> b) -> b -> Joining a -> b #

foldl' :: (b -> a -> b) -> b -> Joining a -> b #

foldr1 :: (a -> a -> a) -> Joining a -> a #

foldl1 :: (a -> a -> a) -> Joining a -> a #

toList :: Joining a -> [a] #

null :: Joining a -> Bool #

length :: Joining a -> Int #

elem :: Eq a => a -> Joining a -> Bool #

maximum :: Ord a => Joining a -> a #

minimum :: Ord a => Joining a -> a #

sum :: Num a => Joining a -> a #

product :: Num a => Joining a -> a #

Traversable Joining Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Joining a -> f (Joining b) #

sequenceA :: Applicative f => Joining (f a) -> f (Joining a) #

mapM :: Monad m => (a -> m b) -> Joining a -> m (Joining b) #

sequence :: Monad m => Joining (m a) -> m (Joining a) #

Bounded a => Bounded (Joining a) Source # 
Enum a => Enum (Joining a) Source # 

Methods

succ :: Joining a -> Joining a #

pred :: Joining a -> Joining a #

toEnum :: Int -> Joining a #

fromEnum :: Joining a -> Int #

enumFrom :: Joining a -> [Joining a] #

enumFromThen :: Joining a -> Joining a -> [Joining a] #

enumFromTo :: Joining a -> Joining a -> [Joining a] #

enumFromThenTo :: Joining a -> Joining a -> Joining a -> [Joining a] #

Eq a => Eq (Joining a) Source # 

Methods

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

(/=) :: Joining a -> Joining a -> Bool #

Num a => Num (Joining a) Source # 

Methods

(+) :: Joining a -> Joining a -> Joining a #

(-) :: Joining a -> Joining a -> Joining a #

(*) :: Joining a -> Joining a -> Joining a #

negate :: Joining a -> Joining a #

abs :: Joining a -> Joining a #

signum :: Joining a -> Joining a #

fromInteger :: Integer -> Joining a #

Ord a => Ord (Joining a) Source # 

Methods

compare :: Joining a -> Joining a -> Ordering #

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

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

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

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

max :: Joining a -> Joining a -> Joining a #

min :: Joining a -> Joining a -> Joining a #

Read a => Read (Joining a) Source # 
Show a => Show (Joining a) Source # 

Methods

showsPrec :: Int -> Joining a -> ShowS #

show :: Joining a -> String #

showList :: [Joining a] -> ShowS #

Join a => Semigroup (Joining a) Source #

Joining <> is associative.

\ a b c -> Joining a <> (Joining b <> Joining c) == (Joining a <> Joining b) <> Joining (c :: IntSet)

Methods

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

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

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

(Lower a, Join a) => Monoid (Joining a) Source #

Joining mempty is the left- and right-identity.

\ x -> let (l, r) = (mappend mempty (Joining x), mappend (Joining x) mempty) in l == Joining x && r == Joining (x :: IntSet)

Methods

mempty :: Joining a #

mappend :: Joining a -> Joining a -> Joining a #

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

Lower a => Lower (Joining a) Source # 
Join a => Join (Joining a) Source # 

Methods

(\/) :: Joining a -> Joining a -> Joining a Source #

newtype LessThan a Source #

Join semilattices give rise to a partial Ordering.

Constructors

LessThan 

Fields

Instances

Functor LessThan Source # 

Methods

fmap :: (a -> b) -> LessThan a -> LessThan b #

(<$) :: a -> LessThan b -> LessThan a #

Foldable LessThan Source # 

Methods

fold :: Monoid m => LessThan m -> m #

foldMap :: Monoid m => (a -> m) -> LessThan a -> m #

foldr :: (a -> b -> b) -> b -> LessThan a -> b #

foldr' :: (a -> b -> b) -> b -> LessThan a -> b #

foldl :: (b -> a -> b) -> b -> LessThan a -> b #

foldl' :: (b -> a -> b) -> b -> LessThan a -> b #

foldr1 :: (a -> a -> a) -> LessThan a -> a #

foldl1 :: (a -> a -> a) -> LessThan a -> a #

toList :: LessThan a -> [a] #

null :: LessThan a -> Bool #

length :: LessThan a -> Int #

elem :: Eq a => a -> LessThan a -> Bool #

maximum :: Ord a => LessThan a -> a #

minimum :: Ord a => LessThan a -> a #

sum :: Num a => LessThan a -> a #

product :: Num a => LessThan a -> a #

Traversable LessThan Source # 

Methods

traverse :: Applicative f => (a -> f b) -> LessThan a -> f (LessThan b) #

sequenceA :: Applicative f => LessThan (f a) -> f (LessThan a) #

mapM :: Monad m => (a -> m b) -> LessThan a -> m (LessThan b) #

sequence :: Monad m => LessThan (m a) -> m (LessThan a) #

Enum a => Enum (LessThan a) Source # 
Eq a => Eq (LessThan a) Source # 

Methods

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

(/=) :: LessThan a -> LessThan a -> Bool #

Num a => Num (LessThan a) Source # 
(Eq a, Join a) => Ord (LessThan a) Source # 

Methods

compare :: LessThan a -> LessThan a -> Ordering #

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

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

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

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

max :: LessThan a -> LessThan a -> LessThan a #

min :: LessThan a -> LessThan a -> LessThan a #

Read a => Read (LessThan a) Source # 
Show a => Show (LessThan a) Source # 

Methods

showsPrec :: Int -> LessThan a -> ShowS #

show :: LessThan a -> String #

showList :: [LessThan a] -> ShowS #

Join a => Join (LessThan a) Source # 

Methods

(\/) :: LessThan a -> LessThan a -> LessThan a Source #