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/bit.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/array.lux132
-rw-r--r--stdlib/source/library/lux/data/collection/bits.lux10
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux158
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux14
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux79
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux62
-rw-r--r--stdlib/source/library/lux/data/collection/set.lux8
-rw-r--r--stdlib/source/library/lux/data/collection/set/multi.lux40
-rw-r--r--stdlib/source/library/lux/data/collection/set/ordered.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux18
-rw-r--r--stdlib/source/library/lux/data/collection/tree/zipper.lux2
-rw-r--r--stdlib/source/library/lux/data/color.lux13
-rw-r--r--stdlib/source/library/lux/data/color/named.lux1
-rw-r--r--stdlib/source/library/lux/data/format/binary.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css.lux4
-rw-r--r--stdlib/source/library/lux/data/format/html.lux10
-rw-r--r--stdlib/source/library/lux/data/format/json.lux42
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux54
-rw-r--r--stdlib/source/library/lux/data/format/xml.lux8
-rw-r--r--stdlib/source/library/lux/data/identity.lux3
-rw-r--r--stdlib/source/library/lux/data/name.lux4
-rw-r--r--stdlib/source/library/lux/data/product.lux1
-rw-r--r--stdlib/source/library/lux/data/text.lux4
-rw-r--r--stdlib/source/library/lux/data/text/buffer.lux16
-rw-r--r--stdlib/source/library/lux/data/text/encoding.lux1
-rw-r--r--stdlib/source/library/lux/data/text/encoding/utf8.lux17
-rw-r--r--stdlib/source/library/lux/data/text/escape.lux4
-rw-r--r--stdlib/source/library/lux/data/text/format.lux34
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux78
-rw-r--r--stdlib/source/library/lux/data/text/unicode/set.lux12
31 files changed, 411 insertions, 432 deletions
diff --git a/stdlib/source/library/lux/data/bit.lux b/stdlib/source/library/lux/data/bit.lux
index 6d7b7c9c3..38f7b5f8d 100644
--- a/stdlib/source/library/lux/data/bit.lux
+++ b/stdlib/source/library/lux/data/bit.lux
@@ -49,12 +49,12 @@
(implementation: .public codec
(Codec Text Bit)
- (def: (encode x)
+ (def: (encoded x)
(if x
"#1"
"#0"))
- (def: (decode input)
+ (def: (decoded input)
(case input
"#1" (#.Right #1)
"#0" (#.Right #0)
diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux
index c7fe53e3f..4ec5d1612 100644
--- a/stdlib/source/library/lux/data/collection/array.lux
+++ b/stdlib/source/library/lux/data/collection/array.lux
@@ -6,14 +6,14 @@
[monoid (#+ Monoid)]
[functor (#+ Functor)]
[equivalence (#+ Equivalence)]
- [fold (#+ Fold)]
+ [mix (#+ Mix)]
[predicate (#+ Predicate)]]
[control
["." maybe]]
[data
["." product]
[collection
- ["." list ("#\." fold)]]]
+ ["." list ("#\." mix)]]]
[math
[number
["n" nat]]]]])
@@ -178,27 +178,27 @@
(Array a)))
(if (n.= 0 length)
dest_array
- (list\fold (function (_ offset target)
- (case (read! (n.+ offset src_start) src_array)
- #.None
- target
-
- (#.Some value)
- (write! (n.+ offset dest_start) value target)))
- dest_array
- (list.indices length))))
+ (list\mix (function (_ offset target)
+ (case (read! (n.+ offset src_start) src_array)
+ #.None
+ target
+
+ (#.Some value)
+ (write! (n.+ offset dest_start) value target)))
+ dest_array
+ (list.indices length))))
(def: .public (occupancy array)
(All [a] (-> (Array a) Nat))
- (list\fold (function (_ idx count)
- (case (read! idx array)
- #.None
- count
-
- (#.Some _)
- (++ count)))
- 0
- (list.indices (size array))))
+ (list\mix (function (_ idx count)
+ (case (read! idx array)
+ #.None
+ count
+
+ (#.Some _)
+ (++ count)))
+ 0
+ (list.indices (size array))))
(def: .public (vacancy array)
(All [a] (-> (Array a) Nat))
@@ -207,17 +207,17 @@
(def: .public (filter! p xs)
(All [a]
(-> (Predicate a) (Array a) (Array a)))
- (list\fold (function (_ idx xs')
- (case (read! idx xs)
- #.None
- xs'
-
- (#.Some x)
- (if (p x)
- xs'
- (delete! idx xs'))))
- xs
- (list.indices (size xs))))
+ (list\mix (function (_ idx xs')
+ (case (read! idx xs)
+ #.None
+ xs'
+
+ (#.Some x)
+ (if (p x)
+ xs'
+ (delete! idx xs'))))
+ xs
+ (list.indices (size xs))))
(def: .public (example p xs)
(All [a]
@@ -254,22 +254,22 @@
(def: .public (clone xs)
(All [a] (-> (Array a) (Array a)))
(let [arr_size (size xs)]
- (list\fold (function (_ idx ys)
- (case (read! idx xs)
- #.None
- ys
+ (list\mix (function (_ idx ys)
+ (case (read! idx xs)
+ #.None
+ ys
- (#.Some x)
- (write! idx x ys)))
- (empty arr_size)
- (list.indices arr_size))))
+ (#.Some x)
+ (write! idx x ys)))
+ (empty arr_size)
+ (list.indices arr_size))))
(def: .public (of_list xs)
(All [a] (-> (List a) (Array a)))
- (product.right (list\fold (function (_ x [idx arr])
- [(++ idx) (write! idx x arr)])
- [0 (empty (list.size xs))]
- xs)))
+ (product.right (list\mix (function (_ x [idx arr])
+ [(++ idx) (write! idx x arr)])
+ [0 (empty (list.size xs))]
+ xs)))
(def: underflow
Nat
@@ -312,19 +312,19 @@
(let [sxs (size xs)
sxy (size ys)]
(and (n.= sxy sxs)
- (list\fold (function (_ idx prev)
- (and prev
- (case [(read! idx xs) (read! idx ys)]
- [#.None #.None]
- true
+ (list\mix (function (_ idx prev)
+ (and prev
+ (case [(read! idx xs) (read! idx ys)]
+ [#.None #.None]
+ true
- [(#.Some x) (#.Some y)]
- (,\= x y)
+ [(#.Some x) (#.Some y)]
+ (,\= x y)
- _
- false)))
- true
- (list.indices sxs))))))
+ _
+ false)))
+ true
+ (list.indices sxs))))))
(implementation: .public monoid
(All [a] (Monoid (Array a)))
@@ -345,21 +345,21 @@
(let [arr_size (size ma)]
(if (n.= 0 arr_size)
(empty arr_size)
- (list\fold (function (_ idx mb)
- (case (read! idx ma)
- #.None
- mb
-
- (#.Some x)
- (write! idx (f x) mb)))
- (empty arr_size)
- (list.indices arr_size))
+ (list\mix (function (_ idx mb)
+ (case (read! idx ma)
+ #.None
+ mb
+
+ (#.Some x)
+ (write! idx (f x) mb)))
+ (empty arr_size)
+ (list.indices arr_size))
))))
-(implementation: .public fold
- (Fold Array)
+(implementation: .public mix
+ (Mix Array)
- (def: (fold f init xs)
+ (def: (mix f init xs)
(let [arr_size (size xs)]
(loop [so_far init
idx 0]
diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux
index 6c375247c..34e45b10f 100644
--- a/stdlib/source/library/lux/data/collection/bits.lux
+++ b/stdlib/source/library/lux/data/collection/bits.lux
@@ -8,7 +8,7 @@
["." maybe]]
[data
[collection
- ["." array (#+ Array) ("#\." fold)]]]
+ ["." array (#+ Array) ("#\." mix)]]]
[math
[number
["n" nat]
@@ -33,10 +33,10 @@
(def: .public (size bits)
(-> Bits Nat)
- (array\fold (function (_ chunk total)
- (|> chunk i64.ones (n.+ total)))
- 0
- bits))
+ (array\mix (function (_ chunk total)
+ (|> chunk i64.ones (n.+ total)))
+ 0
+ bits))
(def: .public (capacity bits)
(-> Bits Nat)
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index faab0f7b2..afc1cd356 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -12,8 +12,8 @@
[data
["." product]
[collection
- ["." list ("#\." fold functor monoid)]
- ["." array (#+ Array) ("#\." functor fold)]]]
+ ["." list ("#\." mix functor monoid)]
+ ["." array (#+ Array) ("#\." functor mix)]]]
[math
["." number
["n" nat]
@@ -234,19 +234,19 @@
... 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\fold (function (_ idx [insertion_idx node])
- (let [[bitmap base] node]
- (case (array.read! idx h_array)
- #.None [insertion_idx node]
- (#.Some sub_node) (if (n.= except_idx idx)
- [insertion_idx node]
- [(++ insertion_idx)
- [(with_bit_position (to_bit_position idx) bitmap)
- (array.write! insertion_idx (#.Left sub_node) base)]])
- )))
- [0 [clean_bitmap
- (array.empty (-- h_size))]]
- (list.indices (array.size h_array)))))
+ (product.right (list\mix (function (_ idx [insertion_idx node])
+ (let [[bitmap base] node]
+ (case (array.read! idx h_array)
+ #.None [insertion_idx node]
+ (#.Some sub_node) (if (n.= except_idx idx)
+ [insertion_idx node]
+ [(++ insertion_idx)
+ [(with_bit_position (to_bit_position idx) bitmap)
+ (array.write! insertion_idx (#.Left sub_node) base)]])
+ )))
+ [0 [clean_bitmap
+ (array.empty (-- h_size))]]
+ (list.indices (array.size h_array)))))
... When #Base nodes grow too large, they're promoted to #Hierarchy to
... add some depth to the tree and help keep its balance.
@@ -260,25 +260,25 @@
(Hash k) Level
Bit_Map (Base k v)
(Array (Node k v))))
- (product.right (list\fold (function (_ hierarchy_idx (^@ default [base_idx h_array]))
- (if (with_bit_position? (to_bit_position hierarchy_idx)
- bitmap)
- [(++ base_idx)
- (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
- (node\has (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
- h_array)
-
- #.None
- (undefined))]
- default))
- [0
- (array.empty hierarchy_nodes_size)]
- hierarchy_indices)))
+ (product.right (list\mix (function (_ hierarchy_idx (^@ default [base_idx h_array]))
+ (if (with_bit_position? (to_bit_position hierarchy_idx)
+ bitmap)
+ [(++ base_idx)
+ (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
+ (node\has (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
+ h_array)
+
+ #.None
+ (undefined))]
+ default))
+ [0
+ (array.empty hierarchy_nodes_size)]
+ hierarchy_indices)))
... All empty nodes look the same (a #Base node with clean bitmap is
... used).
@@ -518,14 +518,14 @@
(All [k v] (-> (Node k v) Nat))
(case node
(#Hierarchy _size hierarchy)
- (array\fold n.+ 0 (array\map size' hierarchy))
+ (array\mix n.+ 0 (array\map size' hierarchy))
(#Base _ base)
- (array\fold n.+ 0 (array\map (function (_ sub_node')
- (case sub_node'
- (#.Left sub_node) (size' sub_node)
- (#.Right _) 1))
- base))
+ (array\mix n.+ 0 (array\map (function (_ sub_node')
+ (case sub_node'
+ (#.Left sub_node) (size' sub_node)
+ (#.Right _) 1))
+ base))
(#Collisions hash colls)
(array.size colls)
@@ -535,25 +535,25 @@
(All [k v] (-> (Node k v) (List [k v])))
(case node
(#Hierarchy _size hierarchy)
- (array\fold (function (_ sub_node tail) (list\compose (entries' sub_node) tail))
- #.End
- hierarchy)
+ (array\mix (function (_ sub_node tail) (list\compose (entries' sub_node) tail))
+ #.End
+ hierarchy)
(#Base bitmap base)
- (array\fold (function (_ branch tail)
- (case branch
- (#.Left sub_node)
- (list\compose (entries' sub_node) tail)
-
- (#.Right [key' val'])
- (#.Item [key' val'] tail)))
- #.End
- base)
+ (array\mix (function (_ branch tail)
+ (case branch
+ (#.Left sub_node)
+ (list\compose (entries' sub_node) tail)
+
+ (#.Right [key' val'])
+ (#.Item [key' val'] tail)))
+ #.End
+ base)
(#Collisions hash colls)
- (array\fold (function (_ [key' val'] tail) (#.Item [key' val'] tail))
- #.End
- colls)))
+ (array\mix (function (_ [key' val'] tail) (#.Item [key' val'] tail))
+ #.End
+ colls)))
(type: .public (Dictionary k v)
{#hash (Hash k)
@@ -627,18 +627,18 @@
(def: .public (of_list key_hash kvs)
(All [k v] (-> (Hash k) (List [k v]) (Dictionary k v)))
- (list\fold (function (_ [k v] dict)
- (..has k v dict))
- (empty key_hash)
- kvs))
+ (list\mix (function (_ [k v] dict)
+ (..has k v dict))
+ (empty key_hash)
+ kvs))
(template [<side> <name>]
[(def: .public <name>
(All [k v] (-> (Dictionary k v) (List <side>)))
(|>> ..entries
- (list\fold (function (_ [k v] bundle)
- (#.Item <side> bundle))
- #.End)))]
+ (list\mix (function (_ [k v] bundle)
+ (#.Item <side> bundle))
+ #.End)))]
[k keys]
[v values]
@@ -646,21 +646,21 @@
(def: .public (merged dict2 dict1)
(All [k v] (-> (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list\fold (function (_ [key val] dict) (has key val dict))
- dict1
- (entries dict2)))
+ (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\fold (function (_ [key val2] dict)
- (case (value key dict)
- #.None
- (has key val2 dict)
+ (list\mix (function (_ [key val2] dict)
+ (case (value key dict)
+ #.None
+ (has key val2 dict)
- (#.Some val1)
- (has key (f val2 val1) dict)))
- dict1
- (entries dict2)))
+ (#.Some val1)
+ (has key (f val2 val1) dict)))
+ dict1
+ (entries dict2)))
(def: .public (re_bound from_key to_key dict)
(All [k v] (-> k k (Dictionary k v) (Dictionary k v)))
@@ -676,12 +676,12 @@
(def: .public (sub keys dict)
(All [k v] (-> (List k) (Dictionary k v) (Dictionary k v)))
(let [[key_hash _] dict]
- (list\fold (function (_ key new_dict)
- (case (value key dict)
- #.None new_dict
- (#.Some val) (has key val new_dict)))
- (empty key_hash)
- keys)))
+ (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 ",\."))
(All [k v] (-> (Equivalence v) (Equivalence (Dictionary k v))))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index f19843db9..49d4068d5 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -10,10 +10,7 @@
[data
["p" product]
[collection
- ["." list ("#\." monoid fold)]]]
- [macro
- ["." code]
- ["." template]]
+ ["." list ("#\." monoid mix)]]]
[math
[number
["n" nat]]]]])
@@ -101,7 +98,6 @@
(template [<name> <side>]
[(def: .public (<name> dict)
- {#.doc (example (~~ (template.text ["Yields value under the " <name> "imum key."])))}
(All [k v] (-> (Dictionary k v) (Maybe v)))
(case (value@ #root dict)
#.None
@@ -537,10 +533,10 @@
(def: .public (of_list order list)
(All [k v] (-> (Order k) (List [k v]) (Dictionary k v)))
- (list\fold (function (_ [key value] dict)
- (has key value dict))
- (empty order)
- list))
+ (list\mix (function (_ [key value] dict)
+ (has key value dict))
+ (empty order)
+ list))
(template [<name> <type> <output>]
[(def: .public (<name> dict)
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index a4bb340e7..98a3224e4 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -7,7 +7,7 @@
[apply (#+ Apply)]
[equivalence (#+ Equivalence)]
[hash (#+ Hash)]
- [fold (#+ Fold)]
+ [mix (#+ Mix)]
[predicate (#+ Predicate)]
["." functor (#+ Functor)]
["." monad (#+ do Monad)]
@@ -23,32 +23,32 @@
... #End
... (#Item a (List a)))
-(implementation: .public fold
- (Fold List)
+(implementation: .public mix
+ (Mix List)
- (def: (fold f init xs)
+ (def: (mix f init xs)
(case xs
#.End
init
(#.Item x xs')
- (fold f (f x init) xs'))))
+ (mix f (f x init) xs'))))
-(def: .public (aggregates f init inputs)
+(def: .public (mixes f init inputs)
(All [a b] (-> (-> a b b) b (List a) (List b)))
(case inputs
#.End
(list init)
(#.Item [head tail])
- (#.Item [init (aggregates f (f head init) tail)])))
+ (#.Item [init (mixes f (f head init) tail)])))
(def: .public (reversed xs)
(All [a]
(-> (List a) (List a)))
- (fold (function (_ head tail) (#.Item head tail))
- #.End
- xs))
+ (mix (function (_ head tail) (#.Item head tail))
+ #.End
+ xs))
(def: .public (only keep? xs)
(All [a]
@@ -205,15 +205,15 @@
(-> (-> a (Maybe b)) (List a) (List b)))
(for {... TODO: Stop relying on this ASAP.
@.js
- (fold (function (_ head tail)
- (case (check head)
- (#.Some head)
- (#.Item head tail)
-
- #.None
- tail))
- #.End
- (reversed xs))}
+ (mix (function (_ head tail)
+ (case (check head)
+ (#.Some head)
+ (#.Item head tail)
+
+ #.None
+ tail))
+ #.End
+ (reversed xs))}
(case xs
#.End
#.End
@@ -250,7 +250,7 @@
(def: .public (size list)
(All [a] (-> (List a) Nat))
- (fold (function (_ _ acc) (n.+ 1 acc)) 0 list))
+ (mix (function (_ _ acc) (n.+ 1 acc)) 0 list))
(template [<name> <init> <op>]
[(def: .public (<name> predicate items)
@@ -303,7 +303,7 @@
(..equivalence (\ super &equivalence)))
(def: hash
- (\ ..fold fold
+ (\ ..mix mix
(function (_ member hash)
(n.+ (\ super hash member) hash))
0)))
@@ -340,13 +340,15 @@
(def: &functor ..functor)
- (def: (apply ff fa)
+ (def: (on fa ff)
(case ff
#.End
#.End
(#.Item f ff')
- (compose (map f fa) (apply ff' fa)))))
+ (|> ff'
+ (on fa)
+ (compose (map f fa))))))
(implementation: .public monad
(Monad List)
@@ -357,7 +359,7 @@
(#.Item a #.End))
(def: join
- (|>> reversed (fold compose identity))))
+ (|>> reversed (mix compose identity))))
(def: .public (sorted < xs)
(All [a] (-> (-> a a Bit) (List a) (List a)))
@@ -366,12 +368,12 @@
(list)
(#.Item x xs')
- (let [[pre post] (fold (function (_ x' [pre post])
- (if (< x x')
- [(#.Item x' pre) post]
- [pre (#.Item x' post)]))
- [(list) (list)]
- xs')]
+ (let [[pre post] (mix (function (_ x' [pre post])
+ (if (< x x')
+ [(#.Item x' pre) post]
+ [pre (#.Item x' post)]))
+ [(list) (list)]
+ xs')]
($_ compose (sorted < pre) (list x) (sorted < post)))))
(def: .public (empty? xs)
@@ -393,9 +395,8 @@
(or (\ eq = x x')
(member? eq xs' x))))
-(template [<name> <output> <side> <doc>]
+(template [<name> <output> <side>]
[(def: .public (<name> xs)
- {#.doc <doc>}
(All [a] (-> (List a) (Maybe <output>)))
(case xs
#.End
@@ -404,8 +405,8 @@
(#.Item x xs')
(#.Some <side>)))]
- [head a x "Yields the first element of a list."]
- [tail (List a) xs' "For a list of size N, yields the N-1 elements after the first one."]
+ [head a x]
+ [tail (List a) xs']
)
(def: .public (indices size)
@@ -418,7 +419,7 @@
(-> Text Code)
[["" 0 0] (#.Identifier "" name)])
-(def: (nat\encode value)
+(def: (nat\encoded value)
(-> Nat Text)
(loop [input value
output ""]
@@ -446,7 +447,7 @@
(if (n.> 0 num_lists)
(let [(^open ".") ..functor
indices (..indices num_lists)
- type_vars (: (List Code) (map (|>> nat\encode identifier$) indices))
+ type_vars (: (List Code) (map (|>> nat\encoded identifier$) indices))
zipped_type (` (All [(~+ type_vars)]
(-> (~+ (map (: (-> Code Code) (function (_ var) (` (List (~ var)))))
type_vars))
@@ -454,7 +455,7 @@
vars+lists (|> indices
(map ++)
(map (function (_ idx)
- (let [base (nat\encode idx)]
+ (let [base (nat\encoded idx)]
[(identifier$ base)
(identifier$ ("lux text concat" base "'"))]))))
pattern (` [(~+ (map (function (_ [v vs]) (` (#.Item (~ v) (~ vs))))
@@ -488,7 +489,7 @@
indices (..indices num_lists)
g!return_type (identifier$ "0return_type0")
g!func (identifier$ "0func0")
- type_vars (: (List Code) (map (|>> nat\encode identifier$) indices))
+ type_vars (: (List Code) (map (|>> nat\encoded identifier$) indices))
zipped_type (` (All [(~+ type_vars) (~ g!return_type)]
(-> (-> (~+ type_vars) (~ g!return_type))
(~+ (map (: (-> Code Code) (function (_ var) (` (List (~ var)))))
@@ -497,7 +498,7 @@
vars+lists (|> indices
(map ++)
(map (function (_ idx)
- (let [base (nat\encode idx)]
+ (let [base (nat\encoded idx)]
[(identifier$ base)
(identifier$ ("lux text concat" base "'"))]))))
pattern (` [(~+ (map (function (_ [v vs]) (` (#.Item (~ v) (~ vs))))
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index 16929459e..d7a792cdc 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -11,7 +11,7 @@
[monad (#+ Monad do)]
[equivalence (#+ Equivalence)]
[monoid (#+ Monoid)]
- [fold (#+ Fold)]
+ [mix (#+ Mix)]
[predicate (#+ Predicate)]]
[control
["." maybe]
@@ -22,8 +22,8 @@
[data
["." product]
[collection
- ["." list ("#\." fold functor monoid)]
- ["." array (#+ Array) ("#\." functor fold)]]]
+ ["." list ("#\." mix functor monoid)]
+ ["." array (#+ Array) ("#\." functor mix)]]]
[macro
[syntax (#+ syntax:)]
["." code]]
@@ -179,8 +179,8 @@
(|> hierarchy
array.list
list.reversed
- (list\fold (function (_ sub acc) (list\compose (list' sub) acc))
- #.End))))
+ (list\mix (function (_ sub acc) (list\compose (list' sub) acc))
+ #.End))))
(type: .public (Row a)
{#level Level
@@ -235,8 +235,8 @@
(exception: incorrect_row_structure)
(exception: .public [a] (index_out_of_bounds {row (Row a)} {index Nat})
- (exception.report ["Size" (\ n.decimal encode (value@ #size row))]
- ["Index" (\ n.decimal encode index)]))
+ (exception.report ["Size" (\ n.decimal encoded (value@ #size row))]
+ ["Index" (\ n.decimal encoded index)]))
(exception: base_was_not_found)
@@ -346,7 +346,7 @@
(def: .public of_list
(All [a] (-> (List a) (Row a)))
- (list\fold ..suffix ..empty))
+ (list\mix ..suffix ..empty))
(def: .public (member? equivalence row val)
(All [a] (-> (Equivalence a) (Row a) a Bit))
@@ -384,29 +384,29 @@
(node\= (#Hierarchy (value@ #root v1))
(#Hierarchy (value@ #root v2))))))))
-(implementation: node_fold
- (Fold Node)
+(implementation: node_mix
+ (Mix Node)
- (def: (fold f init xs)
+ (def: (mix f init xs)
(case xs
(#Base base)
- (array\fold f init base)
+ (array\mix f init base)
(#Hierarchy hierarchy)
- (array\fold (function (_ node init') (fold f init' node))
- init
- hierarchy))))
+ (array\mix (function (_ node init') (mix f init' node))
+ init
+ hierarchy))))
-(implementation: .public fold
- (Fold Row)
+(implementation: .public mix
+ (Mix Row)
- (def: (fold f init xs)
- (let [(^open ".") node_fold]
- (fold f
- (fold f
- init
- (#Hierarchy (value@ #root xs)))
- (#Base (value@ #tail xs))))))
+ (def: (mix f init xs)
+ (let [(^open ".") node_mix]
+ (mix f
+ (mix f
+ init
+ (#Hierarchy (value@ #root xs)))
+ (#Base (value@ #tail xs))))))
(implementation: .public monoid
(All [a] (Monoid (Row a)))
@@ -414,7 +414,7 @@
(def: identity ..empty)
(def: (compose xs ys)
- (list\fold suffix xs (..list ys))))
+ (list\mix suffix xs (..list ys))))
(implementation: node_functor
(Functor Node)
@@ -441,13 +441,13 @@
(def: &functor ..functor)
- (def: (apply ff fa)
+ (def: (on fa ff)
(let [(^open ".") ..functor
- (^open ".") ..fold
+ (^open ".") ..mix
(^open ".") ..monoid
results (map (function (_ f) (map f fa))
ff)]
- (fold compose identity results))))
+ (mix compose identity results))))
(implementation: .public monad
(Monad Row)
@@ -457,15 +457,15 @@
(def: in (|>> row))
(def: join
- (let [(^open ".") ..fold
+ (let [(^open ".") ..mix
(^open ".") ..monoid]
- (fold (function (_ post pre) (compose pre post)) identity))))
+ (mix (function (_ post pre) (compose pre post)) identity))))
(def: .public reversed
(All [a] (-> (Row a) (Row a)))
(|>> ..list
list.reversed
- (list\fold suffix ..empty)))
+ (list\mix suffix ..empty)))
(template [<name> <array> <init> <op>]
[(def: .public <name>
diff --git a/stdlib/source/library/lux/data/collection/set.lux b/stdlib/source/library/lux/data/collection/set.lux
index bd18afe96..00edc5a47 100644
--- a/stdlib/source/library/lux/data/collection/set.lux
+++ b/stdlib/source/library/lux/data/collection/set.lux
@@ -8,7 +8,7 @@
[monoid (#+ Monoid)]]
[data
[collection
- ["." list ("#\." fold)]]]
+ ["." list ("#\." mix)]]]
[math
[number
["n" nat]]]]]
@@ -16,8 +16,6 @@
["#" dictionary (#+ Dictionary)]])
(type: .public (Set a)
- {#.doc (example "An un-ordered data-structure with unique items."
- "This means there is no repetition/duplication among the items.")}
(Dictionary a Any))
(def: .public member_hash
@@ -54,7 +52,7 @@
(def: .public (difference sub base)
(All [a] (-> (Set a) (Set a) (Set a)))
- (list\fold ..lacks base (..list sub)))
+ (list\mix ..lacks base (..list sub)))
(def: .public (intersection filter base)
(All [a] (-> (Set a) (Set a) (Set a)))
@@ -92,7 +90,7 @@
(def: .public (of_list hash elements)
(All [a] (-> (Hash a) (List a) (Set a)))
- (list\fold ..has (..empty hash) elements))
+ (list\mix ..has (..empty hash) elements))
(def: .public (sub? super sub)
(All [a] (-> (Set a) (Set a) Bit))
diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux
index b4786c825..f176dc46a 100644
--- a/stdlib/source/library/lux/data/collection/set/multi.lux
+++ b/stdlib/source/library/lux/data/collection/set/multi.lux
@@ -15,7 +15,7 @@
[abstract (#+ abstract: :abstraction :representation ^:representation)]]]]
["." //
[//
- ["." list ("#\." fold monoid)]
+ ["." list ("#\." mix monoid)]
["." dictionary (#+ Dictionary)]]])
(abstract: .public (Set a)
@@ -29,7 +29,7 @@
(def: .public size
(All [a] (-> (Set a) Nat))
- (|>> :representation dictionary.values (list\fold n.+ 0)))
+ (|>> :representation dictionary.values (list\mix n.+ 0)))
(def: .public (has multiplicity elem set)
(All [a] (-> Nat a (Set a) (Set a)))
@@ -62,9 +62,9 @@
(All [a] (-> (Set a) (List a)))
(|>> :representation
dictionary.entries
- (list\fold (function (_ [elem multiplicity] output)
- (list\compose (list.repeated multiplicity elem) output))
- #.End)))
+ (list\mix (function (_ [elem multiplicity] output)
+ (list\compose (list.repeated multiplicity elem) output))
+ #.End)))
(template [<name> <compose>]
[(def: .public (<name> parameter subject)
@@ -77,22 +77,22 @@
(def: .public (intersection parameter (^:representation subject))
(All [a] (-> (Set a) (Set a) (Set a)))
- (list\fold (function (_ [elem multiplicity] output)
- (..has (n.min (..multiplicity parameter elem)
- multiplicity)
- elem
- output))
- (..empty (dictionary.key_hash subject))
- (dictionary.entries subject)))
+ (list\mix (function (_ [elem multiplicity] output)
+ (..has (n.min (..multiplicity parameter elem)
+ multiplicity)
+ elem
+ output))
+ (..empty (dictionary.key_hash subject))
+ (dictionary.entries subject)))
(def: .public (difference parameter subject)
(All [a] (-> (Set a) (Set a) (Set a)))
(|> parameter
:representation
dictionary.entries
- (list\fold (function (_ [elem multiplicity] output)
- (..lacks multiplicity elem output))
- subject)))
+ (list\mix (function (_ [elem multiplicity] output)
+ (..lacks multiplicity elem output))
+ subject)))
(def: .public (sub? reference subject)
{#.doc (example "Is 'subject' a sub-set of 'reference'?")}
@@ -133,10 +133,10 @@
(def: (hash (^:representation set))
(let [[hash _] set]
- (list\fold (function (_ [elem multiplicity] acc)
- (|> elem (\ hash hash) (n.* multiplicity) (n.+ acc)))
- 0
- (dictionary.entries set)))))
+ (list\mix (function (_ [elem multiplicity] acc)
+ (|> elem (\ hash hash) (n.* multiplicity) (n.+ acc)))
+ 0
+ (dictionary.entries set)))))
)
(def: .public (member? set elem)
@@ -149,7 +149,7 @@
(def: .public (of_list hash subject)
(All [a] (-> (Hash a) (List a) (Set a)))
- (list\fold (..has 1) (..empty hash) subject))
+ (list\mix (..has 1) (..empty hash) subject))
(def: .public (of_set subject)
(All [a] (-> (//.Set a) (Set a)))
diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux
index 28bbf1876..d6d532d02 100644
--- a/stdlib/source/library/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/set/ordered.lux
@@ -6,7 +6,7 @@
[order (#+ Order)]]
[data
[collection
- ["." list ("#\." fold)]
+ ["." list ("#\." mix)]
[dictionary
["/" ordered]]]]
[type
@@ -50,11 +50,11 @@
(def: .public (of_list &order list)
(All [a] (-> (Order a) (List a) (Set a)))
- (list\fold has (..empty &order) list))
+ (list\mix has (..empty &order) list))
(def: .public (union left right)
(All [a] (-> (Set a) (Set a) (Set a)))
- (list\fold ..has right (..list left)))
+ (list\mix ..has right (..list left)))
(def: .public (intersection left right)
(All [a] (-> (Set a) (Set a) (Set a)))
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index 112932a50..bdf10e85b 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -4,14 +4,14 @@
[abstract
[functor (#+ Functor)]
[equivalence (#+ Equivalence)]
- [fold (#+ Fold)]
+ [mix (#+ Mix)]
[monad (#+ do)]]
[control
["<>" parser
["<.>" code (#+ Parser)]]]
[data
[collection
- ["." list ("#\." monad fold)]]]
+ ["." list ("#\." monad mix)]]]
[macro
[syntax (#+ syntax:)]
["." code]]]])
@@ -80,11 +80,11 @@
#children (list\map (map f)
(value@ #children fa))}))
-(implementation: .public fold
- (Fold Tree)
+(implementation: .public mix
+ (Mix Tree)
- (def: (fold f init tree)
- (list\fold (function (_ tree' init') (fold f init' tree'))
- (f (value@ #value tree)
- init)
- (value@ #children tree))))
+ (def: (mix f init tree)
+ (list\mix (function (_ tree' init') (mix f init' tree'))
+ (f (value@ #value tree)
+ init)
+ (value@ #children tree))))
diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux
index 6d1709c55..1c99353bc 100644
--- a/stdlib/source/library/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux
@@ -14,7 +14,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#\." functor fold monoid)]]]]]
+ ["." list ("#\." functor monoid)]]]]]
["." // (#+ Tree) ("#\." functor)])
(type: (Family Zipper a)
diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux
index d34918cf2..fb67c971f 100644
--- a/stdlib/source/library/lux/data/color.lux
+++ b/stdlib/source/library/lux/data/color.lux
@@ -9,14 +9,8 @@
[parser
["<.>" code]]]
[data
- ["." text
- ["%" format (#+ format)]]
[collection
["." list ("#\." functor)]]]
- [macro
- [syntax (#+ syntax:)]
- ["." template]
- ["." code]]
["." math
[number
["n" nat]
@@ -355,14 +349,8 @@
+0.0
luminance])))
-(syntax: (color_scheme_documentation [name <code>.local_identifier])
- (let [name (text.replaced "_" "-" name)
- g!documentation (code.text (format "A " name " color scheme."))]
- (in (list (` {#.doc (.example (~ g!documentation))})))))
-
(template [<name> <1> <2>]
[(`` (def: .public (<name> color)
- (~~ (..color_scheme_documentation <name>))
(-> Color [Color Color Color])
(let [[hue saturation luminance] (hsl color)]
[color
@@ -380,7 +368,6 @@
(template [<name> <1> <2> <3>]
[(`` (def: .public (<name> color)
- (~~ (..color_scheme_documentation <name>))
(-> Color [Color Color Color Color])
(let [[hue saturation luminance] (hsb color)]
[color
diff --git a/stdlib/source/library/lux/data/color/named.lux b/stdlib/source/library/lux/data/color/named.lux
index 5e5e5bc65..43fd25f16 100644
--- a/stdlib/source/library/lux/data/color/named.lux
+++ b/stdlib/source/library/lux/data/color/named.lux
@@ -7,7 +7,6 @@
(template [<red> <green> <blue> <name>]
[(`` (def: .public <name>
- {#.doc (example (~~ (..documentation <red> <green> <blue> <name>)))}
Color
(//.of_rgb {#//.red (hex <red>)
#//.green (hex <green>)
diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux
index bb0510528..85eb0534d 100644
--- a/stdlib/source/library/lux/data/format/binary.lux
+++ b/stdlib/source/library/lux/data/format/binary.lux
@@ -165,7 +165,7 @@
(template [<name> <binary>]
[(def: .public <name>
(Writer Text)
- (|>> (\ utf8.codec encode) <binary>))]
+ (|>> (\ utf8.codec encoded) <binary>))]
[utf8/8 ..binary/8]
[utf8/16 ..binary/16]
@@ -188,7 +188,7 @@
(^open "specification\.") ..monoid
[size mutation] (|> value
(row\map valueW)
- (\ row.fold fold
+ (\ row.mix mix
(function (_ post pre)
(specification\compose pre post))
specification\identity))]
diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux
index 8b3a9270c..75e886e0d 100644
--- a/stdlib/source/library/lux/data/format/css.lux
+++ b/stdlib/source/library/lux/data/format/css.lux
@@ -53,8 +53,8 @@
(-> Font (CSS Special))
(let [with_unicode (case (value@ #/font.unicode_range font)
(#.Some unicode_range)
- (let [unicode_range' (format "U+" (\ nat.hex encode (value@ #/font.start unicode_range))
- "-" (\ nat.hex encode (value@ #/font.end unicode_range)))]
+ (let [unicode_range' (format "U+" (\ nat.hex encoded (value@ #/font.start unicode_range))
+ "-" (\ nat.hex encoded (value@ #/font.end unicode_range)))]
(list ["unicode-range" unicode_range']))
#.None
diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux
index 3a8daf5c0..5bb422c0d 100644
--- a/stdlib/source/library/lux/data/format/html.lux
+++ b/stdlib/source/library/lux/data/format/html.lux
@@ -9,7 +9,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#\." functor fold)]]]
+ ["." list ("#\." functor mix)]]]
[type
abstract]
[host
@@ -219,7 +219,7 @@
(def: .public (svg attributes content)
(-> Attributes XML Element)
(|> content
- (\ xml.codec encode)
+ (\ xml.codec encoded)
(..raw "svg" attributes)))
(type: .public Coord
@@ -300,7 +300,7 @@
(#.Item head tail)
(..tag "map" attributes
- (list\fold (function.flipped ..and) head tail)))))
+ (list\mix (function.flipped ..and) head tail)))))
(template [<name> <tag> <type>]
[(def: .public <name>
@@ -465,7 +465,7 @@
(#.Item head tail)
(..tag "dl" attributes
- (list\fold (function.flipped ..and) head tail))))
+ (list\mix (function.flipped ..and) head tail))))
(def: .public p ..paragraph)
@@ -524,7 +524,7 @@
(#.Item first rest)
(..and head
(..table_body
- (list\fold (function.flipped ..and) first rest))))
+ (list\mix (function.flipped ..and) first rest))))
content (case footer
#.None
content
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index ed2643efa..bcfd44f80 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -19,7 +19,7 @@
["." product]
["." text ("#\." equivalence monoid)]
[collection
- ["." list ("#\." fold functor)]
+ ["." list ("#\." mix functor)]
["." row (#+ Row row) ("#\." monad)]
["." dictionary (#+ Dictionary)]]]
[macro
@@ -169,25 +169,25 @@
[(#Array xs) (#Array ys)]
(and (n.= (row.size xs) (row.size ys))
- (list\fold (function (_ idx prev)
- (and prev
- (maybe.else #0
- (do maybe.monad
- [x' (row.item idx xs)
- y' (row.item idx ys)]
- (in (= x' y'))))))
- #1
- (list.indices (row.size xs))))
+ (list\mix (function (_ idx prev)
+ (and prev
+ (maybe.else #0
+ (do maybe.monad
+ [x' (row.item idx xs)
+ y' (row.item idx ys)]
+ (in (= x' y'))))))
+ #1
+ (list.indices (row.size xs))))
[(#Object xs) (#Object ys)]
(and (n.= (dictionary.size xs) (dictionary.size ys))
- (list\fold (function (_ [xk xv] prev)
- (and prev
- (case (dictionary.value xk ys)
- #.None #0
- (#.Some yv) (= xv yv))))
- #1
- (dictionary.entries xs)))
+ (list\mix (function (_ [xk xv] prev)
+ (and prev
+ (case (dictionary.value xk ys)
+ #.None #0
+ (#.Some yv) (= xv yv))))
+ #1
+ (dictionary.entries xs)))
_
#0)))
@@ -210,7 +210,7 @@
(-> Number Text)
(|>> (case>
(^or +0.0 -0.0) "0.0"
- value (let [raw (\ f.decimal encode value)]
+ value (let [raw (\ f.decimal encoded value)]
(if (f.< +0.0 value)
raw
(|> raw (text.split_at 1) maybe.trusted product.right))))))
@@ -327,7 +327,7 @@
signed?' (<>.parses? (<text>.this "-"))
offset (<text>.many <text>.decimal)]
(in ($_ text\compose mark (if signed?' "-" "") offset))))]
- (case (f\decode ($_ text\compose (if signed? "-" "") digits "." decimals exp))
+ (case (f\decoded ($_ text\compose (if signed? "-" "") digits "." decimals exp))
(#try.Failure message)
(<>.failure message)
@@ -406,5 +406,5 @@
(implementation: .public codec
(Codec Text JSON)
- (def: encode ..format)
- (def: decode (<text>.result json_parser)))
+ (def: encoded ..format)
+ (def: decoded (<text>.result json_parser)))
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 59a24a875..f452a2693 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -19,8 +19,8 @@
["." format #_
["#" binary (#+ Writer) ("#\." monoid)]]
[collection
- ["." list ("#\." fold)]
- ["." row (#+ Row) ("#\." fold)]]]
+ ["." list ("#\." mix)]
+ ["." row (#+ Row) ("#\." mix)]]]
[math
["." number
["n" nat]
@@ -62,7 +62,7 @@
Nat
(|> ..octal_size
(list.repeated <size>)
- (list\fold n.* 1)
+ (list\mix n.* 1)
++))
(exception: .public (<exception> {value Nat})
@@ -90,10 +90,10 @@
(let [suffix <suffix>
padded_size (n.+ (text.size suffix) <size>)]
(|>> :representation
- (\ n.octal encode)
+ (\ n.octal encoded)
(..octal_padding <size>)
(text.suffix suffix)
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
(format.segment padded_size))))
(def: <coercion>
@@ -134,25 +134,25 @@
(Parser Small)
(do <>.monad
[digits (<binary>.segment ..small_size)
- digits (<>.lifted (\ utf8.codec decode digits))
+ digits (<>.lifted (\ utf8.codec decoded digits))
_ ..small_suffix]
(<>.lifted
(do {! try.monad}
- [value (\ n.octal decode digits)]
+ [value (\ n.octal decoded digits)]
(..small value)))))
(def: big_parser
(Parser Big)
(do <>.monad
[digits (<binary>.segment ..big_size)
- digits (<>.lifted (\ utf8.codec decode digits))
+ digits (<>.lifted (\ utf8.codec decoded digits))
end <binary>.bits/8
_ (let [expected (`` (char (~~ (static ..blank))))]
(<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end)))]
(<>.lifted
(do {! try.monad}
- [value (\ n.octal decode digits)]
+ [value (\ n.octal decoded digits)]
(..big value)))))
(abstract: Checksum
@@ -178,7 +178,7 @@
(def: checksum_checksum
(|> ..dummy_checksum
:representation
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
..checksum))
(def: checksum_code
@@ -186,7 +186,7 @@
(|>> ..checksum
..as_small
..from_small
- (\ n.octal encode)
+ (\ n.octal encoded)
(..octal_padding ..small_size)
(text.suffix ..checksum_suffix)
:abstraction))
@@ -196,17 +196,17 @@
(let [padded_size (n.+ (text.size ..checksum_suffix)
..small_size)]
(|>> :representation
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
(format.segment padded_size))))
(def: checksum_parser
(Parser [Nat Checksum])
(do <>.monad
[ascii (<binary>.segment ..small_size)
- digits (<>.lifted (\ utf8.codec decode ascii))
+ digits (<>.lifted (\ utf8.codec decoded ascii))
_ ..small_suffix
value (<>.lifted
- (\ n.octal decode digits))]
+ (\ n.octal decoded digits))]
(in [value
(:abstraction (format digits ..checksum_suffix))])))
)
@@ -217,7 +217,7 @@
(def: ascii?
(-> Text Bit)
- (|>> (\ utf8.codec encode)
+ (|>> (\ utf8.codec encoded)
(binary.aggregate (function (_ char verdict)
(.and verdict
(n.<= ..last_ascii char)))
@@ -236,7 +236,7 @@
0 (#try.Success string)
size (loop [end (-- size)]
(case end
- 0 (#try.Success (\ utf8.codec encode ""))
+ 0 (#try.Success (\ utf8.codec encoded ""))
_ (do try.monad
[last_char (binary.read/8! end string)]
(`` (case (.nat last_char)
@@ -261,7 +261,7 @@
(def: .public (<in> value)
(-> <representation> (Try <type>))
(if (..ascii? value)
- (if (|> value (\ utf8.codec encode) binary.size (n.<= <size>))
+ (if (|> value (\ utf8.codec encoded) binary.size (n.<= <size>))
(#try.Success (:abstraction value))
(exception.except <exception> [value]))
(exception.except ..not_ascii [value])))
@@ -276,7 +276,7 @@
padded_size (n.+ (text.size suffix) <size>)]
(|>> :representation
(text.suffix suffix)
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
(format.segment padded_size))))
(def: <parser>
@@ -290,7 +290,7 @@
(<>.lifted
(do {! try.monad}
[ascii (..un_padded string)
- text (\ utf8.codec decode ascii)]
+ text (\ utf8.codec decoded ascii)]
(<in> text)))))
(def: .public <none>
@@ -320,7 +320,7 @@
(let [padded_size (n.+ (text.size ..null)
..magic_size)]
(|>> :representation
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
(format.segment padded_size))))
(def: magic_parser
@@ -333,7 +333,7 @@
(n.= expected end))]
(<>.lifted
(\ try.monad map (|>> :abstraction)
- (\ utf8.codec decode string)))))
+ (\ utf8.codec decoded string)))))
)
(def: block_size Size 512)
@@ -530,7 +530,7 @@
Nat
(|> ..octal_size
(list.repeated ..content_size)
- (list\fold n.* 1)))
+ (list\mix n.* 1)))
(abstract: .public Content
{}
@@ -739,10 +739,10 @@
(Writer Tar)
(let [end_of_archive (binary.empty ..end_of_archive_size)]
(function (_ tar)
- (format\compose (row\fold (function (_ next total)
- (format\compose total (..entry_writer next)))
- format\identity
- tar)
+ (format\compose (row\mix (function (_ next total)
+ (format\compose total (..entry_writer next)))
+ format\identity
+ tar)
(format.segment ..end_of_archive_size end_of_archive)))))
(exception: .public (wrong_checksum {expected Nat} {actual Nat})
@@ -763,7 +763,7 @@
(-> Checksum Binary Nat)
(let [|checksum| (|> checksum
..from_checksum
- (\ utf8.codec encode)
+ (\ utf8.codec encoded)
..checksum)]
(|> (..checksum header)
(n.- |checksum|)
diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux
index 4e358f91d..064476a7f 100644
--- a/stdlib/source/library/lux/data/format/xml.lux
+++ b/stdlib/source/library/lux/data/format/xml.lux
@@ -127,8 +127,8 @@
(<>.after (<text>.this "/"))
(<text>.enclosed ["<" ">"]))]
(<>.assertion ($_ text\compose "Close tag does not match open tag." text.new_line
- "Expected: " (name\encode expected) text.new_line
- " Actual: " (name\encode actual) text.new_line)
+ "Expected: " (name\encoded expected) text.new_line
+ " Actual: " (name\encoded actual) text.new_line)
(name\= expected actual))))
(def: comment^
@@ -229,7 +229,7 @@
(implementation: .public codec
(Codec Text XML)
- (def: encode
+ (def: encoded
(let [attributes (: (-> Attrs Text)
(function (_ attrs)
(|> attrs
@@ -269,7 +269,7 @@
text.together)
text.new_line prefix "</" tag ">")))))
))))
- (def: decode
+ (def: decoded
(<text>.result ..xml^)))
(implementation: .public equivalence
diff --git a/stdlib/source/library/lux/data/identity.lux b/stdlib/source/library/lux/data/identity.lux
index 72ae09d38..300c0cd7b 100644
--- a/stdlib/source/library/lux/data/identity.lux
+++ b/stdlib/source/library/lux/data/identity.lux
@@ -21,7 +21,8 @@
(Apply Identity)
(def: &functor ..functor)
- (def: (apply ff fa) (ff fa)))
+ (def: (on fa ff)
+ (ff fa)))
(implementation: .public monad
(Monad Identity)
diff --git a/stdlib/source/library/lux/data/name.lux b/stdlib/source/library/lux/data/name.lux
index 3dfa6dcce..99d158095 100644
--- a/stdlib/source/library/lux/data/name.lux
+++ b/stdlib/source/library/lux/data/name.lux
@@ -45,12 +45,12 @@
(implementation: .public codec
(Codec Text Name)
- (def: (encode [module short])
+ (def: (encoded [module short])
(case module
"" short
_ ($_ text\compose module ..separator short)))
- (def: (decode input)
+ (def: (decoded input)
(case (text.all_split_by ..separator input)
(^ (list short))
(#.Right ["" short])
diff --git a/stdlib/source/library/lux/data/product.lux b/stdlib/source/library/lux/data/product.lux
index 9a3bf40dc..1e0bc9c96 100644
--- a/stdlib/source/library/lux/data/product.lux
+++ b/stdlib/source/library/lux/data/product.lux
@@ -1,5 +1,4 @@
(.module:
- {#.doc "Functionality for working with tuples (particularly 2-tuples/pairs)."}
[library
[lux #*
[abstract
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index 70b0360b1..5a1b8a981 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -13,7 +13,7 @@
["." maybe]]
[data
[collection
- ["." list ("#\." fold)]]]
+ ["." list ("#\." mix)]]]
[math
[number
["n" nat]
@@ -288,7 +288,7 @@
(-> (List Text) Text)
(let [(^open ".") ..monoid]
(|>> list.reversed
- (list\fold compose identity))))
+ (list\mix compose identity))))
(def: .public (interposed separator texts)
(-> Text (List Text) Text)
diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux
index 08f640648..e23a11f63 100644
--- a/stdlib/source/library/lux/data/text/buffer.lux
+++ b/stdlib/source/library/lux/data/text/buffer.lux
@@ -11,7 +11,7 @@
["%" format (#+ format)]]
[collection
["." array]
- ["." row (#+ Row) ("#\." fold)]]]
+ ["." row (#+ Row) ("#\." mix)]]]
[math
[number
["n" nat]]]
@@ -108,9 +108,9 @@
@.lua <jvm>}
... default
(|>> :representation
- (row\fold (function (_ chunk total)
- (n.+ (//.size chunk) total))
- 0)))))
+ (row\mix (function (_ chunk total)
+ (n.+ (//.size chunk) total))
+ 0)))))
(def: .public (text buffer)
(-> Buffer Text)
@@ -128,8 +128,8 @@
@.lua (let [[capacity transform] (:representation buffer)]
(table/concat [(transform (array.empty 0)) ""]))}
... default
- (row\fold (function (_ chunk total)
- (format total chunk))
- ""
- (:representation buffer)))))
+ (row\mix (function (_ chunk total)
+ (format total chunk))
+ ""
+ (:representation buffer)))))
))
diff --git a/stdlib/source/library/lux/data/text/encoding.lux b/stdlib/source/library/lux/data/text/encoding.lux
index fbe70b92d..b1947bf67 100644
--- a/stdlib/source/library/lux/data/text/encoding.lux
+++ b/stdlib/source/library/lux/data/text/encoding.lux
@@ -14,7 +14,6 @@
(template [<name> <encoding>]
[(`` (def: .public <name>
- {#.doc (example (~~ (template.text ["'" <encoding> "' text encoding. "])))}
Encoding
(:abstraction <encoding>)))]
diff --git a/stdlib/source/library/lux/data/text/encoding/utf8.lux b/stdlib/source/library/lux/data/text/encoding/utf8.lux
index 0adb95c82..e7d9b611c 100644
--- a/stdlib/source/library/lux/data/text/encoding/utf8.lux
+++ b/stdlib/source/library/lux/data/text/encoding/utf8.lux
@@ -24,8 +24,8 @@
... On Node
(ffi.import: Buffer
["#::."
- (#static from #as from|encode [ffi.String ffi.String] Buffer)
- (#static from #as from|decode [Uint8Array] Buffer)
+ (#static from #as from|encoded [ffi.String ffi.String] Buffer)
+ (#static from #as from|decoded [Uint8Array] Buffer)
(toString [ffi.String] ffi.String)])
... On the browser
@@ -62,7 +62,7 @@
(ffi.import: (utf8->string [Binary] Text)))}
(as_is)))
-(def: (encode value)
+(def: (encoded value)
(-> Text Binary)
(for {@.old
(java/lang/String::getBytes (//.name //.utf_8)
@@ -80,7 +80,7 @@
(:as Binary ("js object do" "getBytes" value ["utf8"]))
ffi.on_node_js?
- (|> (Buffer::from|encode [value "utf8"])
+ (|> (Buffer::from|encoded [value "utf8"])
... This coercion is valid as per NodeJS's documentation:
... https://nodejs.org/api/buffer.html#buffer_buffers_and_typedarrays
(:as Uint8Array))
@@ -111,7 +111,7 @@
@.scheme
(..string->utf8 value)}))
-(def: (decode value)
+(def: (decoded value)
(-> Binary (Try Text))
(with_expansions [<jvm> (#try.Success (java/lang/String::new value (//.name //.utf_8)))]
(for {@.old <jvm>
@@ -124,7 +124,7 @@
#try.Success)
ffi.on_node_js?
- (|> (Buffer::from|decode [value])
+ (|> (Buffer::from|decoded [value])
(Buffer::toString ["utf8"])
#try.Success)
@@ -158,8 +158,7 @@
#try.Success)})))
(implementation: .public codec
- {#.doc (example "A codec for binary encoding of text as UTF-8.")}
(Codec Binary Text)
- (def: encode ..encode)
- (def: decode ..decode))
+ (def: encoded ..encoded)
+ (def: decoded ..decoded))
diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux
index dc847995a..4d99b6c8c 100644
--- a/stdlib/source/library/lux/data/text/escape.lux
+++ b/stdlib/source/library/lux/data/text/escape.lux
@@ -94,7 +94,7 @@
(def: (unicode_escaped char pre_offset pre_limit previous current)
(-> Char Nat Nat Text Text [Text Text Nat])
- (let [code (\ n.hex encode char)
+ (let [code (\ n.hex encoded char)
replacement (format ..sigil "u"
(case ("lux text size" code)
1 (format "000" code)
@@ -178,7 +178,7 @@
(-> Nat Text Text Nat (Try [Text Text Nat]))
(case (|> current
("lux text clip" (n.+ ..ascii_escape_offset offset) ..code_size)
- (\ n.hex decode))
+ (\ n.hex decoded))
(#try.Success char)
(let [limit' (|> limit (n.- offset) (n.- ..unicode_escape_offset))]
(#try.Success [(format previous
diff --git a/stdlib/source/library/lux/data/text/format.lux b/stdlib/source/library/lux/data/text/format.lux
index de6482910..cd953ef05 100644
--- a/stdlib/source/library/lux/data/text/format.lux
+++ b/stdlib/source/library/lux/data/text/format.lux
@@ -56,35 +56,35 @@
(Format <type>)
<formatter>)]
- [bit Bit (\ bit.codec encode)]
- [nat Nat (\ nat.decimal encode)]
- [int Int (\ int.decimal encode)]
- [rev Rev (\ rev.decimal encode)]
- [frac Frac (\ frac.decimal encode)]
+ [bit Bit (\ bit.codec encoded)]
+ [nat Nat (\ nat.decimal encoded)]
+ [int Int (\ int.decimal encoded)]
+ [rev Rev (\ rev.decimal encoded)]
+ [frac Frac (\ frac.decimal encoded)]
[text Text text.format]
- [ratio ratio.Ratio (\ ratio.codec encode)]
- [name Name (\ name.codec encode)]
+ [ratio ratio.Ratio (\ ratio.codec encoded)]
+ [name Name (\ name.codec encoded)]
[location Location location.format]
[code Code code.format]
[type Type type.format]
- [instant instant.Instant (\ instant.codec encode)]
- [duration duration.Duration (\ duration.codec encode)]
- [date date.Date (\ date.codec encode)]
- [time time.Time (\ time.codec encode)]
- [day day.Day (\ day.codec encode)]
- [month month.Month (\ month.codec encode)]
+ [instant instant.Instant (\ instant.codec encoded)]
+ [duration duration.Duration (\ duration.codec encoded)]
+ [date date.Date (\ date.codec encoded)]
+ [time time.Time (\ time.codec encoded)]
+ [day day.Day (\ day.codec encoded)]
+ [month month.Month (\ month.codec encoded)]
- [xml xml.XML (\ xml.codec encode)]
- [json json.JSON (\ json.codec encode)]
+ [xml xml.XML (\ xml.codec encoded)]
+ [json json.JSON (\ json.codec encoded)]
)
(template [<type> <format>,<codec>]
[(`` (template [<format> <codec>]
[(def: .public <format>
(Format <type>)
- (\ <codec> encode))]
+ (\ <codec> encoded))]
(~~ (template.spliced <format>,<codec>))))]
@@ -113,7 +113,7 @@
(def: .public (mod modular)
(All [m] (Format (modular.Mod m)))
(let [codec (modular.codec (modular.modulus modular))]
- (\ codec encode modular)))
+ (\ codec encoded modular)))
(def: .public (list formatter)
(All [a] (-> (Format a) (Format (List a))))
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 8c626ed6e..fa822c33b 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -14,7 +14,7 @@
[data
["." product]
[collection
- ["." list ("#\." fold monad)]]]
+ ["." list ("#\." mix monad)]]]
[macro (#+ with_identifiers)
[syntax (#+ syntax:)]
["." code]]
@@ -119,10 +119,10 @@
[_ (in [])
init re_user_class^'
rest (<>.some (<>.after (<text>.this "&&") (<text>.enclosed ["[" "]"] re_user_class^')))]
- (in (list\fold (function (_ refinement base)
- (` ((~! refine^) (~ refinement) (~ base))))
- init
- rest))))
+ (in (list\mix (function (_ refinement base)
+ (` ((~! refine^) (~ refinement) (~ base))))
+ init
+ rest))))
(def: blank^
(Parser Text)
@@ -195,7 +195,7 @@
(<>.either (do <>.monad
[_ (<text>.this "\")
id number^]
- (in (` ((~! ..copy) (~ (code.identifier ["" (n\encode id)]))))))
+ (in (` ((~! ..copy) (~ (code.identifier ["" (n\encoded id)]))))))
(do <>.monad
[_ (<text>.this "\k<")
captured_name name_part^
@@ -282,38 +282,38 @@
(re_scoped^ current_module)))
.let [g!total (code.identifier ["" "0total"])
g!temp (code.identifier ["" "0temp"])
- [_ names steps] (list\fold (: (-> (Either Code [Re_Group Code])
- [Nat (List Code) (List (List Code))]
- [Nat (List Code) (List (List Code))])
- (function (_ part [idx names steps])
- (case part
- (^or (#.Left complex) (#.Right [#Non_Capturing complex]))
- [idx
- names
- (list& (list g!temp complex
- (` .let) (` [(~ g!total) (\ (~! //.monoid) (~' compose) (~ g!total) (~ g!temp))]))
- steps)]
-
- (#.Right [(#Capturing [?name num_captures]) scoped])
- (let [[idx! name!] (case ?name
- (#.Some _name)
- [idx (code.identifier ["" _name])]
-
- #.None
- [(++ idx) (code.identifier ["" (n\encode idx)])])
- access (if (n.> 0 num_captures)
- (` ((~! product.left) (~ name!)))
- name!)]
- [idx!
- (list& name! names)
- (list& (list name! scoped
- (` .let) (` [(~ g!total) (\ (~! //.monoid) (~' compose) (~ g!total) (~ access))]))
- steps)])
- )))
- [0
- (: (List Code) (list))
- (: (List (List Code)) (list))]
- parts)]]
+ [_ names steps] (list\mix (: (-> (Either Code [Re_Group Code])
+ [Nat (List Code) (List (List Code))]
+ [Nat (List Code) (List (List Code))])
+ (function (_ part [idx names steps])
+ (case part
+ (^or (#.Left complex) (#.Right [#Non_Capturing complex]))
+ [idx
+ names
+ (list& (list g!temp complex
+ (` .let) (` [(~ g!total) (\ (~! //.monoid) (~' compose) (~ g!total) (~ g!temp))]))
+ steps)]
+
+ (#.Right [(#Capturing [?name num_captures]) scoped])
+ (let [[idx! name!] (case ?name
+ (#.Some _name)
+ [idx (code.identifier ["" _name])]
+
+ #.None
+ [(++ idx) (code.identifier ["" (n\encoded idx)])])
+ access (if (n.> 0 num_captures)
+ (` ((~! product.left) (~ name!)))
+ name!)]
+ [idx!
+ (list& name! names)
+ (list& (list name! scoped
+ (` .let) (` [(~ g!total) (\ (~! //.monoid) (~' compose) (~ g!total) (~ access))]))
+ steps)])
+ )))
+ [0
+ (: (List Code) (list))
+ (: (List (List Code)) (list))]
+ parts)]]
(in [(if capturing?
(list.size names)
0)
@@ -374,7 +374,7 @@
tail (<>.some (<>.after (<text>.this "|") sub^))]
(if (list.empty? tail)
(in head)
- (in [(list\fold n.max (product.left head) (list\map product.left tail))
+ (in [(list\mix n.max (product.left head) (list\map product.left tail))
(` ($_ ((~ (if capturing?
(` (~! |||^))
(` (~! |||_^)))))
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index be47d038a..ef489af08 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -5,7 +5,7 @@
[equivalence (#+ Equivalence)]]
[data
[collection
- ["." list ("#\." fold functor)]
+ ["." list ("#\." mix functor)]
["." set ("#\." equivalence)]
["." tree #_
["#" finger (#+ Tree)]]]]
@@ -45,11 +45,11 @@
(def: .public (set [head tail])
(-> [Block (List Block)] Set)
- (list\fold (: (-> Block Set Set)
- (function (_ block set)
- (..composite (..singleton block) set)))
- (..singleton head)
- tail))
+ (list\mix (: (-> Block Set Set)
+ (function (_ block set)
+ (..composite (..singleton block) set)))
+ (..singleton head)
+ tail))
(def: character/0
Set