pomaps-0.0.0.1: Maps and sets of partial orders

Copyright(c) Sebastian Graf 2017
LicenseMIT
Maintainersgraf1337@gmail.com
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.POSet

Contents

Description

A reasonably efficient implementation of partially ordered sets.

These modules are intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.

import qualified Data.POSet as POSet

The implementation of POSet is based on a decomposition of chains (totally ordered submaps), inspired by "Sorting and Selection in Posets".

Operation comments contain the operation time complexity in Big-O notation and commonly refer to two characteristics of the poset from which keys are drawn: The number of elements in the set \(n\) and the width \(w\) of the poset, referring to the size of the biggest anti-chain (set of incomparable elements).

Generally speaking, lookup and mutation operations incur an additional factor of \(\mathcal{O}(w)\) compared to their counter-parts in Data.Set.

Note that for practical applications, the width of the poset should be in the order of \(w\in \mathcal{O}(\frac{n}{\log n})\), otherwise a simple lookup list is asymptotically superior. Even if that holds, the constants might be too big to be useful for any \(n\) that can can happen in practice.

The following examples assume the following definitions for a set on the divisibility relation on Integers:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import           Algebra.PartialOrd
import           Data.POSet (POSet)
import qualified Data.POSet as POSet

newtype Divisibility
  = Div Int
  deriving (Eq, Read, Show, Num)

default (Divisibility)

instance PartialOrd Divisibility where
  Div a `leq` Div b = b `mod` a == 0

type DivSet = POSet Divisibility

-- We want integer literals to be interpreted as Divisibilitys
-- and default emptys to DivSet.
default (Divisibility, DivSet)

Divisility is actually an example for a PartialOrd that should not be used as keys of POSet. Its width is \(w=\frac{n}{2}\in\Omega(n)\)!

Synopsis

Set type

data POSet k Source #

A set of partially ordered values k.

Instances

Foldable POSet Source # 

Methods

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 #

toList :: POSet a -> [a] #

null :: POSet a -> Bool #

length :: POSet a -> Int #

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

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

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

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

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

PartialOrd k => IsList (POSet k) Source # 

Associated Types

type Item (POSet k) :: * #

Methods

fromList :: [Item (POSet k)] -> POSet k #

fromListN :: Int -> [Item (POSet k)] -> POSet k #

toList :: POSet k -> [Item (POSet k)] #

PartialOrd k => Eq (POSet k) Source # 

Methods

(==) :: POSet k -> POSet k -> Bool #

(/=) :: POSet k -> POSet k -> Bool #

(Read a, PartialOrd a) => Read (POSet a) Source # 
Show a => Show (POSet a) Source # 

Methods

showsPrec :: Int -> POSet a -> ShowS #

show :: POSet a -> String #

showList :: [POSet a] -> ShowS #

NFData a => NFData (POSet a) Source # 

Methods

rnf :: POSet a -> () #

PartialOrd k => PartialOrd (POSet k) Source # 

Methods

leq :: POSet k -> POSet k -> Bool #

comparable :: POSet k -> POSet k -> Bool #

type Item (POSet k) Source # 
type Item (POSet k) = k

Query

null :: Foldable t => forall a. t a -> Bool #

Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

size :: POSet k -> Int Source #

\(\mathcal{O}(1)\). The number of elements in this set.

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]

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])
[]

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])
[]

isSubsetOf :: PartialOrd k => POSet k -> POSet k -> Bool Source #

\(\mathcal{O}(n_2 w_1 n_1 \log n_1)\). (s1 isSubsetOf s2) tells whether 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

empty :: POSet k Source #

\(\mathcal{O}(1)\). The empty set.

singleton :: k -> POSet k Source #

\(\mathcal{O}(1)\). A set with a single element.

insert :: PartialOrd k => k -> POSet k -> POSet k Source #

\(\mathcal{O}(w\log n)\). If the key is already present in the map, the associated value is replaced with the supplied value. insert is equivalent to insertWith const.

delete :: PartialOrd k => k -> POSet k -> POSet k Source #

\(\mathcal{O}(w\log n)\). Delete an element from a set.

Combine

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.

unions :: PartialOrd k => [POSet k] -> POSet k Source #

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 :: 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.

Map

map :: PartialOrd k2 => (k1 -> k2) -> POSet k1 -> POSet k2 Source #

\(\mathcal{O}(wn\log n)\). map f s is the set obtained by applying f 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)\). mapMonotonic f s == map f s, but works only when f 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 :: Foldable t => forall a b. (a -> b -> b) -> b -> t a -> b #

Right-associative fold of a structure.

In the case of lists, foldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

Note that, since the head of the resulting expression is produced by an application of the operator to the first element of the list, foldr can produce a terminating expression from an infinite list.

For a general Foldable structure this should be semantically identical to,

foldr f z = foldr f z . toList

foldl :: Foldable t => forall b a. (b -> a -> b) -> b -> t a -> b #

Left-associative fold of a structure.

In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.

Also note that if you want an efficient left-fold, you probably want to use foldl' instead of foldl. The reason for this is that latter does not force the "inner" results (e.g. z f x1 in the above example) before applying them to the operator (e.g. to (f x2)). This results in a thunk chain O(n) elements long, which then must be evaluated from the outside-in.

For a general Foldable structure this should be semantically identical to,

foldl f z = foldl f z . toList

Strict 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

elems :: POSet k -> [k] Source #

\(\mathcal{O}(n)\). The elements of a set in unspecified order.

toList :: POSet k -> [k] Source #

\(\mathcal{O}(n)\). The elements of a set in unspecified order.

fromList :: PartialOrd k => [k] -> POSet k Source #

\(\mathcal{O}(wn\log n)\). Build a set from a list of keys.