lattices-1.4.1: 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.Levitated

Description

 

Synopsis

Documentation

data Levitated a Source

Graft a distinct top and bottom onto an otherwise unbounded lattice. The top is the absorbing element for the join, and the bottom is the absorbing element for the meet.

Constructors

Top 
Levitate a 
Bottom 

Instances

Monad Levitated Source 

Methods

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

(>>) :: Levitated a -> Levitated b -> Levitated b

return :: a -> Levitated a

fail :: String -> Levitated a

Functor Levitated Source 

Methods

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

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

Applicative Levitated Source 

Methods

pure :: a -> Levitated a

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

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

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

Foldable Levitated Source 

Methods

fold :: Monoid m => Levitated m -> m

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

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

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

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

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

foldr1 :: (a -> a -> a) -> Levitated a -> a

foldl1 :: (a -> a -> a) -> Levitated a -> a

toList :: Levitated a -> [a]

null :: Levitated a -> Bool

length :: Levitated a -> Int

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

maximum :: Ord a => Levitated a -> a

minimum :: Ord a => Levitated a -> a

sum :: Num a => Levitated a -> a

product :: Num a => Levitated a -> a

Traversable Levitated Source 

Methods

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

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

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

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

Generic1 Levitated Source 

Associated Types

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

Eq a => Eq (Levitated a) Source 

Methods

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

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

Data a => Data (Levitated a) Source 

Methods

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

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

toConstr :: Levitated a -> Constr

dataTypeOf :: Levitated a -> DataType

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Levitated a) Source 
Read a => Read (Levitated a) Source 
Show a => Show (Levitated a) Source 
Generic (Levitated a) Source 

Associated Types

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

Methods

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

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

NFData a => NFData (Levitated a) Source 

Methods

rnf :: Levitated a -> ()

Hashable a => Hashable (Levitated a) Source 

Methods

hashWithSalt :: Int -> Levitated a -> Int

hash :: Levitated a -> Int

Lattice a => BoundedLattice (Levitated a) Source 
MeetSemiLattice a => BoundedMeetSemiLattice (Levitated a) Source 

Methods

top :: Levitated a Source

JoinSemiLattice a => BoundedJoinSemiLattice (Levitated a) Source 

Methods

bottom :: Levitated a Source

Lattice a => Lattice (Levitated a) Source 
MeetSemiLattice a => MeetSemiLattice (Levitated a) Source 
JoinSemiLattice a => JoinSemiLattice (Levitated a) Source 
type Rep1 Levitated Source 
type Rep (Levitated a) Source 

retractLevitated :: BoundedLattice a => Levitated a -> a Source

Interpret Levitated a using the BoundedLattice of a.