aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/dictionary.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data/collection/dictionary.lux')
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux114
1 files changed, 57 insertions, 57 deletions
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index e86eb437b..3d0e729ce 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -139,7 +139,7 @@
(array.copy! (n.- idx old_size) idx old_array (inc idx)))))
... Creates a copy of an array with an index set to a particular value.
-(def: (update! idx value array)
+(def: (revised! idx value array)
(All [a] (-> Index a (Array a) (Array a)))
(|> array array.clone (array.write! idx value)))
@@ -149,7 +149,7 @@
(|> array array.clone (array.delete! idx)))
... Shrinks a copy of the array by removing the space at index.
-(def: (remove! idx array)
+(def: (lacks! idx array)
(All [a] (-> Index (Array a) (Array a)))
(let [new_size (dec (array.size array))]
(|> (array.empty new_size)
@@ -254,7 +254,7 @@
(List Index)
(list.indices hierarchy_nodes_size))
-(def: (promotion put' key_hash level bitmap base)
+(def: (promotion has' key_hash level bitmap base)
(All [k v]
(-> (-> Level Hash_Code k v (Hash k) (Node k v) (Node k v))
(Hash k) Level
@@ -270,7 +270,7 @@
(#.Some (#.Right [key' val']))
(array.write! hierarchy_idx
- (put' (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
+ (has' (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
h_array)
#.None
@@ -292,7 +292,7 @@
_
#0)))
-(def: (put' level hash key val key_hash node)
+(def: (has' level hash key val key_hash node)
(All [k v] (-> Level Hash_Code k v (Hash k) (Node k v) (Node k v)))
(case node
... For #Hierarchy nodes, check whether one can add the element to
@@ -306,8 +306,8 @@
_
[(inc _size) empty_node])]
(#Hierarchy _size'
- (update! idx (put' (level_up level) hash key val key_hash sub_node)
- hierarchy)))
+ (revised! idx (has' (level_up level) hash key val key_hash sub_node)
+ hierarchy)))
... For #Base nodes, check if the corresponding Bit_Position has
... already been used.
@@ -319,35 +319,35 @@
(case (array.read idx base)
... If it's being used by a node, add the KV to it.
(#.Some (#.Left sub_node))
- (let [sub_node' (put' (level_up level) hash key val key_hash sub_node)]
- (#Base bitmap (update! idx (#.Left sub_node') base)))
+ (let [sub_node' (has' (level_up level) hash key val key_hash sub_node)]
+ (#Base bitmap (revised! idx (#.Left sub_node') base)))
... Otherwise, if it's being used by a KV, compare the keys.
(#.Some (#.Right key' val'))
(if (\ key_hash = key key')
... If the same key is found, replace the value.
- (#Base bitmap (update! idx (#.Right key val) base))
+ (#Base bitmap (revised! idx (#.Right key val) base))
... Otherwise, compare the hashes of the keys.
- (#Base bitmap (update! idx
- (#.Left (let [hash' (\ key_hash hash key')]
- (if (n.= hash hash')
- ... If the hashes are
- ... the same, a new
- ... #Collisions node
- ... is added.
- (#Collisions hash (|> (array.empty 2)
- (array.write! 0 [key' val'])
- (array.write! 1 [key val])))
- ... Otherwise, one can
- ... just keep using
- ... #Base nodes, so
- ... add both KV-pairs
- ... to the empty one.
- (let [next_level (level_up level)]
- (|> empty_node
- (put' next_level hash' key' val' key_hash)
- (put' next_level hash key val key_hash))))))
- base)))
+ (#Base bitmap (revised! idx
+ (#.Left (let [hash' (\ key_hash hash key')]
+ (if (n.= hash hash')
+ ... If the hashes are
+ ... the same, a new
+ ... #Collisions node
+ ... is added.
+ (#Collisions hash (|> (array.empty 2)
+ (array.write! 0 [key' val'])
+ (array.write! 1 [key val])))
+ ... Otherwise, one can
+ ... just keep using
+ ... #Base nodes, so
+ ... add both KV-pairs
+ ... to the empty one.
+ (let [next_level (level_up level)]
+ (|> empty_node
+ (has' next_level hash' key' val' key_hash)
+ (has' next_level hash key val key_hash))))))
+ base)))
#.None
(undefined)))
@@ -359,9 +359,9 @@
... KV-pair as a singleton node to it.
(#Hierarchy (inc base_count)
(|> base
- (promotion put' key_hash level bitmap)
+ (promotion has' key_hash level bitmap)
(array.write! (level_index level hash)
- (put' (level_up level) hash key val key_hash empty_node))))
+ (has' (level_up level) hash key val key_hash empty_node))))
... Otherwise, just resize the #Base node to accommodate the
... new KV-pair.
(#Base (with_bit_position bit bitmap)
@@ -376,7 +376,7 @@
... If the key was already present in the collisions-list, its
... value gets updated.
(#.Some coll_idx)
- (#Collisions _hash (update! coll_idx [key val] _colls))
+ (#Collisions _hash (revised! coll_idx [key val] _colls))
... Otherwise, the KV-pair is added to the collisions-list.
#.None
@@ -386,10 +386,10 @@
(|> (#Base (level_bit_position level _hash)
(|> (array.empty 1)
(array.write! 0 (#.Left node))))
- (put' level hash key val key_hash)))
+ (has' level hash key val key_hash)))
))
-(def: (remove' level hash key key_hash node)
+(def: (lacks' level hash key key_hash node)
(All [k v] (-> Level Hash_Code k (Hash k) (Node k v) (Node k v)))
(case node
... For #Hierarchy nodes, find out if there's a valid sub-node for
@@ -403,7 +403,7 @@
... But if there is, try to remove the key from the sub-node.
(#.Some sub_node)
- (let [sub_node' (remove' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
... Then check if a removal was actually done.
(if (is? sub_node sub_node')
... If not, then there's nothing to change here either.
@@ -418,7 +418,7 @@
(#Hierarchy (dec h_size) (vacant! idx h_array)))
... But if the sub_removal yielded a non_empty node, then
... just update the hiearchy branch.
- (#Hierarchy h_size (update! idx sub_node' h_array)))))))
+ (#Hierarchy h_size (revised! idx sub_node' h_array)))))))
... For #Base nodes, check whether the Bit_Position is set.
(#Base bitmap base)
@@ -429,7 +429,7 @@
... If set, check if it's a sub_node, and remove the KV
... from it.
(#.Some (#.Left sub_node))
- (let [sub_node' (remove' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
... Verify that it was removed.
(if (is? sub_node sub_node')
... If not, there's also nothing to change here.
@@ -443,11 +443,11 @@
... But if not, then just unset the position and
... remove the node.
(#Base (without_bit_position bit bitmap)
- (remove! idx base)))
+ (lacks! idx base)))
... But, if it did not come out empty, then the
... position is kept, and the node gets updated.
(#Base bitmap
- (update! idx (#.Left sub_node') base)))))
+ (revised! idx (#.Left sub_node') base)))))
... If, however, there was a KV-pair instead of a sub-node.
(#.Some (#.Right [key' val']))
@@ -455,7 +455,7 @@
(if (\ key_hash = key key')
... If so, remove the KV-pair and unset the Bit_Position.
(#Base (without_bit_position bit bitmap)
- (remove! idx base))
+ (lacks! idx base))
... Otherwise, there's nothing to remove.
node)
@@ -478,7 +478,7 @@
... an empty node.
empty_node
... Otherwise, just shrink the array by removing the KV-pair.
- (#Collisions _hash (remove! idx _colls))))
+ (#Collisions _hash (lacks! idx _colls))))
))
(def: (get' level hash key key_hash node)
@@ -570,15 +570,15 @@
{#hash key_hash
#root empty_node})
-(def: .public (put key val dict)
+(def: .public (has key val dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (put' root_level (\ key_hash hash key) key val key_hash node)]))
+ [key_hash (has' root_level (\ key_hash hash key) key val key_hash node)]))
-(def: .public (remove key dict)
+(def: .public (lacks key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (remove' root_level (\ key_hash hash key) key key_hash node)]))
+ [key_hash (lacks' root_level (\ key_hash hash key) key key_hash node)]))
(def: .public (get key dict)
(All [k v] (-> k (Dictionary k v) (Maybe v)))
@@ -597,10 +597,10 @@
{#.doc "Only puts the KV-pair if the key is not already present."}
(All [k v] (-> k v (Dictionary k v) (Try (Dictionary k v))))
(case (get key dict)
- #.None (#try.Success (put key val dict))
+ #.None (#try.Success (has key val dict))
(#.Some _) (exception.except ..key_already_exists [])))
-(def: .public (update key f dict)
+(def: .public (revised key f dict)
{#.doc "Transforms the value located at key (if available), using the given function."}
(All [k v] (-> k (-> v v) (Dictionary k v) (Dictionary k v)))
(case (get key dict)
@@ -608,13 +608,13 @@
dict
(#.Some val)
- (put key (f val) dict)))
+ (has key (f val) dict)))
(def: .public (upsert key default f dict)
{#.doc (example "Updates the value at the key; if it exists."
"Otherwise, puts a value by applying the function to a default.")}
(All [k v] (-> k v (-> v v) (Dictionary k v) (Dictionary k v)))
- (..put key
+ (..has key
(f (maybe.else default
(..get key dict)))
dict))
@@ -634,7 +634,7 @@
(def: .public (of_list key_hash kvs)
(All [k v] (-> (Hash k) (List [k v]) (Dictionary k v)))
(list\fold (function (_ [k v] dict)
- (..put k v dict))
+ (..has k v dict))
(empty key_hash)
kvs))
@@ -654,7 +654,7 @@
{#.doc (example "Merges 2 dictionaries."
"If any collisions with keys occur, the values of dict2 will overwrite those of dict1.")}
(All [k v] (-> (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list\fold (function (_ [key val] dict) (put key val dict))
+ (list\fold (function (_ [key val] dict) (has key val dict))
dict1
(entries dict2)))
@@ -665,10 +665,10 @@
(list\fold (function (_ [key val2] dict)
(case (get key dict)
#.None
- (put key val2 dict)
+ (has key val2 dict)
(#.Some val1)
- (put key (f val2 val1) dict)))
+ (has key (f val2 val1) dict)))
dict1
(entries dict2)))
@@ -681,8 +681,8 @@
(#.Some val)
(|> dict
- (remove from_key)
- (put to_key val))))
+ (lacks from_key)
+ (has to_key val))))
(def: .public (sub keys dict)
{#.doc "A sub-dictionary, with only the specified keys."}
@@ -691,7 +691,7 @@
(list\fold (function (_ key new_dict)
(case (get key dict)
#.None new_dict
- (#.Some val) (put key val new_dict)))
+ (#.Some val) (has key val new_dict)))
(empty key_hash)
keys)))