numhask-0.8.1.0: A numeric class hierarchy.
Safe HaskellNone
LanguageHaskell2010

NumHask.Algebra.Lattice

Description

Synopsis

Documentation

class Eq a => JoinSemiLattice a where Source #

A algebraic structure with element joins: See Semilattice

Associativity: x \/ (y \/ z) == (x \/ y) \/ z
Commutativity: x \/ y == y \/ x
Idempotency:   x \/ x == x

Methods

(\/) :: a -> a -> a infixr 5 Source #

Instances

Instances details
JoinSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Integer Source # 
Instance details

Defined in NumHask.Algebra.Lattice

JoinSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

JoinSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

JoinSemiLattice a => JoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

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

(Ord a, Signed a) => JoinSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

(Eq (a -> b), JoinSemiLattice b) => JoinSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

joinLeq :: JoinSemiLattice a => a -> a -> Bool Source #

The partial ordering induced by the join-semilattice structure

class Eq a => MeetSemiLattice a where Source #

A algebraic structure with element meets: See Semilattice

Associativity: x /\ (y /\ z) == (x /\ y) /\ z
Commutativity: x /\ y == y /\ x
Idempotency:   x /\ x == x

Methods

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

Instances

Instances details
MeetSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Integer Source # 
Instance details

Defined in NumHask.Algebra.Lattice

MeetSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

MeetSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

MeetSemiLattice a => MeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

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

(Ord a, Signed a) => MeetSemiLattice (Ratio a) Source # 
Instance details

Defined in NumHask.Data.Rational

Methods

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

(Eq (a -> b), MeetSemiLattice b) => MeetSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

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

meetLeq :: MeetSemiLattice a => a -> a -> Bool Source #

The partial ordering induced by the meet-semilattice structure

class JoinSemiLattice a => BoundedJoinSemiLattice a where Source #

A join-semilattice with an identity element bottom for \/.

Identity: x \/ bottom == x

Methods

bottom :: a Source #

Instances

Instances details
BoundedJoinSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Bool Source #

BoundedJoinSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Double Source #

BoundedJoinSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Float Source #

BoundedJoinSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int Source #

BoundedJoinSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int8 Source #

BoundedJoinSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int16 Source #

BoundedJoinSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int32 Source #

BoundedJoinSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Int64 Source #

BoundedJoinSemiLattice Natural Source # 
Instance details

Defined in NumHask.Algebra.Lattice

BoundedJoinSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word Source #

BoundedJoinSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word8 Source #

BoundedJoinSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word16 Source #

BoundedJoinSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word32 Source #

BoundedJoinSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: Word64 Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

bottom :: Complex a Source #

(Eq (a -> b), BoundedJoinSemiLattice b) => BoundedJoinSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

bottom :: a -> b Source #

class MeetSemiLattice a => BoundedMeetSemiLattice a where Source #

A meet-semilattice with an identity element top for /\.

Identity: x /\ top == x

Methods

top :: a Source #

Instances

Instances details
BoundedMeetSemiLattice Bool Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Bool Source #

BoundedMeetSemiLattice Double Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Double Source #

BoundedMeetSemiLattice Float Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Float Source #

BoundedMeetSemiLattice Int Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int Source #

BoundedMeetSemiLattice Int8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int8 Source #

BoundedMeetSemiLattice Int16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int16 Source #

BoundedMeetSemiLattice Int32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int32 Source #

BoundedMeetSemiLattice Int64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Int64 Source #

BoundedMeetSemiLattice Word Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word Source #

BoundedMeetSemiLattice Word8 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word8 Source #

BoundedMeetSemiLattice Word16 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word16 Source #

BoundedMeetSemiLattice Word32 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word32 Source #

BoundedMeetSemiLattice Word64 Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: Word64 Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Complex a) Source # 
Instance details

Defined in NumHask.Data.Complex

Methods

top :: Complex a Source #

(Eq (a -> b), BoundedMeetSemiLattice b) => BoundedMeetSemiLattice (a -> b) Source # 
Instance details

Defined in NumHask.Algebra.Lattice

Methods

top :: a -> b Source #