semilattices-0.0.0.1: Semilattices

Safe HaskellNone
LanguageHaskell2010

Data.Semilattice.Lower

Description

Lower bounds, related to Bounded, Join, Meet, and Ord.

Synopsis

Documentation

class Lower s where Source #

The greatest lower bound of s.

Laws:

If s is Bounded, we require lowerBound and minBound to agree:

lowerBound = minBound

If s is a Join semilattice, lowerBound must be the identity of \/:

lowerBound \/ a = a

If s is a Meet semilattice, lowerBound must be the absorbing element of /\:

lowerBound /\ a = lowerBound

If s is Ordered, lowerBound must be at least as small as every terminating value:

compare lowerBound a /= GT

Instances

Lower Bool Source # 
Lower Char Source # 
Lower Int Source # 
Lower Int8 Source # 
Lower Int16 Source # 
Lower Int32 Source # 
Lower Int64 Source # 
Lower Ordering Source # 
Lower Word8 Source # 
Lower Word16 Source # 
Lower Word32 Source # 
Lower Word64 Source # 
Lower () Source # 

Methods

lowerBound :: () Source #

Lower CDev Source # 
Lower CIno Source # 
Lower CMode Source # 
Lower COff Source # 
Lower CPid Source # 
Lower CSsize Source # 
Lower CGid Source # 
Lower CNlink Source # 
Lower CUid Source # 
Lower CTcflag Source # 
Lower CRLim Source # 
Lower CBlkSize Source # 
Lower CBlkCnt Source # 
Lower CClockId Source # 
Lower CFsBlkCnt Source # 
Lower CFsFilCnt Source # 
Lower CId Source # 
Lower CKey Source # 
Lower Fd Source # 

Methods

lowerBound :: Fd Source #

Lower All Source # 
Lower Any Source # 
Lower Associativity Source # 
Lower SourceUnpackedness Source # 
Lower SourceStrictness Source # 
Lower DecidedStrictness Source # 
Lower CChar Source # 
Lower CSChar Source # 
Lower CUChar Source # 
Lower CShort Source # 
Lower CUShort Source # 
Lower CInt Source # 
Lower CUInt Source # 
Lower CLong Source # 
Lower CULong Source # 
Lower CLLong Source # 
Lower CULLong Source # 
Lower CBool Source # 
Lower CPtrdiff Source # 
Lower CSize Source # 
Lower CWchar Source # 
Lower CSigAtomic Source # 
Lower CIntPtr Source # 
Lower CUIntPtr Source # 
Lower CIntMax Source # 
Lower CUIntMax Source # 
Lower WordPtr Source # 
Lower IntPtr Source # 
Lower GeneralCategory Source # 
Lower IntSet Source # 
Lower [a] Source # 

Methods

lowerBound :: [a] Source #

Lower (Maybe a) Source # 

Methods

lowerBound :: Maybe a Source #

Lower a => Lower (Min a) Source # 

Methods

lowerBound :: Min a Source #

Lower a => Lower (Max a) Source # 

Methods

lowerBound :: Max a Source #

Lower a => Lower (First a) Source # 

Methods

lowerBound :: First a Source #

Lower a => Lower (Last a) Source # 

Methods

lowerBound :: Last a Source #

Lower a => Lower (WrappedMonoid a) Source # 
Lower a => Lower (Identity a) Source # 
Lower a => Lower (Dual a) Source # 

Methods

lowerBound :: Dual a Source #

Lower (Endo a) Source # 

Methods

lowerBound :: Endo a Source #

Lower a => Lower (Sum a) Source # 

Methods

lowerBound :: Sum a Source #

Lower a => Lower (Product a) Source # 
Lower (First a) Source # 

Methods

lowerBound :: First a Source #

Lower (Last a) Source # 

Methods

lowerBound :: Last a Source #

Lower (IntMap a) Source # 
Lower (Set a) Source # 

Methods

lowerBound :: Set a Source #

Lower (HashSet a) Source # 
Lower a => Lower (Joining a) Source # 
Upper a => Lower (Tumble a) Source # 
Lower a => Lower (Order a) Source # 

Methods

lowerBound :: Order a Source #

Bounded a => Lower (Bound a) Source # 

Methods

lowerBound :: Bound a Source #

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

Methods

lowerBound :: a -> b Source #

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

Methods

lowerBound :: (a, b) Source #

Lower (Proxy k a) Source # 

Methods

lowerBound :: Proxy k a Source #

Lower (Map k a) Source # 

Methods

lowerBound :: Map k a Source #

Lower (HashMap k a) Source # 

Methods

lowerBound :: HashMap k a Source #

(Lower a, Lower b, Lower c) => Lower (a, b, c) Source # 

Methods

lowerBound :: (a, b, c) Source #

Lower a => Lower (Const k a b) Source # 

Methods

lowerBound :: Const k a b Source #

Coercible k a b => Lower (Coercion k a b) Source # 

Methods

lowerBound :: Coercion k a b Source #

(~) k a b => Lower ((:~:) k a b) Source # 

Methods

lowerBound :: (k :~: a) b Source #

(Lower a, Lower b, Lower c, Lower d) => Lower (a, b, c, d) Source # 

Methods

lowerBound :: (a, b, c, d) Source #

(~~) k1 k2 a b => Lower ((:~~:) k1 k2 a b) Source # 

Methods

lowerBound :: (k1 :~~: k2) a b Source #

(Lower a, Lower b, Lower c, Lower d, Lower e) => Lower (a, b, c, d, e) Source # 

Methods

lowerBound :: (a, b, c, d, e) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f) => Lower (a, b, c, d, e, f) Source # 

Methods

lowerBound :: (a, b, c, d, e, f) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g) => Lower (a, b, c, d, e, f, g) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h) => Lower (a, b, c, d, e, f, g, h) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i) => Lower (a, b, c, d, e, f, g, h, i) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j) => Lower (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k) => Lower (a, b, c, d, e, f, g, h, i, j, k) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j, k) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l) => Lower (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m, Lower n) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(Lower a, Lower b, Lower c, Lower d, Lower e, Lower f, Lower g, Lower h, Lower i, Lower j, Lower k, Lower l, Lower m, Lower n, Lower o) => Lower (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

lowerBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

Bounded:

lowerBound == (minBound :: Bool)

Identity of \/:

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

Absorbing element of /\:

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

Ord:

compare lowerBound (a :: Bool) /= GT
>>> import Data.Semilattice.Join
>>> import Data.Semilattice.Meet
>>> import Test.QuickCheck (Arbitrary(..))
>>> import Test.QuickCheck.Function