oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Entity.Sequence.Set

Description

sets of ordered entities.

Synopsis

Set

newtype Set x Source #

set of ordered entities in x.

Property Let s = Set xs be in Set x for a ordered Entity type x, then holds:

  1. For all ..x:y.. in xs holds: x < y.
  2. lengthN s == lengthN xs.

Constructors

Set [x] 

Instances

Instances details
Foldable Set Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

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 #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

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

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

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

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

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

(Integral r, Enum r, Entity x, Ord x) => ConstructableSequence Set r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

sequence :: (r -> Maybe x) -> Set r -> Set x Source #

(<&) :: Set x -> Set r -> Set x Source #

(Integral r, Enum r) => Sequence Set r x Source # 
Instance details

Defined in OAlg.Entity.Sequence.Definition

Methods

graph :: p r -> Set x -> Graph r x Source #

list :: p r -> Set x -> [(x, r)] Source #

(??) :: Set x -> r -> Maybe x Source #

Show x => Show (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

showsPrec :: Int -> Set x -> ShowS #

show :: Set x -> String #

showList :: [Set x] -> ShowS #

Eq x => Eq (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

(==) :: Set x -> Set x -> Bool #

(/=) :: Set x -> Set x -> Bool #

LengthN (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

lengthN :: Set x -> N Source #

Ord x => POrd (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

(<<=) :: Set x -> Set x -> Bool Source #

(Validable x, Ord x, Show x) => Validable (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Methods

valid :: Set x -> Statement Source #

(Entity x, Ord x) => Entity (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

set :: Ord x => [x] -> Set x Source #

makes a set from the given list.

setSpan :: Set x -> Span x Source #

the span of a set.

setxs :: Set x -> [x] Source #

the elements of a set.

setSqc :: Ord x => (i -> Maybe x) -> Set i -> Set x Source #

mapping a set.

setMap :: Ord y => (x -> y) -> Set x -> Set y Source #

mapping of sets.

Note This works only for finite sets!

isSubSet :: Ord x => Set x -> Set x -> Bool Source #

checks for being a sub set.

Operations

setEmpty :: Set x Source #

the empty set.

setUnion :: Ord x => Set x -> Set x -> Set x Source #

the union of two sets.

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.

Propositions

prpSetUnion :: (Ord x, Show x) => X (Set x) -> Statement Source #

validity for the union operator of sets.