aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/dictionary
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux144
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux52
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/plist.lux14
3 files changed, 105 insertions, 105 deletions
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index bdfc2638a..6b0aff962 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -12,8 +12,8 @@
[data
["[0]" product]
[collection
- ["[0]" list ("[1]\[0]" mix functor monoid)]
- ["[0]" array {"+" [Array]} ("[1]\[0]" functor mix)]]]
+ ["[0]" list ("[1]#[0]" mix functor monoid)]
+ ["[0]" array {"+" [Array]} ("[1]#[0]" functor mix)]]]
[math
["[0]" number
["n" nat]
@@ -131,7 +131,7 @@
... Expands a copy of the array, to have 1 extra slot, which is used
... for storing the value.
-(def: (array\has idx value old_array)
+(def: (array#has idx value old_array)
(All (_ a) (-> Index a (Array a) (Array a)))
(let [old_size (array.size old_array)]
(|> (array.empty (++ old_size))
@@ -140,19 +140,19 @@
(array.copy! (n.- idx old_size) idx old_array (++ idx)))))
... Creates a copy of an array with an index set to a particular value.
-(def: (array\revised idx value array)
+(def: (array#revised idx value array)
(All (_ a) (-> Index a (Array a) (Array a)))
(|> array array.clone (array.write! idx value)))
... Creates a clone of the array, with an empty position at index.
-(def: (array\clear idx array)
+(def: (array#clear idx array)
(All (_ a) (-> Index (Array a) (Array a)))
(|> array
array.clone
(array.delete! idx)))
... Shrinks a copy of the array by removing the space at index.
-(def: (array\lacks idx array)
+(def: (array#lacks idx array)
(All (_ a) (-> Index (Array a) (Array a)))
(let [new_size (-- (array.size array))]
(|> (array.empty new_size)
@@ -228,16 +228,16 @@
... Produces the index of a KV-pair within a #Collisions node.
(def: (collision_index key_hash key colls)
(All (_ k v) (-> (Hash k) k (Collisions k v) (Maybe Index)))
- (\ maybe.monad each product.left
+ (# maybe.monad each product.left
(array.example+ (function (_ idx [key' val'])
- (\ key_hash = key key'))
+ (# key_hash = key key'))
colls)))
... When #Hierarchy nodes grow too small, they're demoted to #Base
... nodes to save space.
(def: (demotion except_idx [h_size h_array])
(All (_ k v) (-> Index (Hierarchy k v) [Bit_Map (Base k v)]))
- (product.right (list\mix (function (_ idx [insertion_idx node])
+ (product.right (list#mix (function (_ idx [insertion_idx node])
(let [[bitmap base] node]
(case (array.read! idx h_array)
{.#None} [insertion_idx node]
@@ -257,13 +257,13 @@
(List Index)
(list.indices hierarchy_nodes_size))
-(def: (promotion node\has key_hash level bitmap base)
+(def: (promotion node#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
Bit_Map (Base k v)
(Array (Node k v))))
- (product.right (list\mix (function (_ hierarchy_idx (^@ default [base_idx h_array]))
+ (product.right (list#mix (function (_ hierarchy_idx (^@ default [base_idx h_array]))
(if (with_bit_position? (to_bit_position hierarchy_idx)
bitmap)
[(++ base_idx)
@@ -273,7 +273,7 @@
{.#Some {.#Right [key' val']}}
(array.write! hierarchy_idx
- (node\has (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
+ (node#has (level_up level) (# key_hash hash key') key' val' key_hash empty_node)
h_array)
{.#None}
@@ -286,7 +286,7 @@
... All empty nodes look the same (a #Base node with clean bitmap is
... used).
... So, this test is introduced to detect them.
-(def: (node\empty? node)
+(def: (node#empty? node)
(All (_ k v) (-> (Node k v) Bit))
(`` (case node
{#Base (~~ (static ..clean_bitmap)) _}
@@ -295,7 +295,7 @@
_
#0)))
-(def: (node\has level hash key val key_hash node)
+(def: (node#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
@@ -309,7 +309,7 @@
_
[(++ _size) empty_node])]
{#Hierarchy _size'
- (array\revised idx (node\has (level_up level) hash key val key_hash sub_node)
+ (array#revised idx (node#has (level_up level) hash key val key_hash sub_node)
hierarchy)})
... For #Base nodes, check if the corresponding Bit_Position has
@@ -322,17 +322,17 @@
(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' (node\has (level_up level) hash key val key_hash sub_node)]
- {#Base bitmap (array\revised idx {.#Left sub_node'} base)})
+ (let [sub_node' (node#has (level_up level) hash key val key_hash sub_node)]
+ {#Base bitmap (array#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 (# key_hash = key key')
... If the same key is found, replace the value.
- {#Base bitmap (array\revised idx {.#Right key val} base)}
+ {#Base bitmap (array#revised idx {.#Right key val} base)}
... Otherwise, compare the hashes of the keys.
- {#Base bitmap (array\revised idx
- {.#Left (let [hash' (\ key_hash hash key')]
+ {#Base bitmap (array#revised idx
+ {.#Left (let [hash' (# key_hash hash key')]
(if (n.= hash hash')
... If the hashes are
... the same, a new
@@ -348,8 +348,8 @@
... to the empty one.
(let [next_level (level_up level)]
(|> empty_node
- (node\has next_level hash' key' val' key_hash)
- (node\has next_level hash key val key_hash)))))}
+ (node#has next_level hash' key' val' key_hash)
+ (node#has next_level hash key val key_hash)))))}
base)})
{.#None}
@@ -361,14 +361,14 @@
... If so, resize the #Base node to accommodate the
... new KV-pair.
{#Base (with_bit_position bit bitmap)
- (array\has (base_index bit bitmap) {.#Right [key val]} base)}
+ (array#has (base_index bit bitmap) {.#Right [key val]} base)}
... Otherwise, promote it to a #Hierarchy node, and add the new
... KV-pair as a singleton node to it.
{#Hierarchy (++ base_count)
(|> base
- (promotion node\has key_hash level bitmap)
+ (promotion node#has key_hash level bitmap)
(array.write! (level_index level hash)
- (node\has (level_up level) hash key val key_hash empty_node)))}))))
+ (node#has (level_up level) hash key val key_hash empty_node)))}))))
... For #Collisions nodes, compare the hashes.
{#Collisions _hash _colls}
@@ -379,20 +379,20 @@
... If the key was already present in the collisions-list, its
... value gets updated.
{.#Some coll_idx}
- {#Collisions _hash (array\revised coll_idx [key val] _colls)}
+ {#Collisions _hash (array#revised coll_idx [key val] _colls)}
... Otherwise, the KV-pair is added to the collisions-list.
{.#None}
- {#Collisions _hash (array\has (array.size _colls) [key val] _colls)})
+ {#Collisions _hash (array#has (array.size _colls) [key val] _colls)})
... If the hashes are not equal, create a new #Base node that
... contains the old #Collisions node, plus the new KV-pair.
(|> {#Base (level_bit_position level _hash)
(|> (array.empty 1)
(array.write! 0 {.#Left node}))}
- (node\has level hash key val key_hash)))
+ (node#has level hash key val key_hash)))
))
-(def: (node\lacks level hash key key_hash node)
+(def: (node#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
@@ -406,22 +406,22 @@
... But if there is, try to remove the key from the sub-node.
{.#Some sub_node}
- (let [sub_node' (node\lacks (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (node#lacks (level_up level) hash key key_hash sub_node)]
... Then check if a removal was actually done.
(if (same? sub_node sub_node')
... If not, then there's nothing to change here either.
node
... But if the sub_removal yielded an empty sub_node...
- (if (node\empty? sub_node')
+ (if (node#empty? sub_node')
... Check if it's due time for a demotion.
(if (n.> demotion_threshold h_size)
... If so, just clear the space.
- {#Hierarchy (-- h_size) (array\clear idx h_array)}
+ {#Hierarchy (-- h_size) (array#clear idx h_array)}
... Otherwise, perform it.
{#Base (demotion idx [h_size h_array])})
... But if the sub_removal yielded a non_empty node, then
... just update the hiearchy branch.
- {#Hierarchy h_size (array\revised idx sub_node' h_array)})))))
+ {#Hierarchy h_size (array#revised idx sub_node' h_array)})))))
... For #Base nodes, check whether the Bit_Position is set.
{#Base bitmap base}
@@ -432,13 +432,13 @@
... If set, check if it's a sub_node, and remove the KV
... from it.
{.#Some {.#Left sub_node}}
- (let [sub_node' (node\lacks (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (node#lacks (level_up level) hash key key_hash sub_node)]
... Verify that it was removed.
(if (same? sub_node sub_node')
... If not, there's also nothing to change here.
node
... But if it came out empty...
- (if (node\empty? sub_node')
+ (if (node#empty? sub_node')
...# ... figure out whether that's the only position left.
(if (only_bit_position? bit bitmap)
... If so, removing it leaves this node empty too.
@@ -446,19 +446,19 @@
... But if not, then just unset the position and
... remove the node.
{#Base (without_bit_position bit bitmap)
- (array\lacks idx base)})
+ (array#lacks idx base)})
... But, if it did not come out empty, then the
... position is kept, and the node gets updated.
{#Base bitmap
- (array\revised idx {.#Left sub_node'} base)})))
+ (array#revised idx {.#Left sub_node'} base)})))
... If, however, there was a KV-pair instead of a sub-node.
{.#Some {.#Right [key' val']}}
... Check if the keys match.
- (if (\ key_hash = key key')
+ (if (# key_hash = key key')
... If so, remove the KV-pair and unset the Bit_Position.
{#Base (without_bit_position bit bitmap)
- (array\lacks idx base)}
+ (array#lacks idx base)}
... Otherwise, there's nothing to remove.
node)
@@ -481,17 +481,17 @@
... an empty node.
empty_node
... Otherwise, just shrink the array by removing the KV-pair.
- {#Collisions _hash (array\lacks idx _colls)}))
+ {#Collisions _hash (array#lacks idx _colls)}))
))
-(def: (node\value level hash key key_hash node)
+(def: (node#value level hash key key_hash node)
(All (_ k v) (-> Level Hash_Code k (Hash k) (Node k v) (Maybe v)))
(case node
... For #Hierarchy nodes, just look-up the key on its children.
{#Hierarchy _size hierarchy}
(case (array.read! (level_index level hash) hierarchy)
{.#None} {.#None}
- {.#Some sub_node} (node\value (level_up level) hash key key_hash sub_node))
+ {.#Some sub_node} (node#value (level_up level) hash key key_hash sub_node))
... For #Base nodes, check the leaves, and recursively check the branches.
{#Base bitmap base}
@@ -499,10 +499,10 @@
(if (with_bit_position? bit bitmap)
(case (array.read! (base_index bit bitmap) base)
{.#Some {.#Left sub_node}}
- (node\value (level_up level) hash key key_hash sub_node)
+ (node#value (level_up level) hash key key_hash sub_node)
{.#Some {.#Right [key' val']}}
- (if (\ key_hash = key key')
+ (if (# key_hash = key key')
{.#Some val'}
{.#None})
@@ -512,21 +512,21 @@
... For #Collisions nodes, do a linear scan of all the known KV-pairs.
{#Collisions _hash _colls}
- (\ maybe.monad each product.right
- (array.example (|>> product.left (\ key_hash = key))
+ (# maybe.monad each product.right
+ (array.example (|>> product.left (# key_hash = key))
_colls))
))
-(def: (node\size node)
+(def: (node#size node)
(All (_ k v) (-> (Node k v) Nat))
(case node
{#Hierarchy _size hierarchy}
- (array\mix n.+ 0 (array\each node\size hierarchy))
+ (array#mix n.+ 0 (array#each node#size hierarchy))
{#Base _ base}
- (array\mix n.+ 0 (array\each (function (_ sub_node')
+ (array#mix n.+ 0 (array#each (function (_ sub_node')
(case sub_node'
- {.#Left sub_node} (node\size sub_node)
+ {.#Left sub_node} (node#size sub_node)
{.#Right _} 1))
base))
@@ -534,19 +534,19 @@
(array.size colls)
))
-(def: (node\entries node)
+(def: (node#entries node)
(All (_ k v) (-> (Node k v) (List [k v])))
(case node
{#Hierarchy _size hierarchy}
- (array\mix (function (_ sub_node tail) (list\composite (node\entries sub_node) tail))
+ (array#mix (function (_ sub_node tail) (list#composite (node#entries sub_node) tail))
{.#End}
hierarchy)
{#Base bitmap base}
- (array\mix (function (_ branch tail)
+ (array#mix (function (_ branch tail)
(case branch
{.#Left sub_node}
- (list\composite (node\entries sub_node) tail)
+ (list#composite (node#entries sub_node) tail)
{.#Right [key' val']}
{.#Item [key' val'] tail}))
@@ -554,7 +554,7 @@
base)
{#Collisions hash colls}
- (array\mix (function (_ [key' val'] tail) {.#Item [key' val'] tail})
+ (array#mix (function (_ [key' val'] tail) {.#Item [key' val'] tail})
{.#End}
colls)))
@@ -575,17 +575,17 @@
(def: .public (has key val dict)
(All (_ k v) (-> k v (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (node\has root_level (\ key_hash hash key) key val key_hash node)]))
+ [key_hash (node#has root_level (# key_hash hash key) key val key_hash node)]))
(def: .public (lacks key dict)
(All (_ k v) (-> k (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (node\lacks root_level (\ key_hash hash key) key key_hash node)]))
+ [key_hash (node#lacks root_level (# key_hash hash key) key key_hash node)]))
(def: .public (value key dict)
(All (_ k v) (-> k (Dictionary k v) (Maybe v)))
(let [[key_hash node] dict]
- (node\value root_level (\ key_hash hash key) key key_hash node)))
+ (node#value root_level (# key_hash hash key) key key_hash node)))
(def: .public (key? dict key)
(All (_ k v) (-> (Dictionary k v) k Bit))
@@ -619,7 +619,7 @@
(def: .public size
(All (_ k v) (-> (Dictionary k v) Nat))
- (|>> product.right ..node\size))
+ (|>> product.right ..node#size))
(def: .public empty?
(All (_ k v) (-> (Dictionary k v) Bit))
@@ -627,11 +627,11 @@
(def: .public entries
(All (_ k v) (-> (Dictionary k v) (List [k v])))
- (|>> product.right ..node\entries))
+ (|>> product.right ..node#entries))
(def: .public (of_list key_hash kvs)
(All (_ k v) (-> (Hash k) (List [k v]) (Dictionary k v)))
- (list\mix (function (_ [k v] dict)
+ (list#mix (function (_ [k v] dict)
(..has k v dict))
(empty key_hash)
kvs))
@@ -640,7 +640,7 @@
[(def: .public <name>
(All (_ k v) (-> (Dictionary k v) (List <side>)))
(|>> ..entries
- (list\mix (function (_ [k v] bundle)
+ (list#mix (function (_ [k v] bundle)
{.#Item <side> bundle})
{.#End})))]
@@ -650,13 +650,13 @@
(def: .public (merged dict2 dict1)
(All (_ k v) (-> (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list\mix (function (_ [key val] dict) (has key val dict))
+ (list#mix (function (_ [key val] dict) (has key val dict))
dict1
(entries dict2)))
(def: .public (merged_with f dict2 dict1)
(All (_ k v) (-> (-> v v v) (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list\mix (function (_ [key val2] dict)
+ (list#mix (function (_ [key val2] dict)
(case (value key dict)
{.#None}
(has key val2 dict)
@@ -680,14 +680,14 @@
(def: .public (sub keys dict)
(All (_ k v) (-> (List k) (Dictionary k v) (Dictionary k v)))
(let [[key_hash _] dict]
- (list\mix (function (_ key new_dict)
+ (list#mix (function (_ key new_dict)
(case (value key dict)
{.#None} new_dict
{.#Some val} (has key val new_dict)))
(empty key_hash)
keys)))
-(implementation: .public (equivalence (^open ",\[0]"))
+(implementation: .public (equivalence (^open ",#[0]"))
(All (_ k v) (-> (Equivalence v) (Equivalence (Dictionary k v))))
(def: (= reference subject)
@@ -696,7 +696,7 @@
(list.every? (function (_ [k rv])
(case (..value k subject)
{.#Some sv}
- (,\= rv sv)
+ (,#= rv sv)
_
#0))
@@ -708,10 +708,10 @@
(def: (each f fa)
(case fa
{#Hierarchy size hierarchy}
- {#Hierarchy size (array\each (each f) hierarchy)}
+ {#Hierarchy size (array#each (each f) hierarchy)}
{#Base bitmap base}
- {#Base bitmap (array\each (function (_ either)
+ {#Base bitmap (array#each (function (_ either)
(case either
{.#Left fa'}
{.#Left (each f fa')}
@@ -721,7 +721,7 @@
base)}
{#Collisions hash collisions}
- {#Collisions hash (array\each (function (_ [k v])
+ {#Collisions hash (array#each (function (_ [k v])
[k (f v)])
collisions)})))
@@ -729,4 +729,4 @@
(All (_ k) (Functor (Dictionary k)))
(def: (each f fa)
- (revised@ #root (\ ..node_functor each f) fa)))
+ (revised@ #root (# ..node_functor each f) fa)))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 1fc2e3ea5..1b02f03a3 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -10,7 +10,7 @@
[data
["p" product]
[collection
- ["[0]" list ("[1]\[0]" monoid mix)]]]
+ ["[0]" list ("[1]#[0]" monoid mix)]]]
[math
[number
["n" nat]]]]])
@@ -58,7 +58,7 @@
... TODO: Must improve it as soon as bug is fixed.
(def: .public (value key dict)
(All (_ k v) (-> k (Dictionary k v) (Maybe v)))
- (let [... (^open "_\[0]") (value@ #&order dict)
+ (let [... (^open "_#[0]") (value@ #&order dict)
]
(loop [node (value@ #root dict)]
(case node
@@ -67,15 +67,15 @@
{.#Some node}
(let [node_key (value@ #key node)]
- (cond (\ dict = node_key key)
- ... (_\= node_key key)
+ (cond (# dict = node_key key)
+ ... (_#= node_key key)
{.#Some (value@ #value node)}
- (\ dict < node_key key)
- ... (_\< node_key key)
+ (# dict < node_key key)
+ ... (_#< node_key key)
(recur (value@ #left node))
- ... (_\> (value@ #key node) key)
+ ... (_#> (value@ #key node) key)
(recur (value@ #right node))))
))))
@@ -83,7 +83,7 @@
... TODO: Must improve it as soon as bug is fixed.
(def: .public (key? dict key)
(All (_ k v) (-> (Dictionary k v) k Bit))
- (let [... (^open "_\[0]") (value@ #&order dict)
+ (let [... (^open "_#[0]") (value@ #&order dict)
]
(loop [node (value@ #root dict)]
(case node
@@ -92,10 +92,10 @@
{.#Some node}
(let [node_key (value@ #key node)]
- (or (\ dict = node_key key)
- ... (_\= node_key key)
- (if (\ dict < node_key key)
- ... (_\< node_key key)
+ (or (# dict = node_key key)
+ ... (_#= node_key key)
+ (if (# dict < node_key key)
+ ... (_#< node_key key)
(recur (value@ #left node))
(recur (value@ #right node)))))))))
@@ -249,7 +249,7 @@
(def: .public (has key value dict)
(All (_ k v) (-> k v (Dictionary k v) (Dictionary k v)))
- (let [(^open "_\[0]") (value@ #&order dict)
+ (let [(^open "_#[0]") (value@ #&order dict)
root' (loop [?root (value@ #root dict)]
(case ?root
{.#None}
@@ -266,11 +266,11 @@
{.#Some (<add> (maybe.trusted outcome)
root)}))]
- [_\< #left ..with_left]
+ [_#< #left ..with_left]
[(order.> (value@ #&order dict)) #right ..with_right]
))
- ... (_\= reference key)
+ ... (_#= reference key)
{.#Some (with@ #value value root)}
)))
))]
@@ -355,7 +355,7 @@
{.#Some (right_balanced (value@ #key right)
(value@ #value right)
(value@ #right right>>left)
- (\ maybe.functor each reddened (value@ #right right)))})
+ (# maybe.functor each reddened (value@ #right right)))})
_
(panic! error_message))
@@ -382,7 +382,7 @@
(value@ #value left>>right)
{.#Some (left_balanced (value@ #key left)
(value@ #value left)
- (\ maybe.functor each reddened (value@ #left left))
+ (# maybe.functor each reddened (value@ #left left))
(value@ #left left>>right))}
{.#Some (black key value (value@ #right left>>right) ?right)})
@@ -472,7 +472,7 @@
(def: .public (lacks key dict)
(All (_ k v) (-> k (Dictionary k v) (Dictionary k v)))
- (let [(^open "_\[0]") (value@ #&order dict)
+ (let [(^open "_#[0]") (value@ #&order dict)
[?root found?] (loop [?root (value@ #root dict)]
(case ?root
{.#None}
@@ -481,11 +481,11 @@
{.#Some root}
(let [root_key (value@ #key root)
root_val (value@ #value root)]
- (if (_\= root_key key)
+ (if (_#= root_key key)
[(prepended (value@ #left root)
(value@ #right root))
#1]
- (let [go_left? (_\< root_key key)]
+ (let [go_left? (_#< root_key key)]
(case (recur (if go_left?
(value@ #left root)
(value@ #right root)))
@@ -536,7 +536,7 @@
(def: .public (of_list order list)
(All (_ k v) (-> (Order k) (List [k v]) (Dictionary k v)))
- (list\mix (function (_ [key value] dict)
+ (list#mix (function (_ [key value] dict)
(has key value dict))
(empty order)
list))
@@ -550,7 +550,7 @@
(list)
{.#Some node'}
- ($_ list\composite
+ ($_ list#composite
(recur (value@ #left node'))
(list <output>)
(recur (value@ #right node'))))))]
@@ -560,11 +560,11 @@
[values v (value@ #value node')]
)
-(implementation: .public (equivalence (^open ",\[0]"))
+(implementation: .public (equivalence (^open ",#[0]"))
(All (_ k v) (-> (Equivalence v) (Equivalence (Dictionary k v))))
(def: (= reference sample)
- (let [(^open "/\[0]") (value@ #&order reference)]
+ (let [(^open "/#[0]") (value@ #&order reference)]
(loop [entriesR (entries reference)
entriesS (entries sample)]
(case [entriesR entriesS]
@@ -572,8 +572,8 @@
#1
[{.#Item [keyR valueR] entriesR'} {.#Item [keyS valueS] entriesS'}]
- (and (/\= keyR keyS)
- (,\= valueR valueS)
+ (and (/#= keyR keyS)
+ (,#= valueR valueS)
(recur entriesR' entriesS'))
_
diff --git a/stdlib/source/library/lux/data/collection/dictionary/plist.lux b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
index 8ffa6682a..a429d56f9 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/plist.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
@@ -5,9 +5,9 @@
[equivalence {"+" [Equivalence]}]]
[data
["[0]" product]
- ["[0]" text ("[1]\[0]" equivalence)]
+ ["[0]" text ("[1]#[0]" equivalence)]
[collection
- ["[0]" list ("[1]\[0]" functor)]]]
+ ["[0]" list ("[1]#[0]" functor)]]]
[math
[number
["n" nat]]]]])
@@ -35,14 +35,14 @@
{.#None}
{.#Item [k' v'] properties'}
- (if (text\= key k')
+ (if (text#= key k')
{.#Some v'}
(value key properties'))))
(template [<name> <type> <access>]
[(def: .public <name>
(All (_ a) (-> (PList a) (List <type>)))
- (list\each <access>))]
+ (list#each <access>))]
[keys Text product.left]
[values a product.right]
@@ -64,7 +64,7 @@
(list [key val])
{.#Item [k' v'] properties'}
- (if (text\= key k')
+ (if (text#= key k')
{.#Item [key val]
properties'}
{.#Item [k' v']
@@ -77,7 +77,7 @@
{.#End}
{.#Item [k' v'] properties'}
- (if (text\= key k')
+ (if (text#= key k')
{.#Item [k' (f v')] properties'}
{.#Item [k' v'] (revised key f properties')})))
@@ -88,7 +88,7 @@
properties
{.#Item [k' v'] properties'}
- (if (text\= key k')
+ (if (text#= key k')
properties'
{.#Item [k' v']
(lacks key properties')})))