Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module doesn't respect the PVP! Breaking changes may happen at any minor version (>= *.*.m.*)
Synopsis
- newtype POSet k = POSet (POMap k ())
- size :: POSet k -> Int
- width :: POSet k -> Int
- member :: PartialOrd k => k -> POSet k -> Bool
- notMember :: PartialOrd k => k -> POSet k -> Bool
- lookupLT :: PartialOrd k => k -> POSet k -> [k]
- lookupLE :: PartialOrd k => k -> POSet k -> [k]
- lookupGE :: PartialOrd k => k -> POSet k -> [k]
- lookupGT :: PartialOrd k => k -> POSet k -> [k]
- isSubsetOf :: PartialOrd k => POSet k -> POSet k -> Bool
- isProperSubsetOf :: PartialOrd k => POSet k -> POSet k -> Bool
- empty :: POSet k
- singleton :: k -> POSet k
- insert :: PartialOrd k => k -> POSet k -> POSet k
- delete :: PartialOrd k => k -> POSet k -> POSet k
- union :: PartialOrd k => POSet k -> POSet k -> POSet k
- unions :: PartialOrd k => [POSet k] -> POSet k
- difference :: PartialOrd k => POSet k -> POSet k -> POSet k
- intersection :: PartialOrd k => POSet k -> POSet k -> POSet k
- filter :: (k -> Bool) -> POSet k -> POSet k
- partition :: (k -> Bool) -> POSet k -> (POSet k, POSet k)
- takeWhileAntitone :: (k -> Bool) -> POSet k -> POSet k
- dropWhileAntitone :: (k -> Bool) -> POSet k -> POSet k
- spanAntitone :: (k -> Bool) -> POSet k -> (POSet k, POSet k)
- map :: PartialOrd k2 => (k1 -> k2) -> POSet k1 -> POSet k2
- mapMonotonic :: (k1 -> k2) -> POSet k1 -> POSet k2
- foldr' :: (a -> b -> b) -> b -> POSet a -> b
- foldl' :: (b -> a -> b) -> b -> POSet a -> b
- lookupMin :: PartialOrd k => POSet k -> [k]
- lookupMax :: PartialOrd k => POSet k -> [k]
- elems :: POSet k -> [k]
- toList :: POSet k -> [k]
- fromList :: PartialOrd k => [k] -> POSet k
Documentation
This is some setup code for doctest
.
>>> :set -XGeneralizedNewtypeDeriving
>>> import Algebra.PartialOrd
>>> import Data.POSet
>>> :{
newtype Divisibility
= Div Int
deriving (Eq, Num)
instance Show Divisibility where
show (Div a) = show a
instance PartialOrd Divisibility where
Div a leq
Div b = b mod
a == 0
type DivSet = POSet Divisibility
default (Divisibility, DivSet)
:}
A set of partially ordered values k
.
Instances
Foldable POSet Source # | |
Defined in Data.POSet.Internal fold :: Monoid m => POSet m -> m # foldMap :: Monoid m => (a -> m) -> POSet a -> m # foldr :: (a -> b -> b) -> b -> POSet a -> b # foldr' :: (a -> b -> b) -> b -> POSet a -> b # foldl :: (b -> a -> b) -> b -> POSet a -> b # foldl' :: (b -> a -> b) -> b -> POSet a -> b # foldr1 :: (a -> a -> a) -> POSet a -> a # foldl1 :: (a -> a -> a) -> POSet a -> a # elem :: Eq a => a -> POSet a -> Bool # maximum :: Ord a => POSet a -> a # minimum :: Ord a => POSet a -> a # | |
PartialOrd k => IsList (POSet k) Source # | |
PartialOrd k => Eq (POSet k) Source # | |
(Read a, PartialOrd a) => Read (POSet a) Source # | |
Show a => Show (POSet a) Source # | |
NFData a => NFData (POSet a) Source # | |
Defined in Data.POSet.Internal | |
PartialOrd k => PartialOrd (POSet k) Source # | |
type Item (POSet k) Source # | |
Defined in Data.POSet.Internal |
Instances
Query
width :: POSet k -> Int Source #
\(\mathcal{O}(w)\). The width \(w\) of the chain decomposition in the internal data structure. This is always at least as big as the size of the biggest possible anti-chain.
member :: PartialOrd k => k -> POSet k -> Bool Source #
\(\mathcal{O}(w\log n)\).
Is the key a member of the map? See also notMember
.
notMember :: PartialOrd k => k -> POSet k -> Bool Source #
\(\mathcal{O}(w\log n)\).
Is the key not a member of the map? See also member
.
lookupLT :: PartialOrd k => k -> POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). Find the largest set of keys smaller than the given one and return the corresponding list of (key, value) pairs.
Note that the following examples assume the Divisibility
partial order defined at the top.
>>>
lookupLT 3 (fromList [3, 5])
[]>>>
lookupLT 6 (fromList [3, 5])
[3]
lookupLE :: PartialOrd k => k -> POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). Find the largest key smaller or equal to the given one and return the corresponding list of (key, value) pairs.
Note that the following examples assume the Divisibility
partial order defined at the top.
>>>
lookupLE 2 (fromList [3, 5])
[]>>>
lookupLE 3 (fromList [3, 5])
[3]>>>
lookupLE 10 (fromList [3, 5])
[5]
lookupGE :: PartialOrd k => k -> POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). Find the smallest key greater or equal to the given one and return the corresponding list of (key, value) pairs.
Note that the following examples assume the Divisibility
partial order defined at the top.
>>>
lookupGE 3 (fromList [3, 5])
[3]>>>
lookupGE 5 (fromList [3, 10])
[10]>>>
lookupGE 6 (fromList [3, 5])
[]
lookupGT :: PartialOrd k => k -> POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). Find the smallest key greater than the given one and return the corresponding list of (key, value) pairs.
Note that the following examples assume the Divisibility
partial order defined at the top.
>>>
lookupGT 3 (fromList [6, 5])
[6]>>>
lookupGT 5 (fromList [3, 5])
[]
isSubsetOf :: PartialOrd k => POSet k -> POSet k -> Bool Source #
\(\mathcal{O}(n_2 w_1 n_1 \log n_1)\).
(s1
tells whether isSubsetOf
s2)s1
is a subset of s2
.
isProperSubsetOf :: PartialOrd k => POSet k -> POSet k -> Bool Source #
\(\mathcal{O}(n_2 w_1 n_1 \log n_1)\). Is this a proper subset? (ie. a subset but not equal).
Construction
delete :: PartialOrd k => k -> POSet k -> POSet k Source #
\(\mathcal{O}(w\log n)\). Delete an element from a set.
Combine
Union
union :: PartialOrd k => POSet k -> POSet k -> POSet k Source #
\(\mathcal{O}(wn\log n)\), where \(n=\max(n_1,n_2)\) and \(w=\max(w_1,w_2)\). The union of two sets, preferring the first set when equal elements are encountered.
Difference
difference :: PartialOrd k => POSet k -> POSet k -> POSet k Source #
\(\mathcal{O}(wn\log n)\), where \(n=\max(n_1,n_2)\) and \(w=\max(w_1,w_2)\). Difference of two sets.
Intersection
intersection :: PartialOrd k => POSet k -> POSet k -> POSet k Source #
\(\mathcal{O}(wn\log n)\), where \(n=\max(n_1,n_2)\) and \(w=\max(w_1,w_2)\). The intersection of two sets. Elements of the result come from the first set, so for example
>>>
data AB = A | B deriving Show
>>>
instance Eq AB where _ == _ = True
>>>
instance PartialOrd AB where _ `leq` _ = True
>>>
singleton A `intersection` singleton B
fromList [A]>>>
singleton B `intersection` singleton A
fromList [B]
Filter
filter :: (k -> Bool) -> POSet k -> POSet k Source #
\(\mathcal{O}(n)\). Filter all elements that satisfy the predicate.
partition :: (k -> Bool) -> POSet k -> (POSet k, POSet k) Source #
\(\mathcal{O}(n)\). Partition the set into two sets, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate.
takeWhileAntitone :: (k -> Bool) -> POSet k -> POSet k Source #
\(\mathcal{O}(log n)\). Take while a predicate on the keys holds.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
. See note at spanAntitone
.
takeWhileAntitone p = filter
p
Since: 0.0.1.0
dropWhileAntitone :: (k -> Bool) -> POSet k -> POSet k Source #
\(\mathcal{O}(log n)\). Drop while a predicate on the keys holds.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
. See note at spanAntitone
.
dropWhileAntitone p = filter
(not . p)
Since: 0.0.1.0
spanAntitone :: (k -> Bool) -> POSet k -> (POSet k, POSet k) Source #
\(\mathcal{O}(log n)\). Divide a set at the point where a predicate on the keys stops holding.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
.
spanAntitone p xs = partition
p xs
Note: if p
is not actually antitone, then spanAntitone
will split the set
at some unspecified point where the predicate switches from holding to not
holding (where the predicate is seen to hold before the first element and to fail
after the last element).
Since: 0.0.1.0
Map
map :: PartialOrd k2 => (k1 -> k2) -> POSet k1 -> POSet k2 Source #
\(\mathcal{O}(wn\log n)\).
is the set obtained by applying map
f sf
to each element of s
.
It's worth noting that the size of the result may be smaller if,
for some (x,y)
, x /= y && f x == f y
mapMonotonic :: (k1 -> k2) -> POSet k1 -> POSet k2 Source #
\(\mathcal{O}(n)\).
, but works only when mapMonotonic
f s == map
f sf
is strictly increasing.
The precondition is not checked.
Semi-formally, for every chain ls
in s
we have:
and [x < y ==> f x < f y | x <- ls, y <- ls] ==> mapMonotonic f s == map f s
Folds
foldr' :: (a -> b -> b) -> b -> POSet a -> b Source #
\(\mathcal{O}(n)\).
A strict version of foldr
. Each application of the operator is
evaluated before using the result in the next application. This
function is strict in the starting value.
foldl' :: (b -> a -> b) -> b -> POSet a -> b Source #
\(\mathcal{O}(n)\).
A strict version of foldl
. Each application of the operator is
evaluated before using the result in the next application. This
function is strict in the starting value.
Min/Max
lookupMin :: PartialOrd k => POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). The minimal keys of the set.
lookupMax :: PartialOrd k => POSet k -> [k] Source #
\(\mathcal{O}(w\log n)\). The maximal keys of the set.
Conversion
fromList :: PartialOrd k => [k] -> POSet k Source #
\(\mathcal{O}(wn\log n)\). Build a set from a list of keys.