vicinity-0.1.0

Safe HaskellNone
LanguageHaskell2010

Data.Vicinity

Contents

Synopsis

Documentation

data Vicinity k v Source #

A map-like container optimized for the execution of range queries. The key must have an Ord instance and the value must have Monoid instance whose append operation is also commutative.

Instances

Foldable (Vicinity k) Source # 

Methods

fold :: Monoid m => Vicinity k m -> m #

foldMap :: Monoid m => (a -> m) -> Vicinity k a -> m #

foldr :: (a -> b -> b) -> b -> Vicinity k a -> b #

foldr' :: (a -> b -> b) -> b -> Vicinity k a -> b #

foldl :: (b -> a -> b) -> b -> Vicinity k a -> b #

foldl' :: (b -> a -> b) -> b -> Vicinity k a -> b #

foldr1 :: (a -> a -> a) -> Vicinity k a -> a #

foldl1 :: (a -> a -> a) -> Vicinity k a -> a #

toList :: Vicinity k a -> [a] #

null :: Vicinity k a -> Bool #

length :: Vicinity k a -> Int #

elem :: Eq a => a -> Vicinity k a -> Bool #

maximum :: Ord a => Vicinity k a -> a #

minimum :: Ord a => Vicinity k a -> a #

sum :: Num a => Vicinity k a -> a #

product :: Num a => Vicinity k a -> a #

(Eq k, Eq v) => Eq (Vicinity k v) Source # 

Methods

(==) :: Vicinity k v -> Vicinity k v -> Bool #

(/=) :: Vicinity k v -> Vicinity k v -> Bool #

(Ord k, Ord v) => Ord (Vicinity k v) Source # 

Methods

compare :: Vicinity k v -> Vicinity k v -> Ordering #

(<) :: Vicinity k v -> Vicinity k v -> Bool #

(<=) :: Vicinity k v -> Vicinity k v -> Bool #

(>) :: Vicinity k v -> Vicinity k v -> Bool #

(>=) :: Vicinity k v -> Vicinity k v -> Bool #

max :: Vicinity k v -> Vicinity k v -> Vicinity k v #

min :: Vicinity k v -> Vicinity k v -> Vicinity k v #

(Show k, Show v) => Show (Vicinity k v) Source # 

Methods

showsPrec :: Int -> Vicinity k v -> ShowS #

show :: Vicinity k v -> String #

showList :: [Vicinity k v] -> ShowS #

(Ord k, Monoid v) => Semigroup (Vicinity k v) Source # 

Methods

(<>) :: Vicinity k v -> Vicinity k v -> Vicinity k v #

sconcat :: NonEmpty (Vicinity k v) -> Vicinity k v #

stimes :: Integral b => b -> Vicinity k v -> Vicinity k v #

(Ord k, Monoid v) => Monoid (Vicinity k v) Source # 

Methods

mempty :: Vicinity k v #

mappend :: Vicinity k v -> Vicinity k v -> Vicinity k v #

mconcat :: [Vicinity k v] -> Vicinity k v #

Query

query Source #

Arguments

:: (Ord k, Monoid v) 
=> Maybe k

Lower bound

-> Maybe k

Upper bound

-> Vicinity k v

Vicinity

-> v 

Get the monoidal concatenation of all values in the range. The bounds are both inclusive. Either bound can be omitted.

total :: Monoid v => Vicinity k v -> v Source #

O(1). The monoidal concatenation of all values in the map. This is equivalent to query Nothing Nothing.

lookup :: (Ord k, Monoid v) => k -> Vicinity k v -> v Source #

splitLookup :: (Ord k, Monoid v) => k -> Vicinity k v -> (Vicinity k v, Maybe v, Vicinity k v) Source #

Split the map at the target key. The map that is the first element of the tuple has keys lower than the target. The map that is the third element of the tuple has keys higher than the target. The second element of the tuple is the value at the key if the key was found.

Construct

singleton :: k -> v -> Vicinity k v Source #

Create a map with a single key-value pair.

insert :: (Ord k, Monoid v) => k -> v -> Vicinity k v -> Vicinity k v Source #

Insert a key associated with a value into the map. If the key already exists, the existing value and the new value are combined using the Monoid instance for v. The implementation of mappend is expected to be commutative, so the order in which the old and new values are combined is not specified.

union :: (Ord k, Monoid v) => Vicinity k v -> Vicinity k v -> Vicinity k v Source #

Combine two maps. If the same key exists in both maps, the values associated with it are combined using the Monoid instance for v. Note that the Monoid instance of Vicinity defines mappend as union.

