| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Algebra.Lattice.Stacked
Synopsis
- data Stacked a b
- foldStacked :: (l -> r) -> (u -> r) -> Stacked l u -> r
Documentation
Stacked two lattices, one on top of another. All minimal elements of upper lattice cover all maximal elements of lower lattice.
Instances
| Monad (Stacked a) Source # | |
| Functor (Stacked a) Source # | |
| Applicative (Stacked a) Source # | |
Defined in Algebra.Lattice.Stacked | |
| Foldable (Stacked a) Source # | |
Defined in Algebra.Lattice.Stacked Methods fold :: Monoid m => Stacked a m -> m # foldMap :: Monoid m => (a0 -> m) -> Stacked a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Stacked a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Stacked a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Stacked a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Stacked a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Stacked a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Stacked a a0 -> a0 # toList :: Stacked a a0 -> [a0] # null :: Stacked a a0 -> Bool # length :: Stacked a a0 -> Int # elem :: Eq a0 => a0 -> Stacked a a0 -> Bool # maximum :: Ord a0 => Stacked a a0 -> a0 # minimum :: Ord a0 => Stacked a a0 -> a0 # | |
| Traversable (Stacked a) Source # | |
Defined in Algebra.Lattice.Stacked | |
| Generic1 (Stacked a :: Type -> Type) Source # | |
| (Eq a, Eq b) => Eq (Stacked a b) Source # | |
| (Data a, Data b) => Data (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Stacked a b -> c (Stacked a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Stacked a b) # toConstr :: Stacked a b -> Constr # dataTypeOf :: Stacked a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Stacked a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Stacked a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Stacked a b -> Stacked a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stacked a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stacked a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Stacked a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stacked a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stacked a b -> m (Stacked a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stacked a b -> m (Stacked a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stacked a b -> m (Stacked a b) # | |
| (Ord a, Ord b) => Ord (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (Read a, Read b) => Read (Stacked a b) Source # | |
| (Show a, Show b) => Show (Stacked a b) Source # | |
| Generic (Stacked a b) Source # | |
| (Arbitrary a, Arbitrary b) => Arbitrary (Stacked a b) Source # | |
| (NFData a, NFData b) => NFData (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (Hashable a, Hashable b) => Hashable (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (Universe a, Universe b) => Universe (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (Finite a, Finite b) => Finite (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (PartialOrd a, PartialOrd b) => PartialOrd (Stacked a b) Source # | |
| (Lattice a, BoundedMeetSemiLattice b) => BoundedMeetSemiLattice (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (BoundedJoinSemiLattice a, Lattice b) => BoundedJoinSemiLattice (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked | |
| (Lattice a, Lattice b) => Lattice (Stacked a b) Source # | |
| type Rep1 (Stacked a :: Type -> Type) Source # | |
Defined in Algebra.Lattice.Stacked type Rep1 (Stacked a :: Type -> Type) = D1 (MetaData "Stacked" "Algebra.Lattice.Stacked" "lattices-2.0.2-HdMTcqWeXqlAAQvdNaFFrQ" False) (C1 (MetaCons "Lower" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Upper" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
| type Rep (Stacked a b) Source # | |
Defined in Algebra.Lattice.Stacked type Rep (Stacked a b) = D1 (MetaData "Stacked" "Algebra.Lattice.Stacked" "lattices-2.0.2-HdMTcqWeXqlAAQvdNaFFrQ" False) (C1 (MetaCons "Lower" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Upper" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) | |
foldStacked :: (l -> r) -> (u -> r) -> Stacked l u -> r Source #