Copyright | (c) Adam Wagner 2017 |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Identifiers for ListLike values.
Example usage:
>>>
xs = fromList ["foo", "bar", "baz", "foo"]
>>>
lookupId xs "baz"
Just 2>>>
lookupKey xs 2
Just "baz"
- data Identifiers i n u
- empty :: Identifiers i n u
- fromList :: (ListLike n u, Eq u, Integral i) => [n] -> Identifiers i n u
- combine :: (ListLike n u, Integral i, Eq u) => Identifiers i n u -> Identifiers i n u -> (Identifiers i n u, Map i i)
- insert :: (ListLike n u, Eq u, Integral i) => Identifiers i n u -> n -> Identifiers i n u
- insertMany :: (ListLike n u, Eq u, Integral i) => Identifiers i n u -> [n] -> Identifiers i n u
- size :: Identifiers i n u -> Int
- toList :: Identifiers i n u -> [n]
- lookupId :: (Eq u, ListLike n u) => Identifiers i n u -> n -> Maybe i
- lookupKey :: Integral i => Identifiers i n u -> i -> Maybe n
- lookupKeys :: Integral i => Identifiers i n u -> [i] -> [n]
- unsafeLookupId :: (ListLike n u, Eq u) => Identifiers i n u -> n -> i
- unsafeLookupKey :: Integral i => Identifiers i n u -> i -> n
- (!) :: Integral i => Identifiers i n u -> i -> n
- prop_hasId :: String -> Bool
- prop_stableId :: String -> Bool
- prop_keyRetrieval :: [String] -> Bool
- prop_keyRetrievalUnsafe :: [String] -> Bool
- prop_idempotent :: String -> Bool
- prop_stableCombine :: [String] -> [String] -> Bool
- prop_properMigration :: [String] -> [String] -> Bool
Documentation
data Identifiers i n u Source #
(Eq n, Eq i, Eq u) => Eq (Identifiers i n u) Source # | |
Show n => Show (Identifiers i n u) Source # | |
(Binary n, ListLike n u, Integral i, Eq u) => Binary (Identifiers i n u) Source # | |
(Serialize n, ListLike n u, Integral i, Eq u) => Serialize (Identifiers i n u) Source # | |
(NFData i, NFData n, NFData u) => NFData (Identifiers i n u) Source # | |
Construction
empty :: Identifiers i n u Source #
The empty Identifiers
fromList :: (ListLike n u, Eq u, Integral i) => [n] -> Identifiers i n u Source #
New Identifiers from list
combine :: (ListLike n u, Integral i, Eq u) => Identifiers i n u -> Identifiers i n u -> (Identifiers i n u, Map i i) Source #
Combine two identifier sets into one. Because the ids will change while combining two sets, a map is also returned that identifies the new location of old ids for the second set passed in.
Insertion
insert :: (ListLike n u, Eq u, Integral i) => Identifiers i n u -> n -> Identifiers i n u Source #
Insert item into set (given it a new id)
insertMany :: (ListLike n u, Eq u, Integral i) => Identifiers i n u -> [n] -> Identifiers i n u Source #
Insert many items into set
Info
size :: Identifiers i n u -> Int Source #
Number of items in Identifiers value
Extraction
toList :: Identifiers i n u -> [n] Source #
New List from Identifiers
Lookups
lookupId :: (Eq u, ListLike n u) => Identifiers i n u -> n -> Maybe i Source #
Find id for given value
lookupKeys :: Integral i => Identifiers i n u -> [i] -> [n] Source #
Given many ids, return many keys. Ids with no associated values will be omitted from the resulting list.
unsafeLookupId :: (ListLike n u, Eq u) => Identifiers i n u -> n -> i Source #
Find numeric id for given value. Will error when the value is not a member of the Identifiers map.
unsafeLookupKey :: Integral i => Identifiers i n u -> i -> n Source #
Find id for given value. Will error when the id has no associated value.
(!) :: Integral i => Identifiers i n u -> i -> n Source #
Infix version of unsafeLookupKey
Properties
prop_hasId :: String -> Bool Source #
Items inserted are given ids
prop_stableId :: String -> Bool Source #
Inserted items have stable ids
prop_keyRetrieval :: [String] -> Bool Source #
Given id can be used to fetch inserted item
prop_keyRetrievalUnsafe :: [String] -> Bool Source #
Given id can be used to fetch inserted item
prop_idempotent :: String -> Bool Source #
Inserting something more than once does not change the set