lattices-1.5.0: Fine-grained library for constructing and manipulating lattices

Copyright(C) 2010-2015 Maximilian Bolingbroke, 2015 Oleg Grenrus
LicenseBSD-3-Clause (see the file LICENSE)
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellSafe
LanguageHaskell2010

Algebra.Lattice.Op

Description

 

Synopsis

Documentation

newtype Op a Source

The opposite lattice of a given lattice. That is, switch meets and joins.

Constructors

Op 

Fields

Instances

Monad Op Source 

Methods

(>>=) :: Op a -> (a -> Op b) -> Op b

(>>) :: Op a -> Op b -> Op b

return :: a -> Op a

fail :: String -> Op a

Functor Op Source 

Methods

fmap :: (a -> b) -> Op a -> Op b

(<$) :: a -> Op b -> Op a

Applicative Op Source 

Methods

pure :: a -> Op a

(<*>) :: Op (a -> b) -> Op a -> Op b

(*>) :: Op a -> Op b -> Op b

(<*) :: Op a -> Op b -> Op a

Foldable Op Source 

Methods

fold :: Monoid m => Op m -> m

foldMap :: Monoid m => (a -> m) -> Op a -> m

foldr :: (a -> b -> b) -> b -> Op a -> b

foldr' :: (a -> b -> b) -> b -> Op a -> b

foldl :: (b -> a -> b) -> b -> Op a -> b

foldl' :: (b -> a -> b) -> b -> Op a -> b

foldr1 :: (a -> a -> a) -> Op a -> a

foldl1 :: (a -> a -> a) -> Op a -> a

toList :: Op a -> [a]

null :: Op a -> Bool

length :: Op a -> Int

elem :: Eq a => a -> Op a -> Bool

maximum :: Ord a => Op a -> a

minimum :: Ord a => Op a -> a

sum :: Num a => Op a -> a

product :: Num a => Op a -> a

Traversable Op Source 

Methods

traverse :: Applicative f => (a -> f b) -> Op a -> f (Op b)

sequenceA :: Applicative f => Op (f a) -> f (Op a)

mapM :: Monad m => (a -> m b) -> Op a -> m (Op b)

sequence :: Monad m => Op (m a) -> m (Op a)

Generic1 Op Source 

Associated Types

type Rep1 (Op :: * -> *) :: * -> *

Methods

from1 :: Op a -> Rep1 Op a

to1 :: Rep1 Op a -> Op a

Eq a => Eq (Op a) Source 

Methods

(==) :: Op a -> Op a -> Bool

(/=) :: Op a -> Op a -> Bool

Data a => Data (Op a) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op a -> c (Op a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Op a)

toConstr :: Op a -> Constr

dataTypeOf :: Op a -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Op a))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Op a))

gmapT :: (forall b. Data b => b -> b) -> Op a -> Op a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op a -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op a -> r

gmapQ :: (forall d. Data d => d -> u) -> Op a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op a -> m (Op a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op a -> m (Op a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op a -> m (Op a)

Ord a => Ord (Op a) Source 

Methods

compare :: Op a -> Op a -> Ordering

(<) :: Op a -> Op a -> Bool

(<=) :: Op a -> Op a -> Bool

(>) :: Op a -> Op a -> Bool

(>=) :: Op a -> Op a -> Bool

max :: Op a -> Op a -> Op a

min :: Op a -> Op a -> Op a

Read a => Read (Op a) Source 
Show a => Show (Op a) Source 

Methods

showsPrec :: Int -> Op a -> ShowS

show :: Op a -> String

showList :: [Op a] -> ShowS

Generic (Op a) Source 

Associated Types

type Rep (Op a) :: * -> *

Methods

from :: Op a -> Rep (Op a) x

to :: Rep (Op a) x -> Op a

NFData a => NFData (Op a) Source 

Methods

rnf :: Op a -> ()

Hashable a => Hashable (Op a) Source 

Methods

hashWithSalt :: Int -> Op a -> Int

hash :: Op a -> Int

PartialOrd a => PartialOrd (Op a) Source 

Methods

leq :: Op a -> Op a -> Bool Source

(BoundedLattice a, Ord a, Bounded a) => BoundedLattice (Op a) Source 
BoundedJoinSemiLattice a => BoundedMeetSemiLattice (Op a) Source 

Methods

top :: Op a Source

BoundedMeetSemiLattice a => BoundedJoinSemiLattice (Op a) Source 

Methods

bottom :: Op a Source

(Lattice a, Ord a) => Lattice (Op a) Source 
JoinSemiLattice a => MeetSemiLattice (Op a) Source 

Methods

(/\) :: Op a -> Op a -> Op a Source

meet :: Op a -> Op a -> Op a Source

MeetSemiLattice a => JoinSemiLattice (Op a) Source 

Methods

(\/) :: Op a -> Op a -> Op a Source

join :: Op a -> Op a -> Op a Source

type Rep1 Op Source 
type Rep (Op a) Source