Copyright | © 2017 Herbert Valerio Riedel |
---|---|
License | GPLv3 |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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.
- data TextMap v
- type Key = ShortText
- size :: TextMap v -> Int
- null :: TextMap v -> Bool
- member :: Key -> TextMap v -> Bool
- lookup :: Key -> TextMap v -> Maybe v
- (!?) :: TextMap v -> Key -> Maybe v
- findWithDefault :: v -> Key -> TextMap v -> v
- lookupMin :: TextMap v -> Maybe (Key, v)
- lookupMax :: TextMap v -> Maybe (Key, v)
- lookupLE :: Key -> TextMap v -> Maybe (Key, v)
- lookupGE :: Key -> TextMap v -> Maybe (Key, v)
- empty :: TextMap v
- singleton :: Key -> v -> TextMap v
- fromList :: [(Key, v)] -> TextMap v
- fromDistinctAscList :: [(Key, v)] -> TextMap v
- fromMap :: Map Key v -> TextMap v
- toList :: TextMap v -> [(Key, v)]
- toMap :: TextMap v -> Map Key v
- map :: (v -> w) -> TextMap v -> TextMap w
Documentation
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.
Functor TextMap Source # | |
Foldable TextMap Source # | |
Traversable TextMap Source # | |
IsList (TextMap v) Source # | |
Eq v => Eq (TextMap v) Source # | |
Ord v => Ord (TextMap v) Source # | |
Read v => Read (TextMap v) Source # | |
Show v => Show (TextMap v) Source # | |
NFData v => NFData (TextMap v) Source # | |
Hashable v => Hashable (TextMap v) Source # | |
type Item (TextMap v) Source # | |
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
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
findWithDefault :: v -> Key -> TextMap v -> v Source #
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
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.
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)]