semilattices-0.0.0.0: Semilattices

Safe HaskellNone
LanguageHaskell2010

Data.Semilattice.Upper

Description

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

Synopsis

Documentation

class Upper s where Source #

The least upper bound of s.

Laws:

If s is Bounded, we require upperBound and maxBound to agree:

upperBound = maxBound

If s is a Meet semilattice, upperBound must be the identity of /\:

upperBound \/ a = a

If s is a Join semilattice, upperBound must be the absorbing element of \/:

upperBound \/ a = upperBound

If s is Ordered, upperBound must be at least as large as every terminating value:

compare upperBound a /= LT

Instances

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

Methods

upperBound :: () Source #

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

Methods

upperBound :: Fd Source #

Upper All Source # 
Upper Any Source # 
Upper Associativity Source # 
Upper SourceUnpackedness Source # 
Upper SourceStrictness Source # 
Upper DecidedStrictness Source # 
Upper CChar Source # 
Upper CSChar Source # 
Upper CUChar Source # 
Upper CShort Source # 
Upper CUShort Source # 
Upper CInt Source # 
Upper CUInt Source # 
Upper CLong Source # 
Upper CULong Source # 
Upper CLLong Source # 
Upper CULLong Source # 
Upper CBool Source # 
Upper CPtrdiff Source # 
Upper CSize Source # 
Upper CWchar Source # 
Upper CSigAtomic Source # 
Upper CIntPtr Source # 
Upper CUIntPtr Source # 
Upper CIntMax Source # 
Upper CUIntMax Source # 
Upper WordPtr Source # 
Upper IntPtr Source # 
Upper GeneralCategory Source # 
Upper a => Upper (Min a) Source # 

Methods

upperBound :: Min a Source #

Upper a => Upper (Max a) Source # 

Methods

upperBound :: Max a Source #

Upper a => Upper (First a) Source # 

Methods

upperBound :: First a Source #

Upper a => Upper (Last a) Source # 

Methods

upperBound :: Last a Source #

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

Methods

upperBound :: Dual a Source #

Upper a => Upper (Sum a) Source # 

Methods

upperBound :: Sum a Source #

Upper a => Upper (Product a) Source # 
Upper a => Upper (Meeting a) Source # 
Lower a => Upper (Tumble a) Source # 
Upper a => Upper (Order a) Source # 

Methods

upperBound :: Order a Source #

Bounded a => Upper (Bound a) Source # 

Methods

upperBound :: Bound a Source #

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

Methods

upperBound :: a -> b Source #

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

Methods

upperBound :: (a, b) Source #

Upper (Proxy k a) Source # 

Methods

upperBound :: Proxy k a Source #

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

Methods

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

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

Methods

upperBound :: Const k a b Source #

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

Methods

upperBound :: Coercion k a b Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Bounded:

upperBound == (maxBound :: Bool)

Identity of /\:

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

Absorbing element of \/:

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

Ord:

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