Safe Haskell | None |
---|---|
Language | Haskell2010 |
Join semilattices, related to Lower
and Upper
.
- class Meet s where
- newtype Meeting a = Meeting {
- getMeeting :: a
- newtype GreaterThan a = GreaterThan {
- getGreaterThan :: a
Documentation
A meet semilattice is an idempotent commutative semigroup.
(/\) :: s -> s -> s infixr 7 Source #
The meet operation.
Laws:
Idempotence:
x /\
x = x
Associativity:
a/\
(b/\
c) = (a/\
b)/\
c
Commutativity:
a/\
b = b/\
a
Additionally, if s
has an Upper
bound, then upperBound
must be its identity:
upperBound
/\
a = a a/\
upperBound
= a
If s
has a Lower
bound, then lowerBound
must be its absorbing element:
lowerBound
/\
a =lowerBound
a/\
lowerBound
=lowerBound
Meet Bool Source # | Boolean conjunction forms a semilattice. Idempotence: x /\ x == (x :: Bool) Associativity: a /\ (b /\ c) == (a /\ b) /\ (c :: Bool) Commutativity: a /\ b == b /\ (a :: Bool) Identity: upperBound /\ a == (a :: Bool) Absorption: lowerBound /\ a == (lowerBound :: Bool) |
Meet 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: upperBound /\ a == (a :: Ordering) Absorption: lowerBound /\ a == (lowerBound :: Ordering) |
Meet () Source # | |
Meet IntSet Source # | IntSet intersection forms a semilattice. Idempotence: x /\ x == (x :: IntSet) Associativity: a /\ (b /\ c) == (a /\ b) /\ (c :: IntSet) Commutativity: a /\ b == b /\ (a :: IntSet) Absorption: lowerBound /\ a == (lowerBound :: IntSet) |
Ord a => Meet (Min a) Source # | The greatest lowerBound bound gives rise to a meet semilattice. Idempotence: x /\ x == (x :: Min Int) Associativity: a /\ (b /\ c) == (a /\ b) /\ (c :: Min Int) Commutativity: a /\ b == b /\ (a :: Min Int) Identity: upperBound /\ a == (a :: Min Int) Absorption: lowerBound /\ a == (lowerBound :: Min Int) |
Meet a => Meet (IntMap a) Source # | IntMap union with 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)) Absorption: lowerBound /\ a == (lowerBound :: IntMap (Set Char)) |
Ord a => Meet (Set a) Source # | Set intersection 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) Absorption: lowerBound /\ a == (lowerBound :: Set Char) |
(Eq a, Hashable a) => Meet (HashSet a) Source # | HashSet intersection 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) Absorption: lowerBound /\ a == (lowerBound :: HashSet Char) |
Meet a => Meet (GreaterThan a) Source # | |
Meet a => Meet (Meeting a) Source # | |
Join a => Meet (Tumble a) Source # | |
Ord a => Meet (Order a) Source # | Total 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: upperBound /\ Order a == Order (a :: Int) Absorption: lowerBound /\ Order a == (lowerBound :: Order Int) Distributivity: Order a /\ (Order b \/ Order c) == Order a /\ Order b \/ Order a /\ Order c |
Meet b => Meet (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) -> upperBound /\ a ~= (a :: Int -> Bool) Absorption: \ (Fn a) -> lowerBound /\ a ~= (lowerBound :: Int -> Bool) |
(Ord k, Meet a) => Meet (Map k a) Source # | Map union with 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)) Absorption: lowerBound /\ a == (lowerBound :: Map Char (Set Char)) |
(Eq k, Hashable k, Meet a) => Meet (HashMap k a) Source # | HashMap union with 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)) Absorption: lowerBound /\ a == (lowerBound :: HashMap Char (Set Char)) |
A Semigroup
for any Meet
semilattice.
If the semilattice has an Upper
bound, there is additionally a Monoid
instance.
Meeting | |
|
Functor Meeting Source # | |
Foldable Meeting Source # | |
Traversable Meeting Source # | |
Bounded a => Bounded (Meeting a) Source # | |
Enum a => Enum (Meeting a) Source # | |
Eq a => Eq (Meeting a) Source # | |
Num a => Num (Meeting a) Source # | |
Ord a => Ord (Meeting a) Source # | |
Read a => Read (Meeting a) Source # | |
Show a => Show (Meeting a) Source # | |
Meet a => Semigroup (Meeting a) Source # | Meeting a <> (Meeting b <> Meeting c) == (Meeting a <> Meeting b) <> Meeting (c :: IntSet) |
(Upper a, Meet a) => Monoid (Meeting a) Source # |
let (l, r) = (mappend mempty (Meeting x), mappend (Meeting x) mempty) in l == Meeting x && r == Meeting (x :: Bool) |
Upper a => Upper (Meeting a) Source # | |
Meet a => Meet (Meeting a) Source # | |
newtype GreaterThan a Source #
Functor GreaterThan Source # | |
Foldable GreaterThan Source # | |
Traversable GreaterThan Source # | |
Enum a => Enum (GreaterThan a) Source # | |
Eq a => Eq (GreaterThan a) Source # | |
Num a => Num (GreaterThan a) Source # | |
(Eq a, Meet a) => Ord (GreaterThan a) Source # | |
Read a => Read (GreaterThan a) Source # | |
Show a => Show (GreaterThan a) Source # | |
Meet a => Meet (GreaterThan a) Source # | |