Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
sets of ordered entities.
Synopsis
- newtype Set x = Set [x]
- set :: Ord x => [x] -> Set x
- setSpan :: Set x -> Span x
- setxs :: Set x -> [x]
- setSqc :: Ord x => (i -> Maybe x) -> Set i -> Set x
- setMap :: Ord y => (x -> y) -> Set x -> Set y
- isSubSet :: Ord x => Set x -> Set x -> Bool
- setEmpty :: Set x
- setUnion :: Ord x => Set x -> Set x -> Set x
- setIndex :: Ord x => Set x -> x -> Maybe N
- xSet :: Ord x => N -> X x -> X (Set x)
- prpSetUnion :: (Ord x, Show x) => X (Set x) -> Statement
Set
set of ordered entities in x
.
Property Let s =
be in Set
xs
for a ordered Set
xEntity
type x
,
then holds:
Set [x] |
Instances
Foldable Set Source # | |
Defined in OAlg.Entity.Sequence.Set fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
(Integral r, Enum r, Entity x, Ord x) => ConstructableSequence Set r x Source # | |
(Integral r, Enum r) => Sequence Set r x Source # | |
Show x => Show (Set x) Source # | |
Eq x => Eq (Set x) Source # | |
LengthN (Set x) Source # | |
Ord x => POrd (Set x) Source # | |
(Validable x, Ord x, Show x) => Validable (Set x) Source # | |
(Entity x, Ord x) => Entity (Set x) Source # | |
Defined in OAlg.Entity.Sequence.Set |
setMap :: Ord y => (x -> y) -> Set x -> Set y Source #
mapping of sets.
Note This works only for finite sets!
Operations
Lookup
setIndex :: Ord x => Set x -> x -> Maybe N Source #
the index of an element, where the elements of the given set are indexed from 0
.
Examples
>>>
setIndex (Set ['a'..'x']) 'c'
Just 2
X
xSet :: Ord x => N -> X x -> X (Set x) Source #
random variable of sets with maximal the given length.