text-containers-0.1.0.0: Memory-efficient string-indexed container types.

Copyright© 2017 Herbert Valerio Riedel
LicenseGPLv3
Safe HaskellTrustworthy
LanguageHaskell2010

Data.TextMap.Unboxed.Lazy

Contents

Description

This module provides the TextMap container for storing maps of text keys to non-strict values.

This module is intended to be imported qualified, e.g.

import           Data.TextMap.Unboxed.Lazy (TextMap)
import qualified Data.TextMap.Unboxed.Lazy as TextMap

The API of this module provides value-lazy operations.

Synopsis

Documentation

data TextMap v Source #

A map of (unboxed) ShortText string keys to values.

The memory footprint of this data-structure is expressed in words

\[ 8 + 2n + \left\lceil \frac{1}{w} \sum_{i=0}^{n-1} len(k_i) \right\rceil + \sum_{i=0}^{n-1} size(v_i) \]

where

  • the word-size \(w\) is either \(w = 4\) or \(w = 8\) bytes,
  • \(len(k_i)\) denotes the UTF-8 size in bytes of the \(i\)-th key string, and
  • \(size(v_i)\) denotes the allocated heap size of the \(i\)-th value in words.

NOTE: One word can be saved by unpacking TextMap (i.e. via {-# UNPACK #-}) into another constructor.

Instances

Functor TextMap Source # 

Methods

fmap :: (a -> b) -> TextMap a -> TextMap b #

(<$) :: a -> TextMap b -> TextMap a #

Foldable TextMap Source # 

Methods

fold :: Monoid m => TextMap m -> m #

foldMap :: Monoid m => (a -> m) -> TextMap a -> m #

foldr :: (a -> b -> b) -> b -> TextMap a -> b #

foldr' :: (a -> b -> b) -> b -> TextMap a -> b #

foldl :: (b -> a -> b) -> b -> TextMap a -> b #

foldl' :: (b -> a -> b) -> b -> TextMap a -> b #

foldr1 :: (a -> a -> a) -> TextMap a -> a #

foldl1 :: (a -> a -> a) -> TextMap a -> a #

toList :: TextMap a -> [a] #

null :: TextMap a -> Bool #

length :: TextMap a -> Int #

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

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

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

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

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

Traversable TextMap Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TextMap a -> f (TextMap b) #

sequenceA :: Applicative f => TextMap (f a) -> f (TextMap a) #

mapM :: Monad m => (a -> m b) -> TextMap a -> m (TextMap b) #

sequence :: Monad m => TextMap (m a) -> m (TextMap a) #

IsList (TextMap v) Source # 

Associated Types

type Item (TextMap v) :: * #

Methods

fromList :: [Item (TextMap v)] -> TextMap v #

fromListN :: Int -> [Item (TextMap v)] -> TextMap v #

toList :: TextMap v -> [Item (TextMap v)] #

Eq v => Eq (TextMap v) Source # 

Methods

(==) :: TextMap v -> TextMap v -> Bool #

(/=) :: TextMap v -> TextMap v -> Bool #

Ord v => Ord (TextMap v) Source # 

Methods

compare :: TextMap v -> TextMap v -> Ordering #

(<) :: TextMap v -> TextMap v -> Bool #

(<=) :: TextMap v -> TextMap v -> Bool #

(>) :: TextMap v -> TextMap v -> Bool #

(>=) :: TextMap v -> TextMap v -> Bool #

max :: TextMap v -> TextMap v -> TextMap v #

min :: TextMap v -> TextMap v -> TextMap v #

Read v => Read (TextMap v) Source # 
Show v => Show (TextMap v) Source # 

Methods

showsPrec :: Int -> TextMap v -> ShowS #

show :: TextMap v -> String #

showList :: [TextMap v] -> ShowS #

NFData v => NFData (TextMap v) Source # 

Methods

rnf :: TextMap v -> () #

Hashable v => Hashable (TextMap v) Source # 

Methods

hashWithSalt :: Int -> TextMap v -> Int #

hash :: TextMap v -> Int #

type Item (TextMap v) Source # 
type Item (TextMap v) = (Key, v)

Querying & lookup

size :: TextMap v -> Int Source #

\(\mathcal{O}(1)\). Report number of entries in map.

>>> size empty
0
>>> size (singleton "sa" LT)
1
>>> size (fromList [("a",True),("b",False),("a",False)])
2

null :: TextMap v -> Bool Source #

\(\mathcal{O}(1)\). Test whether map is empty.

>>> null empty
True
>>> null (singleton "" ())
False

member :: Key -> TextMap v -> Bool Source #

\(\mathcal{O}(\log n)\). Test whether key is present in map.

>>> member "empty" empty
False
>>> member "a" (fromList [("a",EQ),("b",GT),("c",LT)])
True
>>> member "d" (fromList [("a",EQ),("b",GT),("c",LT)])
False

lookup :: Key -> TextMap v -> Maybe v Source #

\(\mathcal{O}(\log n)\). Lookup value for given key.

>>> lookup "a" (fromList [("bb",False),("cc",True)])
Nothing
>>> lookup "c" (fromList [("bb",False),("cc",True)])
Nothing
>>> lookup "cc" (fromList [("bb",False),("cc",True)])
Just True
>>> lookup "z" (fromList [("bb",False),("cc",True)])
Nothing

(!?) :: TextMap v -> Key -> Maybe v Source #

\(\mathcal{O}(\log n)\). Lookup value for given key.

>>> fromList [("bb",False),("cc",True)] !? "cc"
Just True

This is a flipped infix alias of lookup.

findWithDefault :: v -> Key -> TextMap v -> v Source #

\(\mathcal{O}(\log n)\). Lookup value for key in map or return default value if key not contained in map.

>>> findWithDefault True "z" (fromList [("bb",False),("cc",True)])
True
>>> findWithDefault True "bb" (fromList [("bb",False),("cc",True)])
False

See also lookup or !?.

lookupMin :: TextMap v -> Maybe (Key, v) Source #

\(\mathcal{O}(1)\). Extract minimal key and its associated value.

>>> lookupMin empty
Nothing
>>> lookupMin (fromList [("a",EQ),("b",GT),("c",LT)])
Just ("a",EQ)

lookupMax :: TextMap v -> Maybe (Key, v) Source #

\(\mathcal{O}(1)\). Extract maximal key and its associated value.

>>> lookupMax empty
Nothing
>>> lookupMax (fromList [("a",EQ),("b",GT),("c",LT)])
Just ("c",LT)

lookupLE :: Key -> TextMap v -> Maybe (Key, v) Source #

\(\mathcal{O}(\log n)\). Lookup "greatest" key in map less or equal to given key and return key/value pair.

>>> lookupLE "a" (fromList [("bb",False),("cc",True)])
Nothing
>>> lookupLE "c" (fromList [("bb",False),("cc",True)])
Just ("bb",False)
>>> lookupLE "cc" (fromList [("bb",False),("cc",True)])
Just ("cc",True)
>>> lookupLE "z" (fromList [("bb",False),("cc",True)])
Just ("cc",True)

lookupGE :: Key -> TextMap v -> Maybe (Key, v) Source #

\(\mathcal{O}(\log n)\). Lookup "least" key in map less or equal to given key and return key/value pair.

>>> lookupGE "a" (fromList [("bb",False),("cc",True)])
Just ("bb",False)
>>> lookupGE "c" (fromList [("bb",False),("cc",True)])
Just ("cc",True)
>>> lookupGE "cc" (fromList [("bb",False),("cc",True)])
Just ("cc",True)
>>> lookupGE "z" (fromList [("bb",False),("cc",True)])
Nothing

Construction

empty :: TextMap v Source #

\(\mathcal{O}(1)\). An empty TextMap.

singleton :: Key -> v -> TextMap v Source #

\(\mathcal{O}(1)\). Construct map containing a single entry.

>>> toList (singleton "sa" LT)
[("sa",LT)]

fromList :: [(Key, v)] -> TextMap v Source #

\(\mathcal{O}(n \log n)\). Construct map from list of key/value pairs.

>>> toList (fromList [("Hey",GT),("Jude",EQ),("Hey",LT),("Law",EQ),("Hey",EQ),("",EQ)])
[("",EQ),("Hey",EQ),("Jude",EQ),("Law",EQ)]

fromDistinctAscList :: [(Key, v)] -> TextMap v Source #

\(\mathcal{O}(n)\). Construct map from list with distinct keys in ascending order.

NOTE: If the input list is not strictly ascending, an error is thrown.

fromMap :: Map Key v -> TextMap v Source #

\(\mathcal{O}(n)\). Convert Map to TextMap.

Deconstruction

toList :: TextMap v -> [(Key, v)] Source #

\(\mathcal{O}(n)\). list all key/value pairs of the map in ascending order of their keys.

>>> toList (fromList [("Hey",GT),("Jude",EQ),("Hey",LT),("Law",EQ),("Hey",EQ),("",EQ)])
[("",EQ),("Hey",EQ),("Jude",EQ),("Law",EQ)]

toMap :: TextMap v -> Map Key v Source #

\(\mathcal{O}(n)\). Convert TextMap to Map.

Traversals

map :: (v -> w) -> TextMap v -> TextMap w Source #

\(\mathcal{O}(n)\). Apply function to values in map.

>>> toList (map not (fromList [("a",True),("b",False),("a",False)]))
[("a",True),("b",True)]

This is a specialised version of fmap.