Copyright | (C) 2010-2015 Maximilian Bolingbroke 2015-2019 Oleg Grenrus |
---|---|
License | BSD-3-Clause (see the file LICENSE) |
Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Lifted a
- retractLifted :: BoundedJoinSemiLattice a => Lifted a -> a
- foldLifted :: b -> (a -> b) -> Lifted a -> b
Documentation
Graft a distinct bottom onto an otherwise unbounded lattice. As a bonus, the bottom will be an absorbing element for the meet.
Instances
Foldable Lifted Source # | |
Defined in Algebra.Lattice.Lifted fold :: Monoid m => Lifted m -> m # foldMap :: Monoid m => (a -> m) -> Lifted a -> 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 # elem :: Eq a => a -> Lifted a -> Bool # maximum :: Ord a => Lifted a -> a # minimum :: Ord a => Lifted a -> a # | |
Traversable Lifted Source # | |
Applicative Lifted Source # | |
Functor Lifted Source # | |
Monad Lifted Source # | |
Generic1 Lifted Source # | |
Arbitrary a => Arbitrary (Lifted a) Source # | |
CoArbitrary a => CoArbitrary (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted coarbitrary :: Lifted a -> Gen b -> Gen b # | |
Function a => Function (Lifted a) Source # | |
Data a => Data (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted 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 :: forall r r'. (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) # | |
Generic (Lifted a) Source # | |
Read a => Read (Lifted a) Source # | |
Show a => Show (Lifted a) Source # | |
NFData a => NFData (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
Eq a => Eq (Lifted a) Source # | |
Ord a => Ord (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
Hashable a => Hashable (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
Lattice a => BoundedJoinSemiLattice (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
Lattice a => Lattice (Lifted a) Source # | |
PartialOrd a => PartialOrd (Lifted a) Source # | |
Finite a => Finite (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
Universe a => Universe (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted | |
type Rep1 Lifted Source # | |
Defined in Algebra.Lattice.Lifted type Rep1 Lifted = D1 ('MetaData "Lifted" "Algebra.Lattice.Lifted" "lattices-2.1-FTYhZPoI65oIdMkyt1I5F1" 'False) (C1 ('MetaCons "Bottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lift" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
type Rep (Lifted a) Source # | |
Defined in Algebra.Lattice.Lifted type Rep (Lifted a) = D1 ('MetaData "Lifted" "Algebra.Lattice.Lifted" "lattices-2.1-FTYhZPoI65oIdMkyt1I5F1" 'False) (C1 ('MetaCons "Bottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lift" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
retractLifted :: BoundedJoinSemiLattice a => Lifted a -> a Source #
Interpret
using the Lifted
aBoundedJoinSemiLattice
of a
.