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

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

Algebra.Lattice.Lifted

Description

 
Synopsis

Documentation

data Lifted a Source #

Graft a distinct bottom onto an otherwise unbounded lattice. As a bonus, the bottom will be an absorbing element for the meet.

Constructors

Bottom 
Lift a 
Instances
Monad Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

(>>=) :: Lifted a -> (a -> Lifted b) -> Lifted b #

(>>) :: Lifted a -> Lifted b -> Lifted b #

return :: a -> Lifted a #

fail :: String -> Lifted a #

Functor Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

fmap :: (a -> b) -> Lifted a -> Lifted b #

(<$) :: a -> Lifted b -> Lifted a #

Applicative Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

pure :: a -> Lifted a #

(<*>) :: Lifted (a -> b) -> Lifted a -> Lifted b #

liftA2 :: (a -> b -> c) -> Lifted a -> Lifted b -> Lifted c #

(*>) :: Lifted a -> Lifted b -> Lifted b #

(<*) :: Lifted a -> Lifted b -> Lifted a #

Foldable Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

fold :: Monoid m => Lifted m -> m #

foldMap :: Monoid m => (a -> m) -> Lifted a -> m #

foldr :: (a -> b -> b) -> b -> Lifted a -> b #

foldr' :: (a -> b -> b) -> b -> Lifted a -> b #

foldl :: (b -> a -> b) -> b -> Lifted a -> b #

foldl' :: (b -> a -> b) -> b -> Lifted a -> b #

foldr1 :: (a -> a -> a) -> Lifted a -> a #

foldl1 :: (a -> a -> a) -> Lifted a -> a #

toList :: Lifted a -> [a] #

null :: Lifted a -> Bool #

length :: Lifted a -> Int #

elem :: Eq a => a -> Lifted a -> Bool #

maximum :: Ord a => Lifted a -> a #

minimum :: Ord a => Lifted a -> a #

sum :: Num a => Lifted a -> a #

product :: Num a => Lifted a -> a #

Traversable Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

traverse :: Applicative f => (a -> f b) -> Lifted a -> f (Lifted b) #

sequenceA :: Applicative f => Lifted (f a) -> f (Lifted a) #

mapM :: Monad m => (a -> m b) -> Lifted a -> m (Lifted b) #

sequence :: Monad m => Lifted (m a) -> m (Lifted a) #

Eq a => Eq (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

(==) :: Lifted a -> Lifted a -> Bool #

(/=) :: Lifted a -> Lifted a -> Bool #

Data a => Data (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

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

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

toConstr :: Lifted a -> Constr #

dataTypeOf :: Lifted a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

compare :: Lifted a -> Lifted a -> Ordering #

(<) :: Lifted a -> Lifted a -> Bool #

(<=) :: Lifted a -> Lifted a -> Bool #

(>) :: Lifted a -> Lifted a -> Bool #

(>=) :: Lifted a -> Lifted a -> Bool #

max :: Lifted a -> Lifted a -> Lifted a #

min :: Lifted a -> Lifted a -> Lifted a #

Read a => Read (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Show a => Show (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

showsPrec :: Int -> Lifted a -> ShowS #

show :: Lifted a -> String #

showList :: [Lifted a] -> ShowS #

Generic (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Associated Types

type Rep (Lifted a) :: Type -> Type #

Methods

from :: Lifted a -> Rep (Lifted a) x #

to :: Rep (Lifted a) x -> Lifted a #

Function a => Function (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

function :: (Lifted a -> b) -> Lifted a :-> b #

Arbitrary a => Arbitrary (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

arbitrary :: Gen (Lifted a) #

shrink :: Lifted a -> [Lifted a] #

CoArbitrary a => CoArbitrary (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

coarbitrary :: Lifted a -> Gen b -> Gen b #

NFData a => NFData (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

rnf :: Lifted a -> () #

Hashable a => Hashable (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

hashWithSalt :: Int -> Lifted a -> Int #

hash :: Lifted a -> Int #

Universe a => Universe (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

universe :: [Lifted a] #

Finite a => Finite (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

PartialOrd a => PartialOrd (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

leq :: Lifted a -> Lifted a -> Bool Source #

comparable :: Lifted a -> Lifted a -> Bool Source #

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

Defined in Algebra.Lattice.Lifted

Methods

top :: Lifted a Source #

Lattice a => BoundedJoinSemiLattice (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

bottom :: Lifted a Source #

Lattice a => Lattice (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

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

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

Generic1 Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Associated Types

type Rep1 Lifted :: k -> Type #

Methods

from1 :: Lifted a -> Rep1 Lifted a #

to1 :: Rep1 Lifted a -> Lifted a #

type Rep (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

type Rep (Lifted a) = D1 (MetaData "Lifted" "Algebra.Lattice.Lifted" "lattices-2.0.1-DhjhXTEEVqrG2Ss9wckwFx" False) (C1 (MetaCons "Bottom" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Lift" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Lifted Source # 
Instance details

Defined in Algebra.Lattice.Lifted

type Rep1 Lifted = D1 (MetaData "Lifted" "Algebra.Lattice.Lifted" "lattices-2.0.1-DhjhXTEEVqrG2Ss9wckwFx" False) (C1 (MetaCons "Bottom" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Lift" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

foldLifted :: b -> (a -> b) -> Lifted a -> b Source #

Similar to maybe, but for Lifted type.