An Olist
is an ordered list. The main function of this module is the implementation of the finite subset structure of a given type a
. Finite sets are represented as ordered lists and the basic set functions and relations like union
, intersection
, included
etc. are provided.
- type Olist a = [a]
- olist :: Ord a => [a] -> Olist a
- isOlist :: Ord a => [a] -> Bool
- empty :: Ord a => Olist a
- isEmpty :: Ord a => Olist a -> Bool
- member :: Ord a => a -> Olist a -> Bool
- insert :: Ord a => a -> Olist a -> Olist a
- delete :: Ord a => a -> Olist a -> Olist a
- included :: Ord a => Olist a -> Olist a -> Bool
- properlyIncluded :: Ord a => Olist a -> Olist a -> Bool
- disjunct :: Ord a => Olist a -> Olist a -> Bool
- properlyDisjunct :: Ord a => Olist a -> Olist a -> Bool
- equal :: Ord a => Olist a -> Olist a -> Bool
- union :: Ord a => Olist a -> Olist a -> Olist a
- intersection :: Ord a => Olist a -> Olist a -> Olist a
- difference :: Ord a => Olist a -> Olist a -> Olist a
- opposition :: Ord a => Olist a -> Olist a -> Olist a
- unionList :: Ord a => [Olist a] -> Olist a
- intersectionList :: Ord a => [Olist a] -> Olist a
The Olist
type
The construction and test for ordered lists
For example,
> olist ["b", "c", "b", "a", "c", "a"] ["a","b","c"]
As the example shows, multiple occuring members are deleted.
(The implementation builts the ordered list with component-wise insert
and that is not an optimal sorting algorithm in general.
But it is optimal, when the argument is an already ordered list. We use olist
only as a an additional safety-mechanism for
functions like ext :: p -> [a] -> p
, where in most cases the second argument will usually be an Olist a
value, anyway.)
Checks if the given argument is ordered.
The empty list
Returns the empty list []
, i.e.
> Olist.empty []
(Note, that there is also an empty
function in the Costack
module.)
Checks on emptiness; i.e. it is the same as the Haskell native null
.
> isEmpty [1,2,3] False
Singular operations on ordered lists
For example,
> member 7 [3,5,7,9] True > 4 `member` [2,3,4,5] True
For example,
> insert 7 [3,5,9,11] [3,5,7,9,11] > insert 7 [3,5,7,9,11] [3,5,7,9,11]
For example,
> delete 7 [3,5,7,9,11] [3,5,9,11] > delete 7 [3,5,9,11] [3,5,9,11]
The common binary operations on sets
These functions all assume, that the arguments are actually Olist
values. Otherwise, the function doesn't terminate with an
error, it just produces unintended results.
Implementation of ⊆ on (finite) sets. For example,
> included "acd" "abcd" -- recall, that "acd" is the list ['a', 'c', 'd'] True > [2,4] `included` [1,2,3,4,5] True
Implementation of the strict version ⊂ of ⊆, i.e. the first argument must be included, but different to the second one.
Two finite sets, i.e. two ordered lists are disjunct iff they do not have a common member. For example
> disjunct "acd" "bef" True > "abc" `disjunct` "bef" False > [] `disjunct` [1,2,3] True
Two finite sets are properly disjunct iff they are disjunct and none of them is empty.
> [] `properlyDisjunct` [1,2,3] False
The equality of two finite sets; actually it is just another name for (==)
on ordered lists.
The implementation of ∪, for example
> [1,2,4,5] `union` [1,3,5,7] [1,2,3,4,5,7]
The implementation of ∩, for example
> [1,2,4,5] `intersection` [1,3,5,7] [1,5]
Implementation of the difference operator \ on sets. For example,
> [1,2,4,5] `difference` [1,3,5,7] [2,4]
The opposition or symmetric difference S
∇T
of two sets S
, T
is defined as (S\T)∪(T\S)
. For example,
> [1,2,4,5] `opposition` [1,3,5,7] [2,3,4,7]
Returns the union of a list of ordered lists. For example,
> unionList [[1,3,5], [1,2,3], [1,5,9]] [1,2,3,5,9] > unionList [] []
intersectionList :: Ord a => [Olist a] -> Olist aSource
Returns the intersection of a list of ordered lists. The result is undefined for the empty list.
> intersectionList [[1,3,5], [1,2,3], [1,5,9]] [1] > intersectionList [] *** Exception: Olist.intersectionList: not defined for empty list argument