aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data')
-rw-r--r--stdlib/source/library/lux/data/binary.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/array.lux48
-rw-r--r--stdlib/source/library/lux/data/collection/bits.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux112
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux10
-rw-r--r--stdlib/source/library/lux/data/collection/queue.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/queue/priority.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/set/multi.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/stack.lux6
-rw-r--r--stdlib/source/library/lux/data/format/binary.lux2
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux2
-rw-r--r--stdlib/source/library/lux/data/format/json.lux4
-rw-r--r--stdlib/source/library/lux/data/format/markdown.lux22
-rw-r--r--stdlib/source/library/lux/data/text.lux6
16 files changed, 129 insertions, 121 deletions
diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux
index b1290557f..cff9714e2 100644
--- a/stdlib/source/library/lux/data/binary.lux
+++ b/stdlib/source/library/lux/data/binary.lux
@@ -143,7 +143,7 @@
... Default
(|> binary
- (array.read index)
+ (array.read! index)
(maybe.else (: (I64 Any) 0))
(:as I64)))])
@@ -358,7 +358,7 @@
... Default
(..copy length offset binary 0 (..empty length)))))))
-(def: .public (drop bytes binary)
+(def: .public (after bytes binary)
{#.doc (example "Yields a binary BLOB with at most the specified number of bytes removed.")}
(-> Nat Binary Binary)
(case bytes
diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux
index a141fad68..5d306f773 100644
--- a/stdlib/source/library/lux/data/collection/array.lux
+++ b/stdlib/source/library/lux/data/collection/array.lux
@@ -77,13 +77,13 @@
@.php ("php array length" array)
@.scheme ("scheme array length" array)}))
- (template: (!read <read> <null?>)
- [(let [output (<read> index array)]
+ (template: (!read! <read!> <null?>)
+ [(let [output (<read!> index array)]
(if (<null?> output)
#.None
(#.Some output)))])
- (def: .public (read index array)
+ (def: .public (read! index array)
(All [a]
(-> Nat (Array a) (Maybe a)))
(if (n.< (size array) index)
@@ -101,12 +101,12 @@
#.None
(#.Some (:expected value))))
- @.js (!read "js array read" "js object undefined?")
- @.python (!read "python array read" "python object none?")
- @.lua (!read "lua array read" "lua object nil?")
- @.ruby (!read "ruby array read" "ruby object nil?")
- @.php (!read "php array read" "php object null?")
- @.scheme (!read "scheme array read" "scheme object nil?")})
+ @.js (!read! "js array read" "js object undefined?")
+ @.python (!read! "python array read" "python object none?")
+ @.lua (!read! "lua array read" "lua object nil?")
+ @.ruby (!read! "ruby array read" "ruby object nil?")
+ @.php (!read! "php array read" "php object null?")
+ @.scheme (!read! "scheme array read" "scheme object nil?")})
#.None))
(def: .public (write! index value array)
@@ -152,7 +152,7 @@
(def: .public (contains? index array)
(All [a]
(-> Nat (Array a) Bit))
- (case (..read index array)
+ (case (..read! index array)
(#.Some _)
true
@@ -163,7 +163,7 @@
{#.doc (.example "Mutate the array by updating the value at the specified index.")}
(All [a]
(-> Nat (-> a a) (Array a) (Array a)))
- (case (read index array)
+ (case (read! index array)
#.None
array
@@ -176,7 +176,7 @@
(All [a]
(-> Nat a (-> a a) (Array a) (Array a)))
(write! index
- (|> array (read index) (maybe.else default) transform)
+ (|> array (read! index) (maybe.else default) transform)
array))
(def: .public (copy! length src_start src_array dest_start dest_array)
@@ -187,7 +187,7 @@
(if (n.= 0 length)
dest_array
(list\fold (function (_ offset target)
- (case (read (n.+ offset src_start) src_array)
+ (case (read! (n.+ offset src_start) src_array)
#.None
target
@@ -200,7 +200,7 @@
{#.doc "Finds out how many cells in an array are occupied."}
(All [a] (-> (Array a) Nat))
(list\fold (function (_ idx count)
- (case (read idx array)
+ (case (read! idx array)
#.None
count
@@ -219,7 +219,7 @@
(All [a]
(-> (Predicate a) (Array a) (Array a)))
(list\fold (function (_ idx xs')
- (case (read idx xs)
+ (case (read! idx xs)
#.None
xs'
@@ -237,7 +237,7 @@
(let [arr_size (size xs)]
(loop [idx 0]
(if (n.< arr_size idx)
- (case (read idx xs)
+ (case (read! idx xs)
#.None
(recur (inc idx))
@@ -254,7 +254,7 @@
(let [arr_size (size xs)]
(loop [idx 0]
(if (n.< arr_size idx)
- (case (read idx xs)
+ (case (read! idx xs)
#.None
(recur (inc idx))
@@ -269,7 +269,7 @@
(All [a] (-> (Array a) (Array a)))
(let [arr_size (size xs)]
(list\fold (function (_ idx ys)
- (case (read idx xs)
+ (case (read! idx xs)
#.None
ys
@@ -300,7 +300,7 @@
_
(recur (dec idx)
- (case (read idx array)
+ (case (read! idx array)
(#.Some head)
(#.Item head output)
@@ -318,7 +318,7 @@
_
(recur (dec idx)
- (#.Item (maybe.else default (read idx array))
+ (#.Item (maybe.else default (read! idx array))
output)))))
(implementation: .public (equivalence (^open ",\."))
@@ -330,7 +330,7 @@
(and (n.= sxy sxs)
(list\fold (function (_ idx prev)
(and prev
- (case [(read idx xs) (read idx ys)]
+ (case [(read! idx xs) (read! idx ys)]
[#.None #.None]
true
@@ -362,7 +362,7 @@
(if (n.= 0 arr_size)
(empty arr_size)
(list\fold (function (_ idx mb)
- (case (read idx ma)
+ (case (read! idx ma)
#.None
mb
@@ -380,7 +380,7 @@
(loop [so_far init
idx 0]
(if (n.< arr_size idx)
- (case (read idx xs)
+ (case (read! idx xs)
#.None
(recur so_far (inc idx))
@@ -396,7 +396,7 @@
(let [size (..size array)]
(loop [idx 0]
(if (n.< size idx)
- (case (..read idx array)
+ (case (..read! idx array)
(#.Some value)
(<op> (predicate value)
(recur (inc idx)))
diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux
index ef10e0f6d..e5e85e361 100644
--- a/stdlib/source/library/lux/data/collection/bits.lux
+++ b/stdlib/source/library/lux/data/collection/bits.lux
@@ -52,14 +52,14 @@
(-> Nat Bits Bit)
(let [[chunk_index bit_index] (n./% chunk_size index)]
(.and (n.< (array.size bits) chunk_index)
- (|> (array.read chunk_index bits)
+ (|> (array.read! chunk_index bits)
(maybe.else empty_chunk)
(i64.one? bit_index)))))
(def: (chunk idx bits)
(-> Nat Bits Chunk)
(if (n.< (array.size bits) idx)
- (|> bits (array.read idx) (maybe.else empty_chunk))
+ (|> bits (array.read! idx) (maybe.else empty_chunk))
empty_chunk))
(template [<name> <op>]
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index 642b19b57..fb7aaaa83 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -130,7 +130,7 @@
... Expands a copy of the array, to have 1 extra slot, which is used
... for storing the value.
-(def: (insert! 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 (inc old_size))
@@ -139,17 +139,17 @@
(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: (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: (vacant! idx array)
+(def: (array\lacks' 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: (lacks! idx array)
+(def: (array\lacks idx array)
(All [a] (-> Index (Array a) (Array a)))
(let [new_size (dec (array.size array))]
(|> (array.empty new_size)
@@ -236,7 +236,7 @@
(All [k v] (-> Index (Hierarchy k v) [Bit_Map (Base k v)]))
(product.right (list\fold (function (_ idx [insertion_idx node])
(let [[bitmap base] node]
- (case (array.read idx h_array)
+ (case (array.read! idx h_array)
#.None [insertion_idx node]
(#.Some sub_node) (if (n.= except_idx idx)
[insertion_idx node]
@@ -254,7 +254,7 @@
(List Index)
(list.indices hierarchy_nodes_size))
-(def: (promotion 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
@@ -264,13 +264,13 @@
(if (with_bit_position? (to_bit_position hierarchy_idx)
bitmap)
[(inc base_idx)
- (case (array.read base_idx base)
+ (case (array.read! base_idx base)
(#.Some (#.Left sub_node))
(array.write! hierarchy_idx sub_node h_array)
(#.Some (#.Right [key' val']))
(array.write! hierarchy_idx
- (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
@@ -292,22 +292,22 @@
_
#0)))
-(def: (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
... a sub-node. If impossible, introduce a new singleton sub-node.
(#Hierarchy _size hierarchy)
(let [idx (level_index level hash)
- [_size' sub_node] (case (array.read idx hierarchy)
+ [_size' sub_node] (case (array.read! idx hierarchy)
(#.Some sub_node)
[_size sub_node]
_
[(inc _size) empty_node])]
(#Hierarchy _size'
- (revised! idx (has' (level_up level) hash key val key_hash sub_node)
- hierarchy)))
+ (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
... already been used.
@@ -316,38 +316,38 @@
(if (with_bit_position? bit bitmap)
... If so...
(let [idx (base_index bit bitmap)]
- (case (array.read idx base)
+ (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' (has' (level_up level) hash key val key_hash sub_node)]
- (#Base bitmap (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 the same key is found, replace the value.
- (#Base bitmap (revised! idx (#.Right key val) base))
+ (#Base bitmap (array\revised idx (#.Right key val) base))
... Otherwise, compare the hashes of the keys.
- (#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)))
+ (#Base bitmap (array\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
+ (node\has next_level hash' key' val' key_hash)
+ (node\has next_level hash key val key_hash))))))
+ base)))
#.None
(undefined)))
@@ -359,13 +359,13 @@
... KV-pair as a singleton node to it.
(#Hierarchy (inc base_count)
(|> base
- (promotion has' key_hash level bitmap)
+ (promotion node\has key_hash level bitmap)
(array.write! (level_index level hash)
- (has' (level_up level) hash key val key_hash empty_node))))
+ (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)
- (insert! (base_index bit bitmap) (#.Right [key val]) base))))))
+ (array\has (base_index bit bitmap) (#.Right [key val]) base))))))
... For #Collisions nodes, compare the hashes.
(#Collisions _hash _colls)
@@ -376,17 +376,17 @@
... If the key was already present in the collisions-list, its
... value gets updated.
(#.Some coll_idx)
- (#Collisions _hash (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 (insert! (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))))
- (has' level hash key val key_hash)))
+ (node\has level hash key val key_hash)))
))
(def: (lacks' level hash key key_hash node)
@@ -396,7 +396,7 @@
... the Hash-Code.
(#Hierarchy h_size h_array)
(let [idx (level_index level hash)]
- (case (array.read idx h_array)
+ (case (array.read! idx h_array)
... If not, there's nothing to remove.
#.None
node
@@ -415,17 +415,17 @@
... If so, perform it.
(#Base (demotion idx [h_size h_array]))
... Otherwise, just clear the space.
- (#Hierarchy (dec h_size) (vacant! idx h_array)))
+ (#Hierarchy (dec h_size) (array\lacks' idx h_array)))
... But if the sub_removal yielded a non_empty node, then
... just update the hiearchy branch.
- (#Hierarchy h_size (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)
(let [bit (level_bit_position level hash)]
(if (with_bit_position? bit bitmap)
(let [idx (base_index bit bitmap)]
- (case (array.read idx base)
+ (case (array.read! idx base)
... If set, check if it's a sub_node, and remove the KV
... from it.
(#.Some (#.Left sub_node))
@@ -443,11 +443,11 @@
... But if not, then just unset the position and
... remove the node.
(#Base (without_bit_position bit bitmap)
- (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
- (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']))
@@ -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)
- (lacks! idx base))
+ (array\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 (lacks! idx _colls))))
+ (#Collisions _hash (array\lacks idx _colls))))
))
(def: (value' level hash key key_hash node)
@@ -486,7 +486,7 @@
(case node
... For #Hierarchy nodes, just look-up the key on its children.
(#Hierarchy _size hierarchy)
- (case (array.read (level_index level hash) hierarchy)
+ (case (array.read! (level_index level hash) hierarchy)
#.None #.None
(#.Some sub_node) (value' (level_up level) hash key key_hash sub_node))
@@ -494,7 +494,7 @@
(#Base bitmap base)
(let [bit (level_bit_position level hash)]
(if (with_bit_position? bit bitmap)
- (case (array.read (base_index bit bitmap) base)
+ (case (array.read! (base_index bit bitmap) base)
(#.Some (#.Left sub_node))
(value' (level_up level) hash key key_hash sub_node)
@@ -573,7 +573,7 @@
(def: .public (has key val dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (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)))
@@ -593,7 +593,7 @@
(exception: .public key_already_exists)
-(def: .public (try_put key val dict)
+(def: .public (has' key val dict)
{#.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 (value key dict)
@@ -610,7 +610,7 @@
(#.Some val)
(has key (f val) dict)))
-(def: .public (upsert key default f dict)
+(def: .public (revised' 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)))
@@ -672,7 +672,7 @@
dict1
(entries dict2)))
-(def: .public (re_bind from_key to_key dict)
+(def: .public (re_bound from_key to_key dict)
{#.doc (example "If there is a value under 'from_key', remove 'from_key' and store the value under 'to_key'.")}
(All [k v] (-> k k (Dictionary k v) (Dictionary k v)))
(case (value from_key dict)
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index ff5a1fe12..7298a5039 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -100,8 +100,8 @@
<then>)
<else>))]
- [take (#.Item x (take (dec n) xs')) #.End]
- [drop (drop (dec n) xs') xs]
+ [first (#.Item x (first (dec n) xs')) #.End]
+ [after (after (dec n) xs') xs]
)
(template [<name> <then> <else>]
@@ -121,7 +121,7 @@
[until (until predicate xs') xs]
)
-(def: .public (split n xs)
+(def: .public (split_at n xs)
(All [a]
(-> Nat (List a) [(List a) (List a)]))
(if (n.> 0 n)
@@ -130,7 +130,7 @@
[#.End #.End]
(#.Item x xs')
- (let [[tail rest] (split (dec n) xs')]
+ (let [[tail rest] (split_at (dec n) xs')]
[(#.Item x tail) rest]))
[#.End xs]))
@@ -161,7 +161,7 @@
#.End
_
- (let [[pre post] (split size list)]
+ (let [[pre post] (split_at size list)]
(#.Item pre (sub size post)))))
(def: .public (repeated n x)
diff --git a/stdlib/source/library/lux/data/collection/queue.lux b/stdlib/source/library/lux/data/collection/queue.lux
index 04fd1c6b5..3e017d382 100644
--- a/stdlib/source/library/lux/data/collection/queue.lux
+++ b/stdlib/source/library/lux/data/collection/queue.lux
@@ -31,7 +31,7 @@
(let [(^slots [#front #rear]) queue]
(list\compose front (list.reversed rear))))
-(def: .public peek
+(def: .public front
{#.doc (example "Yields the first value in the queue, if any.")}
(All [a] (-> (Queue a) (Maybe a)))
(|>> (get@ #front) list.head))
@@ -52,7 +52,7 @@
(or (list.member? equivalence front member)
(list.member? equivalence rear member))))
-(def: .public (pop queue)
+(def: .public (next queue)
(All [a] (-> (Queue a) (Queue a)))
(case (get@ #front queue)
... Empty...
@@ -70,7 +70,7 @@
(|> queue
(set@ #front front'))))
-(def: .public (push val queue)
+(def: .public (end val queue)
(All [a] (-> a (Queue a) (Queue a)))
(case (get@ #front queue)
#.End
diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux
index 138b86876..88da217c3 100644
--- a/stdlib/source/library/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/library/lux/data/collection/queue/priority.lux
@@ -46,7 +46,7 @@
Queue
(:abstraction #.None))
- (def: .public (peek queue)
+ (def: .public (front queue)
(All [a] (-> (Queue a) (Maybe a)))
(do maybe.monad
[tree (:representation queue)]
@@ -84,7 +84,7 @@
(or (recur left)
(recur right))))))
- (def: .public (pop queue)
+ (def: .public (next queue)
(All [a] (-> (Queue a) (Queue a)))
(:abstraction
(do maybe.monad
@@ -112,7 +112,7 @@
(#.Some =right)
(#.Some (\ ..builder branch left =right)))))))))
- (def: .public (push priority value queue)
+ (def: .public (end priority value queue)
(All [a] (-> Priority a (Queue a) (Queue a)))
(let [addition (\ ..builder leaf priority value)]
(:abstraction
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index c36a5377e..230de34a1 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -105,7 +105,7 @@
... Just add the tail to it
(#Base tail)
... Otherwise, check whether there's a vacant spot
- (case (array.read sub_idx parent)
+ (case (array.read! sub_idx parent)
... If so, set the path to the tail
#.None
(..path (level_down level) tail)
@@ -129,7 +129,7 @@
(def: (put' level idx val hierarchy)
(All [a] (-> Level Index a (Hierarchy a) (Hierarchy a)))
(let [sub_idx (branch_idx (i64.right_shifted level idx))]
- (case (array.read sub_idx hierarchy)
+ (case (array.read! sub_idx hierarchy)
(#.Some (#Hierarchy sub_node))
(|> (array.clone hierarchy)
(array.write! sub_idx (#Hierarchy (put' (level_down level) idx val sub_node))))
@@ -152,7 +152,7 @@
(n.> branching_exponent level)
(do maybe.monad
- [base|hierarchy (array.read sub_idx hierarchy)
+ [base|hierarchy (array.read! sub_idx hierarchy)
sub (case base|hierarchy
(#Hierarchy sub)
(without_tail size (level_down level) sub)
@@ -254,7 +254,7 @@
(loop [level (get@ #level row)
hierarchy (get@ #root row)]
(case [(n.> branching_exponent level)
- (array.read (branch_idx (i64.right_shifted level idx)) hierarchy)]
+ (array.read! (branch_idx (i64.right_shifted level idx)) hierarchy)]
[#1 (#.Some (#Hierarchy sub))]
(recur (level_down level) sub)
@@ -272,7 +272,7 @@
(All [a] (-> Nat (Row a) (Try a)))
(do try.monad
[base (base_for idx row)]
- (case (array.read (branch_idx idx) base)
+ (case (array.read! (branch_idx idx) base)
(#.Some value)
(#try.Success value)
@@ -324,7 +324,7 @@
root (maybe.else (empty_hierarchy [])
(without_tail row_size init_level (get@ #root row)))]
(if (n.> branching_exponent level)
- (case [(array.read 1 root) (array.read 0 root)]
+ (case [(array.read! 1 root) (array.read! 0 root)]
[#.None (#.Some (#Hierarchy sub_node))]
(recur (level_down level) sub_node)
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index 6264d6083..d60fd99d4 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -84,7 +84,7 @@
xs)))]
[while until (-> a Bit) (pred x) pred |>]
- [take drop Nat (n.= 0 pred) (dec pred) not]
+ [first after Nat (n.= 0 pred) (dec pred) not]
)
(template [<splitter> <pred_type> <pred_test> <pred_step>]
@@ -98,7 +98,7 @@
[(#.Item [x tail]) next]))))]
[split_when (-> a Bit) (pred x) pred]
- [split Nat (n.= 0 pred) (dec pred)]
+ [split_at Nat (n.= 0 pred) (dec pred)]
)
(def: .public (unfold step init)
diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux
index 46f395b21..b4786c825 100644
--- a/stdlib/source/library/lux/data/collection/set/multi.lux
+++ b/stdlib/source/library/lux/data/collection/set/multi.lux
@@ -37,7 +37,7 @@
0 set
_ (|> set
:representation
- (dictionary.upsert elem 0 (n.+ multiplicity))
+ (dictionary.revised' elem 0 (n.+ multiplicity))
:abstraction)))
(def: .public (lacks multiplicity elem set)
diff --git a/stdlib/source/library/lux/data/collection/stack.lux b/stdlib/source/library/lux/data/collection/stack.lux
index af2b3c3ea..2b9cbc2e4 100644
--- a/stdlib/source/library/lux/data/collection/stack.lux
+++ b/stdlib/source/library/lux/data/collection/stack.lux
@@ -27,7 +27,7 @@
(All [a] (-> (Stack a) Bit))
(|>> :representation //.empty?))
- (def: .public (peek stack)
+ (def: .public (value stack)
{#.doc (example "Yields the top value in the stack, if any.")}
(All [a] (-> (Stack a) (Maybe a)))
(case (:representation stack)
@@ -37,7 +37,7 @@
(#.Item value _)
(#.Some value)))
- (def: .public (pop stack)
+ (def: .public (next stack)
(All [a] (-> (Stack a) (Maybe [a (Stack a)])))
(case (:representation stack)
#.End
@@ -46,7 +46,7 @@
(#.Item top stack')
(#.Some [top (:abstraction stack')])))
- (def: .public (push value stack)
+ (def: .public (top value stack)
(All [a] (-> a (Stack a) (Stack a)))
(:abstraction (#.Item value (:representation stack))))
diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux
index f3ce9f830..e16c2cebd 100644
--- a/stdlib/source/library/lux/data/format/binary.lux
+++ b/stdlib/source/library/lux/data/format/binary.lux
@@ -192,7 +192,7 @@
original_count)
value (if (n.= original_count capped_count)
value
- (|> value row.list (list.take capped_count) row.of_list))
+ (|> value row.list (list.first capped_count) row.of_list))
(^open "specification\.") ..monoid
[size mutation] (|> value
(row\map valueW)
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index a39469994..c2fb914c2 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -61,7 +61,7 @@
(let [raw (%.frac value)]
(if (f.< +0.0 value)
raw
- (|> raw (text.split 1) maybe.assume product.right))))
+ (|> raw (text.split_at 1) maybe.assume product.right))))
(abstract: .public (Value brand)
{}
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 45ac870c0..7f6ca24a8 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -227,7 +227,7 @@
value (let [raw (\ f.decimal encode value)]
(if (f.< +0.0 value)
raw
- (|> raw (text.split 1) maybe.assume product.right))))))
+ (|> raw (text.split_at 1) maybe.assume product.right))))))
(def: escape "\")
(def: escaped_dq (text\compose ..escape text.double_quote))
@@ -372,7 +372,7 @@
(loop [_ []])
(do {! <>.monad}
[chars (<text>.some (<text>.none_of (text\compose "\" text.double_quote)))
- stop <text>.peek])
+ stop <text>.next])
(if (text\= "\" stop)
(do !
[escaped escaped_parser
diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux
index 08b26a686..281425105 100644
--- a/stdlib/source/library/lux/data/format/markdown.lux
+++ b/stdlib/source/library/lux/data/format/markdown.lux
@@ -52,7 +52,7 @@
(template [<name> <prefix>]
[(def: .public (<name> content)
- (-> Text Markdown)
+ (-> Text (Markdown Block))
(:abstraction (format <prefix> " " (..safe content) ..blank_line)))]
[heading/1 "#"]
@@ -110,10 +110,14 @@
(Markdown Block))
(|>> list.enumeration
(list\map (function (_ [idx [summary detail]])
- (format (%.nat (inc idx)) ". " (:representation summary) text.new_line
+ (format "1. " (:representation summary)
(case detail
(#.Some detail)
- (|> detail :representation ..indent (text.enclosed [text.new_line text.new_line]))
+ (|> detail
+ :representation
+ ..indent
+ (text.enclosed [text.new_line text.new_line])
+ (format text.new_line))
#.None
""))))
@@ -124,10 +128,14 @@
(-> (List [(Markdown Span) (Maybe (Markdown Block))])
(Markdown Block))
(|>> (list\map (function (_ [summary detail])
- (format "*. " (:representation summary) text.new_line
+ (format "* " (:representation summary)
(case detail
(#.Some detail)
- (|> detail :representation ..indent (text.enclosed [text.new_line text.new_line]))
+ (|> detail
+ :representation
+ ..indent
+ (text.enclosed [text.new_line text.new_line])
+ (format text.new_line))
#.None
""))))
@@ -137,7 +145,7 @@
(def: .public snippet
{#.doc "A snippet of code."}
(-> Text (Markdown Span))
- (|>> ..safe (text.enclosed ["`" "`"]) :abstraction))
+ (|>> (text.enclosed ["`` " " ``"]) :abstraction))
(def: .public code
{#.doc "A block of code."}
@@ -180,6 +188,6 @@
)
(def: .public markdown
- (-> (Markdown Any) Text)
+ (All [a] (-> (Markdown a) Text))
(|>> :representation))
)
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index 096a968ee..e2f781d64 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -154,7 +154,7 @@
(#.Some ("lux text clip" offset (n.- offset size) input))
#.None)))
-(def: .public (split at x)
+(def: .public (split_at at x)
(-> Nat Text (Maybe [Text Text]))
(case [(..clip 0 at x) (..clip' at x)]
[(#.Some pre) (#.Some post)]
@@ -167,8 +167,8 @@
(-> Text Text (Maybe [Text Text]))
(do maybe.monad
[index (index_of token sample)
- [pre post'] (split index sample)
- [_ post] (split (size token) post')]
+ [pre post'] (split_at index sample)
+ [_ post] (split_at (size token) post')]
(in [pre post])))
(def: .public (all_split_by token sample)