aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly
diff options
context:
space:
mode:
authorEduardo Julian2021-09-14 02:56:22 -0400
committerEduardo Julian2021-09-14 02:56:22 -0400
commit971767f1eafb22208912353d8709f11081f2d3c8 (patch)
tree9b043f1238af49a33c1a625d737c9f0e1abb6e99 /stdlib/source/poly
parent1c93f003f73116202b1f964b0d1b6d3f07b69fb0 (diff)
Re-named "Identifier" to "Symbol".
Diffstat (limited to 'stdlib/source/poly')
-rw-r--r--stdlib/source/poly/lux/abstract/equivalence.lux16
-rw-r--r--stdlib/source/poly/lux/abstract/functor.lux18
-rw-r--r--stdlib/source/poly/lux/data/format/json.lux26
3 files changed, 30 insertions, 30 deletions
diff --git a/stdlib/source/poly/lux/abstract/equivalence.lux b/stdlib/source/poly/lux/abstract/equivalence.lux
index 71441f13b..7db8d5c13 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_identifier "_____________")]
+ [.let [g!_ (code.local_symbol "_____________")]
*env* <type>.env
inputT <type>.next
.let [@Equivalence (: (-> Type Code)
@@ -109,9 +109,9 @@
(do !
[members (<type>.variant (<>.many equivalence))
.let [last (-- (list.size members))
- g!_ (code.local_identifier "_____________")
- g!left (code.local_identifier "_____________left")
- g!right (code.local_identifier "_____________right")]]
+ g!_ (code.local_symbol "_____________")
+ g!left (code.local_symbol "_____________left")
+ g!right (code.local_symbol "_____________right")]]
(in (` (: (~ (@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_identifier "_____________")
+ .let [g!_ (code.local_symbol "_____________")
indices (list.indices (list.size g!eqs))
- g!lefts (list#each (|>> nat#encoded (text#composite "left") code.local_identifier) indices)
- g!rights (list#each (|>> nat#encoded (text#composite "right") code.local_identifier) indices)]]
+ 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)]]
(in (` (: (~ (@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_identifier "_____________")]]
+ .let [g!_ (code.local_symbol "_____________")]]
(in (` (: (~ (@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 895d509be..b4c5e44a3 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_identifier "____________")
- type_funcC (code.local_identifier "____________type_funcC")
- funcC (code.local_identifier "____________funcC")
- inputC (code.local_identifier "____________inputC")]
+ [.let [g!_ (code.local_symbol "____________")
+ type_funcC (code.local_symbol "____________type_funcC")
+ funcC (code.local_symbol "____________funcC")
+ inputC (code.local_symbol "____________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_identifier)))]
+ (let [paramsC (|> num_vars -- list.indices (list#each (|>> %.nat code.local_symbol)))]
(` (All ((~ g!_) (~+ paramsC))
((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
Arg<?> (: (-> Code (<type>.Parser Code))
@@ -69,7 +69,7 @@
(<type>.tuple (loop [idx 0
pairsCC (: (List [Code Code])
(list))]
- (p.either (let [slotC (|> idx %.nat (format "____________slot") code.local_identifier)]
+ (p.either (let [slotC (|> idx %.nat (format "____________slot") code.local_symbol)]
(do !
[_ (in [])
memberC (Arg<?> slotC)]
@@ -82,13 +82,13 @@
... Functions
(do !
[_ (in [])
- .let [g! (code.local_identifier "____________")
- outL (code.local_identifier "____________outL")]
+ .let [g! (code.local_symbol "____________")
+ outL (code.local_symbol "____________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_identifier)))]]
+ (list#each (|>> %.nat (format "____________inC") code.local_symbol)))]]
(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 df9c9cc5b..964d7918b 100644
--- a/stdlib/source/poly/lux/data/format/json.lux
+++ b/stdlib/source/poly/lux/data/format/json.lux
@@ -100,12 +100,12 @@
(with_expansions
[<basic> (template [<matcher> <encoder>]
[(do !
- [.let [g!_ (code.local_identifier "_______")]
+ [.let [g!_ (code.local_symbol "_______")]
_ <matcher>]
(in (` (: (~ (@JSON#encoded inputT))
<encoder>))))]
- [(<type>.exactly Any) (function ((~ g!_) (~ (code.identifier ["" "0"]))) {/.#Null})]
+ [(<type>.exactly Any) (function ((~ g!_) (~ (code.symbol ["" "0"]))) {/.#Null})]
[(<type>.sub Bit) (|>> {/.#Boolean})]
[(<type>.sub Nat) (# (~! ..nat_codec) (~' encoded))]
[(<type>.sub Int) (# (~! ..int_codec) (~' encoded))]
@@ -124,7 +124,7 @@
[month.Month month.codec])]
(do [! <>.monad]
[*env* <type>.env
- .let [g!_ (code.local_identifier "_______")
+ .let [g!_ (code.local_symbol "_______")
@JSON#encoded (: (-> Type Code)
(function (_ type)
(` (-> (~ (poly.code *env* type)) /.JSON))))]
@@ -138,9 +138,9 @@
(in (` (: (~ (@JSON#encoded inputT))
(# (~! qty_codec) (~' encoded))))))
(do !
- [.let [g!_ (code.local_identifier "_______")
- g!key (code.local_identifier "_______key")
- g!val (code.local_identifier "_______val")]
+ [.let [g!_ (code.local_symbol "_______")
+ g!key (code.local_symbol "_______key")
+ g!val (code.local_symbol "_______val")]
[_ _ =val=] (<type>.applied ($_ <>.and
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
@@ -164,8 +164,8 @@
(in (` (: (~ (@JSON#encoded inputT))
(|>> ((~! list#each) (~ =sub=)) ((~! row.of_list)) {/.#Array})))))
(do !
- [.let [g!_ (code.local_identifier "_______")
- g!input (code.local_identifier "_______input")]
+ [.let [g!_ (code.local_symbol "_______")
+ g!input (code.local_symbol "_______input")]
members (<type>.variant (<>.many encoded))
.let [last (-- (list.size members))]]
(in (` (: (~ (@JSON#encoded inputT))
@@ -184,10 +184,10 @@
(list.enumeration members))))))))))
(do !
[g!encoders (<type>.tuple (<>.many encoded))
- .let [g!_ (code.local_identifier "_______")
+ .let [g!_ (code.local_symbol "_______")
g!members (|> (list.size g!encoders)
list.indices
- (list#each (|>> n#encoded code.local_identifier)))]]
+ (list#each (|>> n#encoded code.local_symbol)))]]
(in (` (: (~ (@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_identifier "____________")]]
+ .let [g! (code.local_symbol "____________")]]
(in (` (: (~ (@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_identifier "_______")
+ .let [g!_ (code.local_symbol "_______")
@JSON#decoded (: (-> Type Code)
(function (_ type)
(` (</>.Parser (~ (poly.code *env* type))))))]
@@ -301,7 +301,7 @@
... Type recursion
(do !
[[selfC bodyC] (<type>.recursive decoded)
- .let [g! (code.local_identifier "____________")]]
+ .let [g! (code.local_symbol "____________")]]
(in (` (: (~ (@JSON#decoded inputT))
((~! <>.rec) (.function ((~ g!) (~ selfC))
(~ bodyC)))))))