aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/poly/lux/abstract/equivalence.lux16
-rw-r--r--stdlib/source/poly/lux/abstract/functor.lux20
-rw-r--r--stdlib/source/poly/lux/data/format/json.lux32
3 files changed, 34 insertions, 34 deletions
diff --git a/stdlib/source/poly/lux/abstract/equivalence.lux b/stdlib/source/poly/lux/abstract/equivalence.lux
index e531aa9dd..e65bd5b5e 100644
--- a/stdlib/source/poly/lux/abstract/equivalence.lux
+++ b/stdlib/source/poly/lux/abstract/equivalence.lux
@@ -43,7 +43,7 @@
(poly: .public equivalence
(`` (do [! <>.monad]
- [.let [g!_ (code.local_symbol "_____________")]
+ [.let [g!_ (code.local "_____________")]
*env* <type>.env
inputT <type>.next
.let [@Equivalence (is (-> Type Code)
@@ -109,9 +109,9 @@
(do !
[members (<type>.variant (<>.many equivalence))
.let [last (-- (list.size members))
- g!_ (code.local_symbol "_____________")
- g!left (code.local_symbol "_____________left")
- g!right (code.local_symbol "_____________right")]]
+ g!_ (code.local "_____________")
+ g!left (code.local "_____________left")
+ g!right (code.local "_____________right")]]
(in (` (is (~ (@Equivalence inputT))
(function ((~ g!_) (~ g!left) (~ g!right))
(case [(~ g!left) (~ g!right)]
@@ -129,10 +129,10 @@
... Tuples
(do !
[g!eqs (<type>.tuple (<>.many equivalence))
- .let [g!_ (code.local_symbol "_____________")
+ .let [g!_ (code.local "_____________")
indices (list.indices (list.size g!eqs))
- g!lefts (list#each (|>> nat#encoded (text#composite "left") code.local_symbol) indices)
- g!rights (list#each (|>> nat#encoded (text#composite "right") code.local_symbol) indices)]]
+ g!lefts (list#each (|>> nat#encoded (text#composite "left") code.local) indices)
+ g!rights (list#each (|>> nat#encoded (text#composite "right") code.local) indices)]]
(in (` (is (~ (@Equivalence inputT))
(function ((~ g!_) [(~+ g!lefts)] [(~+ g!rights)])
(and (~+ (|> (list.zipped/3 g!eqs g!lefts g!rights)
@@ -141,7 +141,7 @@
... Type recursion
(do !
[[g!self bodyC] (<type>.recursive equivalence)
- .let [g!_ (code.local_symbol "_____________")]]
+ .let [g!_ (code.local "_____________")]]
(in (` (is (~ (@Equivalence inputT))
((~! /.rec) (.function ((~ g!_) (~ g!self))
(~ bodyC)))))))
diff --git a/stdlib/source/poly/lux/abstract/functor.lux b/stdlib/source/poly/lux/abstract/functor.lux
index 52f237a54..c22faabe2 100644
--- a/stdlib/source/poly/lux/abstract/functor.lux
+++ b/stdlib/source/poly/lux/abstract/functor.lux
@@ -26,10 +26,10 @@
(poly: .public functor
(do [! p.monad]
- [.let [g!_ (code.local_symbol "____________")
- type_funcC (code.local_symbol "____________type_funcC")
- funcC (code.local_symbol "____________funcC")
- inputC (code.local_symbol "____________inputC")]
+ [.let [g!_ (code.local "____________")
+ type_funcC (code.local "____________type_funcC")
+ funcC (code.local "____________funcC")
+ inputC (code.local "____________inputC")]
*env* <type>.env
inputT <type>.next
[polyC varsC non_functorT] (<type>.local (list inputT)
@@ -39,7 +39,7 @@
(function (_ unwrappedT)
(if (n.= 1 num_vars)
(` ((~! /.Functor) (~ (poly.code *env* unwrappedT))))
- (let [paramsC (|> num_vars -- list.indices (list#each (|>> %.nat code.local_symbol)))]
+ (let [paramsC (|> num_vars -- list.indices (list#each (|>> %.nat code.local)))]
(` (All ((~ g!_) (~+ paramsC))
((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
Arg<?> (is (-> Code (<type>.Parser Code))
@@ -48,7 +48,7 @@
... Type-var
(do p.monad
[.let [varI (|> num_vars (n.* 2) --)]
- _ (<type>.parameter! varI)]
+ _ (<type>.this_parameter varI)]
(in (` ((~ funcC) (~ valueC)))))
... Variants
(do !
@@ -69,7 +69,7 @@
(<type>.tuple (loop [idx 0
pairsCC (is (List [Code Code])
(list))]
- (p.either (let [slotC (|> idx %.nat (format "____________slot") code.local_symbol)]
+ (p.either (let [slotC (|> idx %.nat (format "____________slot") code.local)]
(do !
[_ (in [])
memberC (Arg<?> slotC)]
@@ -82,13 +82,13 @@
... Functions
(do !
[_ (in [])
- .let [g! (code.local_symbol "____________")
- outL (code.local_symbol "____________outL")]
+ .let [g! (code.local "____________")
+ outL (code.local "____________outL")]
[inT+ outC] (<type>.function (p.many <type>.any)
(Arg<?> outL))
.let [inC+ (|> (list.size inT+)
list.indices
- (list#each (|>> %.nat (format "____________inC") code.local_symbol)))]]
+ (list#each (|>> %.nat (format "____________inC") code.local)))]]
(in (` (function ((~ g!) (~+ inC+))
(let [(~ outL) ((~ valueC) (~+ inC+))]
(~ outC))))))
diff --git a/stdlib/source/poly/lux/data/format/json.lux b/stdlib/source/poly/lux/data/format/json.lux
index 67f6fb464..e7b0bd1fe 100644
--- a/stdlib/source/poly/lux/data/format/json.lux
+++ b/stdlib/source/poly/lux/data/format/json.lux
@@ -100,7 +100,7 @@
(with_expansions
[<basic> (template [<matcher> <encoder>]
[(do !
- [.let [g!_ (code.local_symbol "_______")]
+ [.let [g!_ (code.local "_______")]
_ <matcher>]
(in (` (is (~ (@JSON#encoded inputT))
<encoder>))))]
@@ -124,7 +124,7 @@
[month.Month month.codec])]
(do [! <>.monad]
[*env* <type>.env
- .let [g!_ (code.local_symbol "_______")
+ .let [g!_ (code.local "_______")
@JSON#encoded (is (-> Type Code)
(function (_ type)
(` (-> (~ (poly.code *env* type)) /.JSON))))]
@@ -138,9 +138,9 @@
(in (` (is (~ (@JSON#encoded inputT))
(# (~! qty_codec) (~' encoded))))))
(do !
- [.let [g!_ (code.local_symbol "_______")
- g!key (code.local_symbol "_______key")
- g!val (code.local_symbol "_______val")]
+ [.let [g!_ (code.local "_______")
+ g!key (code.local "_______key")
+ g!val (code.local "_______val")]
[_ _ =val=] (<type>.applied ($_ <>.and
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
@@ -164,8 +164,8 @@
(in (` (is (~ (@JSON#encoded inputT))
(|>> ((~! list#each) (~ =sub=)) ((~! sequence.of_list)) {/.#Array})))))
(do !
- [.let [g!_ (code.local_symbol "_______")
- g!input (code.local_symbol "_______input")]
+ [.let [g!_ (code.local "_______")
+ g!input (code.local "_______input")]
members (<type>.variant (<>.many encoded))
.let [last (-- (list.size members))]]
(in (` (is (~ (@JSON#encoded inputT))
@@ -184,10 +184,10 @@
(list.enumeration members))))))))))
(do !
[g!encoders (<type>.tuple (<>.many encoded))
- .let [g!_ (code.local_symbol "_______")
+ .let [g!_ (code.local "_______")
g!members (|> (list.size g!encoders)
list.indices
- (list#each (|>> n#encoded code.local_symbol)))]]
+ (list#each (|>> n#encoded code.local)))]]
(in (` (is (~ (@JSON#encoded inputT))
(function ((~ g!_) [(~+ g!members)])
((~! /.json) [(~+ (list#each (function (_ [g!member g!encoded])
@@ -196,7 +196,7 @@
... Type recursion
(do !
[[selfC non_recC] (<type>.recursive encoded)
- .let [g! (code.local_symbol "____________")]]
+ .let [g! (code.local "____________")]]
(in (` (is (~ (@JSON#encoded inputT))
((~! ..rec_encoded) (.function ((~ g!) (~ selfC))
(~ non_recC)))))))
@@ -248,7 +248,7 @@
[month.Month month.codec])]
(do [! <>.monad]
[*env* <type>.env
- .let [g!_ (code.local_symbol "_______")
+ .let [g!_ (code.local "_______")
@JSON#decoded (is (-> Type Code)
(function (_ type)
(` (</>.Parser (~ (poly.code *env* type))))))]
@@ -286,12 +286,12 @@
(~+ (list#each (function (_ [tag memberC])
(if (n.= last tag)
(` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag (-- tag))))))
+ ((~! <>.after) ((~! </>.this_boolean) (~ (code.bit #1))))
+ ((~! <>.after) ((~! </>.this_number) (~ (code.frac (..tag (-- tag))))))
((~! </>.array))))
(` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #0))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag tag)))))
+ ((~! <>.after) ((~! </>.this_boolean) (~ (code.bit #0))))
+ ((~! <>.after) ((~! </>.this_number) (~ (code.frac (..tag tag)))))
((~! </>.array))))))
(list.enumeration members))))))))
(do !
@@ -301,7 +301,7 @@
... Type recursion
(do !
[[selfC bodyC] (<type>.recursive decoded)
- .let [g! (code.local_symbol "____________")]]
+ .let [g! (code.local "____________")]]
(in (` (is (~ (@JSON#decoded inputT))
((~! <>.rec) (.function ((~ g!) (~ selfC))
(~ bodyC)))))))