aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/coll/dict.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/data/coll/dict.lux62
1 files changed, 31 insertions, 31 deletions
diff --git a/stdlib/source/lux/data/coll/dict.lux b/stdlib/source/lux/data/coll/dict.lux
index cee6a83fc..0273dc852 100644
--- a/stdlib/source/lux/data/coll/dict.lux
+++ b/stdlib/source/lux/data/coll/dict.lux
@@ -97,13 +97,13 @@
## which is 1/4 of the branching factor (or a left-shift 2).
(def: demotion-threshold
Nat
- (bit;shift-left (n.- +2 branching-exponent) +1))
+ (bit;shift-left (n/- +2 branching-exponent) +1))
## The threshold on which #Base nodes are promoted to #Hierarchy nodes,
## which is 1/2 of the branching factor (or a left-shift 1).
(def: promotion-threshold
Nat
- (bit;shift-left (n.- +1 branching-exponent) +1))
+ (bit;shift-left (n/- +1 branching-exponent) +1))
## The size of hierarchy-nodes, which is 2^(branching-exponent).
(def: hierarchy-nodes-size
@@ -120,12 +120,12 @@
(def: (insert! idx value old-array)
(All [a] (-> Index a (Array a) (Array a)))
(let [old-size (array;size old-array)]
- (|> ## (array;new (n.inc old-size))
+ (|> ## (array;new (n/inc old-size))
(: (Array ($ +0))
- (array;new (n.inc old-size)))
+ (array;new (n/inc old-size)))
(array;copy idx +0 old-array +0)
(array;write idx value)
- (array;copy (n.- idx old-size) idx old-array (n.inc idx)))))
+ (array;copy (n/- idx old-size) idx old-array (n/inc idx)))))
## Creates a copy of an array with an index set to a particular value.
(def: (update! idx value array)
@@ -140,23 +140,23 @@
## Shrinks a copy of the array by removing the space at index.
(def: (remove! idx array)
(All [a] (-> Index (Array a) (Array a)))
- (let [new-size (n.dec (array;size array))]
+ (let [new-size (n/dec (array;size array))]
(|> (array;new new-size)
(array;copy idx +0 array +0)
- (array;copy (n.- idx new-size) (n.inc idx) array idx))))
+ (array;copy (n/- idx new-size) (n/inc idx) array idx))))
## Given a top-limit for indices, produces all indices in [0, R).
(def: indices-for
(-> Nat (List Index))
- (|>. n.dec (list;n.range +0)))
+ (|>. n/dec (list;n/range +0)))
## Increases the level-shift by the branching-exponent, to explore
## levels further down the tree.
(def: level-up
(-> Level Level)
- (n.+ branching-exponent))
+ (n/+ branching-exponent))
-(def: hierarchy-mask BitMap (n.dec hierarchy-nodes-size))
+(def: hierarchy-mask BitMap (n/dec hierarchy-nodes-size))
## Gets the branching-factor sized section of the hash corresponding
## to a particular level, and uses that as an index into the array.
@@ -177,12 +177,12 @@
(def: (bit-position-is-set? bit bitmap)
(-> BitPosition BitMap Bool)
- (not (n.= clean-bitmap (bit;and bit bitmap))))
+ (not (n/= clean-bitmap (bit;and bit bitmap))))
## Figures out whether a bitmap only contains a single bit-position.
(def: only-bit-position?
(-> BitPosition BitMap Bool)
- n.=)
+ n/=)
(def: (set-bit-position bit bitmap)
(-> BitPosition BitMap BitMap)
@@ -203,7 +203,7 @@
## associated with it.
(def: bit-position-mask
(-> BitPosition BitMap)
- n.dec)
+ n/dec)
## The index on the base array, based on it's bit-position.
(def: (base-index bit-position bitmap)
@@ -227,16 +227,16 @@
(let [[bitmap base] node]
(case (array;read idx h-array)
#;None [insertion-idx node]
- (#;Some sub-node) (if (n.= except-idx idx)
+ (#;Some sub-node) (if (n/= except-idx idx)
[insertion-idx node]
- [(n.inc insertion-idx)
+ [(n/inc insertion-idx)
[(set-bit-position (->bit-position idx) bitmap)
(array;write insertion-idx (#;Left sub-node) base)]])
)))
[+0 [clean-bitmap
- ## (array;new (n.dec h-size))
+ ## (array;new (n/dec h-size))
(: (Base ($ +0) ($ +1))
- (array;new (n.dec h-size)))
+ (array;new (n/dec h-size)))
]]
(list;indices (array;size h-array)))))
@@ -253,7 +253,7 @@
(product;right (list/fold (function [hierarchy-idx (^@ default [base-idx h-array])]
(if (bit-position-is-set? (->bit-position hierarchy-idx)
bitmap)
- [(n.inc base-idx)
+ [(n/inc base-idx)
(case (array;read base-idx base)
(#;Some (#;Left sub-node))
(array;write hierarchy-idx sub-node h-array)
@@ -297,14 +297,14 @@
## [_size sub-node]
## _
- ## [(n.inc _size) empty])
+ ## [(n/inc _size) empty])
[_size' sub-node] (: [Nat (Node ($ +0) ($ +1))]
(case (array;read idx hierarchy)
(#;Some sub-node)
[_size sub-node]
_
- [(n.inc _size) empty]))
+ [(n/inc _size) empty]))
]
(#Hierarchy _size'
(update! idx (put' (level-up level) hash key val Hash<k> sub-node)
@@ -334,7 +334,7 @@
## Otherwise, I compare the hashes of the keys.
(#Base bitmap (update! idx
(#;Left (let [hash' (:: Hash<k> hash key')]
- (if (n.= hash hash')
+ (if (n/= hash hash')
## If the hashes are
## the same, a new
## #Collisions node
@@ -357,10 +357,10 @@
## However, if the BitPosition has not been used yet, I check
## whether this #Base node is ready for a promotion.
(let [base-count (bitmap-size bitmap)]
- (if (n.>= promotion-threshold base-count)
+ (if (n/>= promotion-threshold base-count)
## If so, I promote it to a #Hierarchy node, and add the new
## KV-pair as a singleton node to it.
- (#Hierarchy (n.inc base-count)
+ (#Hierarchy (n/inc base-count)
(|> (promote-base put' Hash<k> level bitmap base)
(array;write (level-index level hash)
(put' (level-up level) hash key val Hash<k> empty))))
@@ -371,7 +371,7 @@
## For #Collisions nodes, I compare the hashes.
(#Collisions _hash _colls)
- (if (n.= hash _hash)
+ (if (n/= hash _hash)
## If they're equal, that means the new KV contributes to the
## collisions.
(case (collision-index Hash<k> key _colls)
@@ -415,11 +415,11 @@
## But if the sub-removal yielded an empty sub-node...
(if (empty?' sub-node')
## Check if it's due time for a demotion.
- (if (n.<= demotion-threshold h-size)
+ (if (n/<= demotion-threshold h-size)
## If so, perform it.
(#Base (demote-hierarchy idx [h-size h-array]))
## Otherwise, just clear the space.
- (#Hierarchy (n.dec h-size) (vacant! idx h-array)))
+ (#Hierarchy (n/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)))))))
@@ -477,7 +477,7 @@
## But if so, then check the size of the collisions list.
(#;Some idx)
- (if (n.= +1 (array;size _colls))
+ (if (n/= +1 (array;size _colls))
## If there's only one left, then removing it leaves us with
## an empty node.
empty
@@ -522,10 +522,10 @@
(All [k v] (-> (Node k v) Nat))
(case node
(#Hierarchy _size hierarchy)
- (array/fold n.+ +0 (array/map size' hierarchy))
+ (array/fold n/+ +0 (array/map size' hierarchy))
(#Base _ base)
- (array/fold n.+ +0 (array/map (function [sub-node']
+ (array/fold n/+ +0 (array/map (function [sub-node']
(case sub-node'
(#;Left sub-node) (size' sub-node)
(#;Right _) +1))
@@ -614,7 +614,7 @@
(def: #export empty?
(All [k v] (-> (Dict k v) Bool))
- (|>. size (n.= +0)))
+ (|>. size (n/= +0)))
(def: #export (entries dict)
(All [k v] (-> (Dict k v) (List [k v])))
@@ -685,7 +685,7 @@
## [Structures]
(struct: #export (Eq<Dict> Eq<v>) (All [k v] (-> (Eq v) (Eq (Dict k v))))
(def: (= test subject)
- (and (n.= (size test)
+ (and (n/= (size test)
(size subject))
(list;every? (function [k]
(case [(get k test) (get k subject)]