fromList :: (Ord k, Monoid v) => [(k, v)] -> Vicinity k v Source #

Build a map from a list of key-value pairs.

Deconstruct

foldrWithKey :: (k -> v -> a -> a) -> a -> Vicinity k v -> a Source #

Fold over the keys in the map along with their values.

keys :: Vicinity k v -> [k] Source #

Get the keys of the map.

toList :: Vicinity k v -> [(k, v)] Source #

Convert the map to a list of key-value pairs.

Unsafe

uncheckedConcat :: Monoid v => Vicinity k v -> Vicinity k v -> Vicinity k v Source #

Combine two vicinities. All keys is the first one must be less than all keys in the second one.

Example

A Vicinity performs lookups of a commutative monoid over a key range in optimal time. Consider a collection of books in print that share a common set of properties:

>>> data Book = Book { title :: String, author :: String, year :: Int, cost :: Int }
>>> let b1 = Book "The Wings of Vanessa" "Diana Alexander" 1974 7
>>> let b2 = Book "Dweller and a Card" "Diana Alexander" 1977 4
>>> let b3 = Book "The Weeping Blight" "Diana Alexander" 1980 8
>>> let b4 = Book "The Northern Dog" "Thomas Brown" 1982 2
>>> let b5 = Book "Bridge and Blade" "Thomas Brown" 1988 3
>>> let b6 = Book "The Manor" "Bernice McNeilly" 1983 11
>>> let b7 = Book "Southern Pirate" "Donna Arnold" 1985 23
>>> let b8 = Book "Without the Mesa" "Donna Arnold" 1991 25
>>> let b9 = Book "The Hollywood Sky" "Preston Richey" 1975 10
>>> let books = [b1,b2,b3,b4,b5,b6,b7,b8,b9]

We would like to find the cheapest books published within various time ranges. So, we must also define a price metric that has a commutative semigroup instance:

>>> data Price = Price { ptitle :: String, pcost :: Int } deriving (Show)
>>> appendPrice (Price t1 c1) (Price t2 c2) = case compare c1 c2 of {LT -> Price t1 c1; EQ -> Price (min t1 t2) c1; GT -> Price t2 c2}
>>> instance Semigroup Price where { (<>) = appendPrice }

What does the append operator do here? It chooses the information for the value with the lower price. In the event of a tie (handled by the EQ case), it choose the lexographically lower title. Breaking the tie this way ensures that append is commutative. However, we're still missing a Monoid instance. Notice that Price cannot be made into a Monoid, since there is no sensible and law-abiding mempty. We will need to lift Price to get a Monoid. We can do this with Data.Semigroup.Option. Let's write a function to turn our collection of books into Option Price:

>>> import Data.Semigroup (Option(..))
>>> toPrice (Book t _ _ c) = Option (Just (Price t c))
>>> :t toPrice
toPrice :: Book -> Option Price

Now, we can fold over the collection of books to build our index of the cheapest book in each time range:

>>> let ixc = foldMap (\b -> singleton (year b) (toPrice b)) books
>>> :t ixc
ixc :: Vicinity Int (Option Price)
>>> query (Just 1977) (Just 1986) ixc
Option {getOption = Just (Price {ptitle = "The Northern Dog", pcost = 2})}

Cool. We could pick other commutative monoidal metrics as wells. We could handle things like the set of authors that published during the time range or the total number of books published during the time range. Or we could just do them all at once using the monoid instance of a three-tuple:

>>> import Data.Set (Set)
>>> import qualified Data.Set as S
>>> type Metrics = (Option Price, Set String, Sum Int)
>>> printMetrics (a,b,c) = print a >> print b >> print c
>>> toMetrics b = (toPrice b, S.singleton (author b), Sum (1 :: Int))
>>> :t toMetrics
toMetrics :: Book -> (Option Price, Set String, Sum Int)
>>> let ixa = foldMap (\b -> singleton (year b) (toMetrics b)) books
>>> printMetrics (query (Just 1974) (Just 1989) ixa)
Option {getOption = Just (Price {ptitle = "The Northern Dog", pcost = 2})}
fromList ["Bernice McNeilly","Diana Alexander","Donna Arnold","Preston Richey","Thomas Brown"]
Sum {getSum = 8}
>>> printMetrics (query (Just 1982) (Just 1985) ixa)
Option {getOption = Just (Price {ptitle = "The Northern Dog", pcost = 2})}
fromList ["Bernice McNeilly","Donna Arnold","Thomas Brown"]
Sum {getSum = 3}