hgeometry-combinatorial-0.12.0.2: Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Set.Util

Description

 
Synopsis

Documentation

data S Source #

Constructors

S String 

Instances

Instances details
Show S Source # 
Instance details

Defined in Data.Set.Util

Methods

showsPrec :: Int -> S -> ShowS #

show :: S -> String #

showList :: [S] -> ShowS #

cmpS :: S -> S -> Ordering Source #

>>> import Data.Ord(comparing)
>>> data S = S String deriving Show
>>> cmpS = comparing (\(S s) -> length s)

splitOn :: Ord b => (a -> b) -> b -> Set a -> (Set a, Set a, Set a) Source #

Given a monotonic function f that maps a to b, split the sequence s depending on the b values. I.e. the result (l,m,r) is such that * all (< x) . fmap f $ l * all (== x) . fmap f $ m * all (> x) . fmap f $ r

running time: \(O(\log n)\)

splitBy :: (a -> Ordering) -> Set a -> (Set a, Set a, Set a) Source #

Given a monotonic function f that orders a, split the sequence s into three parts. I.e. the result (lt,eq,gt) is such that * all (x -> f x == LT) . fmap f $ lt * all (x -> f x == EQ) . fmap f $ eq * all (x -> f x == GT) . fmap f $ gt

running time: \(O(\log n)\)

fromListBy :: (a -> a -> Ordering) -> [a] -> Set a Source #

Constructs a Set using the given Order.

Note that this is dangerous as the resulting set may not abide the ordering expected of such sets.

running time: \(O(n\log n)\)

join :: Set a -> Set a -> Set a Source #

Given two sets l and r, such that all elements of l occur before r, join the two sets into a combined set.

running time: \(O(\log n)\)

insertBy :: (a -> a -> Ordering) -> a -> Set a -> Set a Source #

Inserts an element into the set, assuming that the set is ordered by the given order.

>>> insertBy cmpS (S "ccc") $ fromListBy cmpS [S "a" , S "bb" , S "dddd"]
fromList [S "a",S "bb",S "ccc",S "dddd"]

When trying to insert an element that equals an element already in the set (according to the given comparator), this function replaces the old element by the new one:

>>> insertBy cmpS (S "cc") $ fromListBy cmpS [S "a" , S "bb" , S "dddd"]
fromList [S "a",S "cc",S "dddd"]

running time: \(O(\log n)\)

deleteAllBy :: (a -> a -> Ordering) -> a -> Set a -> Set a Source #

Deletes an element from the set, assuming the set is ordered by the given ordering.

>>> deleteAllBy cmpS (S "bb") $ fromListBy cmpS [S "a" , S "bb" , S "dddd"]
fromList [S "a",S "dddd"]
>>> deleteAllBy cmpS (S "bb") $ fromListBy cmpS [S "a" , S "bb" , S "cc", S "dd", S "ee", S "ff", S "dddd"]
fromList [S "a",S "dddd"]

running time: \(O(\log n)\)

queryBy :: (a -> a -> Ordering) -> (forall b. Ord b => b -> Set b -> t b) -> a -> Set a -> t a Source #

Run a query, eg. lookupGE, on the set with the given ordering.

Note: The binarySearchIn function may be a useful alternative to queryBy

>>> queryBy cmpS Set.lookupGE (S "22") $ fromListBy cmpS [S "a" , S "bbb" , S "ddddddd"]
Just (S "bbb")
>>> queryBy cmpS Set.lookupLE (S "22") $ fromListBy cmpS [S "a" , S "bbb" , S "ddddddd"]
Just (S "a")
>>> queryBy cmpS Set.lookupGE (S "333") $ fromListBy cmpS [S "a" , S "bbb" , S "ddddddd"]
Just (S "bbb")