aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly
diff options
context:
space:
mode:
authorEduardo Julian2021-09-12 15:39:55 -0400
committerEduardo Julian2021-09-12 15:39:55 -0400
commit2dbbaaec93a53f8dd0b96a0028b9cf125c9066cd (patch)
tree14bc8b5abe09b46ef005c3ff7cf132f1d98ddf0d /stdlib/source/poly
parentdda05bca0956af5e5b3875c4cc36e61aa04772e4 (diff)
Re-named \ => # && \\ => ##
Diffstat (limited to 'stdlib/source/poly')
-rw-r--r--stdlib/source/poly/lux/abstract/equivalence.lux20
-rw-r--r--stdlib/source/poly/lux/abstract/functor.lux14
-rw-r--r--stdlib/source/poly/lux/data/format/json.lux78
3 files changed, 56 insertions, 56 deletions
diff --git a/stdlib/source/poly/lux/abstract/equivalence.lux b/stdlib/source/poly/lux/abstract/equivalence.lux
index 37bb54d79..1159d4ff4 100644
--- a/stdlib/source/poly/lux/abstract/equivalence.lux
+++ b/stdlib/source/poly/lux/abstract/equivalence.lux
@@ -10,10 +10,10 @@
[data
["[0]" product]
["[0]" bit]
- ["[0]" text ("[1]\[0]" monoid)
+ ["[0]" text ("[1]#[0]" monoid)
["%" format {"+" [format]}]]
[collection
- ["[0]" list ("[1]\[0]" monad)]
+ ["[0]" list ("[1]#[0]" monad)]
["[0]" row]
["[0]" array]
["[0]" queue]
@@ -25,7 +25,7 @@
["[0]" code]]
[math
[number
- ["[0]" nat ("[1]\[0]" decimal)]
+ ["[0]" nat ("[1]#[0]" decimal)]
["[0]" int]
["[0]" rev]
["[0]" frac]]]
@@ -115,7 +115,7 @@
(in (` (: (~ (@Equivalence inputT))
(function ((~ g!_) (~ g!left) (~ g!right))
(case [(~ g!left) (~ g!right)]
- (~+ (list\conjoint (list\each (function (_ [tag g!eq])
+ (~+ (list#conjoint (list#each (function (_ [tag g!eq])
(if (nat.= last tag)
(list (` [{(~ (code.nat (-- tag))) #1 (~ g!left)}
{(~ (code.nat (-- tag))) #1 (~ g!right)}])
@@ -131,12 +131,12 @@
[g!eqs (<type>.tuple (<>.many equivalence))
.let [g!_ (code.local_identifier "_____________")
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_identifier) indices)
+ g!rights (list#each (|>> nat#encoded (text#composite "right") code.local_identifier) indices)]]
(in (` (: (~ (@Equivalence inputT))
(function ((~ g!_) [(~+ g!lefts)] [(~+ g!rights)])
(and (~+ (|> (list.zipped/3 g!eqs g!lefts g!rights)
- (list\each (function (_ [g!eq g!left g!right])
+ (list#each (function (_ [g!eq g!left g!right])
(` ((~ g!eq) (~ g!left) (~ g!right)))))))))))))
... Type recursion
(do !
@@ -156,13 +156,13 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic equivalence)]
(in (` (: (All ((~ g!_) (~+ varsC))
- (-> (~+ (list\each (|>> (~) ((~! /.Equivalence)) (`)) varsC))
+ (-> (~+ (list#each (|>> (~) ((~! /.Equivalence)) (`)) varsC))
((~! /.Equivalence) ((~ (poly.code *env* inputT)) (~+ varsC)))))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))
<type>.recursive_call
... If all else fails...
(|> <type>.any
- (\ ! each (|>> %.type (format "Cannot create Equivalence for: ") <>.failure))
- (\ ! conjoint))
+ (# ! each (|>> %.type (format "Cannot create Equivalence for: ") <>.failure))
+ (# ! conjoint))
))))
diff --git a/stdlib/source/poly/lux/abstract/functor.lux b/stdlib/source/poly/lux/abstract/functor.lux
index d4637711f..2c9ba91f1 100644
--- a/stdlib/source/poly/lux/abstract/functor.lux
+++ b/stdlib/source/poly/lux/abstract/functor.lux
@@ -12,7 +12,7 @@
["[0]" text
["%" format {"+" [format]}]]
[collection
- ["[0]" list ("[1]\[0]" monad monoid)]]]
+ ["[0]" list ("[1]#[0]" monad monoid)]]]
[macro
[syntax {"+" [syntax:]}]
["[0]" code]]
@@ -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_identifier)))]
(` (All ((~ g!_) (~+ paramsC))
((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
Arg<?> (: (-> Code (<type>.Parser Code))
@@ -56,7 +56,7 @@
membersC (<type>.variant (p.many (Arg<?> valueC)))
.let [last (-- (list.size membersC))]]
(in (` (case (~ valueC)
- (~+ (list\conjoint (list\each (function (_ [tag memberC])
+ (~+ (list#conjoint (list#each (function (_ [tag memberC])
(if (n.= last tag)
(list (` {(~ (code.nat (-- tag))) #1 (~ valueC)})
(` {(~ (code.nat (-- tag))) #1 (~ memberC)}))
@@ -74,11 +74,11 @@
[_ (in [])
memberC (Arg<?> slotC)]
(recur (++ idx)
- (list\composite pairsCC (list [slotC memberC])))))
+ (list#composite pairsCC (list [slotC memberC])))))
(in pairsCC)))))]
(in (` (case (~ valueC)
- [(~+ (list\each product.left pairsCC))]
- [(~+ (list\each product.right pairsCC))]))))
+ [(~+ (list#each product.left pairsCC))]
+ [(~+ (list#each product.right pairsCC))]))))
... Functions
(do !
[_ (in [])
@@ -88,7 +88,7 @@
(Arg<?> outL))
.let [inC+ (|> (list.size inT+)
list.indices
- (list\each (|>> %.nat (format "____________inC") code.local_identifier)))]]
+ (list#each (|>> %.nat (format "____________inC") code.local_identifier)))]]
(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 53bdcd06c..f6ab79e6a 100644
--- a/stdlib/source/poly/lux/data/format/json.lux
+++ b/stdlib/source/poly/lux/data/format/json.lux
@@ -15,7 +15,7 @@
["[0]" text
["%" format {"+" [format]}]]
[collection
- ["[0]" list ("[1]\[0]" monad)]
+ ["[0]" list ("[1]#[0]" monad)]
["[0]" row {"+" [row]}]
["[0]" dictionary]]]
[macro
@@ -23,7 +23,7 @@
["[0]" code]]
[math
[number
- ["n" nat ("[1]\[0]" decimal)]
+ ["n" nat ("[1]#[0]" decimal)]
["[0]" i64]
["[0]" int]
["[0]" frac]]]
@@ -73,9 +73,9 @@
(codec.Codec JSON Int)
(def: encoded
- (|>> .nat (\ nat_codec encoded)))
+ (|>> .nat (# nat_codec encoded)))
(def: decoded
- (|>> (\ nat_codec decoded) (\ try.functor each .int))))
+ (|>> (# nat_codec decoded) (# try.functor each .int))))
... Builds a JSON generator for potentially inexistent values.
(def: (nullable writer)
@@ -91,10 +91,10 @@
(def: encoded
(|>> ((debug.private unit.out'))
- (\ ..int_codec encoded)))
+ (# ..int_codec encoded)))
(def: decoded
- (|>> (\ ..int_codec decoded)
- (\ try.functor each (debug.private unit.in')))))
+ (|>> (# ..int_codec decoded)
+ (# try.functor each (debug.private unit.in')))))
(poly: encoded
(with_expansions
@@ -102,20 +102,20 @@
[(do !
[.let [g!_ (code.local_identifier "_______")]
_ <matcher>]
- (in (` (: (~ (@JSON\encoded inputT))
+ (in (` (: (~ (@JSON#encoded inputT))
<encoder>))))]
[(<type>.exactly Any) (function ((~ g!_) (~ (code.identifier ["" "0"]))) {/.#Null})]
[(<type>.sub Bit) (|>> {/.#Boolean})]
- [(<type>.sub Nat) (\ (~! ..nat_codec) (~' encoded))]
- [(<type>.sub Int) (\ (~! ..int_codec) (~' encoded))]
+ [(<type>.sub Nat) (# (~! ..nat_codec) (~' encoded))]
+ [(<type>.sub Int) (# (~! ..int_codec) (~' encoded))]
[(<type>.sub Frac) (|>> {/.#Number})]
[(<type>.sub Text) (|>> {/.#String})])
<time> (template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (: (~ (@JSON\encoded inputT))
- (|>> (\ (~! <codec>) (~' encoded)) {/.#String})))))]
+ (in (` (: (~ (@JSON#encoded inputT))
+ (|>> (# (~! <codec>) (~' encoded)) {/.#String})))))]
... [duration.Duration duration.codec]
... [instant.Instant instant.codec]
@@ -125,7 +125,7 @@
(do [! <>.monad]
[*env* <type>.env
.let [g!_ (code.local_identifier "_______")
- @JSON\encoded (: (-> Type Code)
+ @JSON#encoded (: (-> Type Code)
(function (_ type)
(` (-> (~ (poly.code *env* type)) /.JSON))))]
inputT <type>.next]
@@ -135,8 +135,8 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Qty)
<type>.any))]
- (in (` (: (~ (@JSON\encoded inputT))
- (\ (~! qty_codec) (~' encoded))))))
+ (in (` (: (~ (@JSON#encoded inputT))
+ (# (~! qty_codec) (~' encoded))))))
(do !
[.let [g!_ (code.local_identifier "_______")
g!key (code.local_identifier "_______key")
@@ -145,9 +145,9 @@
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
encoded))]
- (in (` (: (~ (@JSON\encoded inputT))
+ (in (` (: (~ (@JSON#encoded inputT))
(|>> ((~! dictionary.entries))
- ((~! list\each) (function ((~ g!_) [(~ g!key) (~ g!val)])
+ ((~! list#each) (function ((~ g!_) [(~ g!key) (~ g!val)])
[(~ g!key) ((~ =val=) (~ g!val))]))
((~! dictionary.of_list) (~! text.hash))
{/.#Object})))))
@@ -155,23 +155,23 @@
[[_ =sub=] (<type>.applied ($_ <>.and
(<type>.exactly .Maybe)
encoded))]
- (in (` (: (~ (@JSON\encoded inputT))
+ (in (` (: (~ (@JSON#encoded inputT))
((~! ..nullable) (~ =sub=))))))
(do !
[[_ =sub=] (<type>.applied ($_ <>.and
(<type>.exactly .List)
encoded))]
- (in (` (: (~ (@JSON\encoded inputT))
- (|>> ((~! list\each) (~ =sub=)) ((~! row.of_list)) {/.#Array})))))
+ (in (` (: (~ (@JSON#encoded inputT))
+ (|>> ((~! list#each) (~ =sub=)) ((~! row.of_list)) {/.#Array})))))
(do !
[.let [g!_ (code.local_identifier "_______")
g!input (code.local_identifier "_______input")]
members (<type>.variant (<>.many encoded))
.let [last (-- (list.size members))]]
- (in (` (: (~ (@JSON\encoded inputT))
+ (in (` (: (~ (@JSON#encoded inputT))
(function ((~ g!_) (~ g!input))
(case (~ g!input)
- (~+ (list\conjoint (list\each (function (_ [tag g!encoded])
+ (~+ (list#conjoint (list#each (function (_ [tag g!encoded])
(if (n.= last tag)
(.list (` {(~ (code.nat (-- tag))) #1 (~ g!input)})
(` ((~! /.json) [(~ (code.frac (..tag (-- tag))))
@@ -187,17 +187,17 @@
.let [g!_ (code.local_identifier "_______")
g!members (|> (list.size g!encoders)
list.indices
- (list\each (|>> n\encoded code.local_identifier)))]]
- (in (` (: (~ (@JSON\encoded inputT))
+ (list#each (|>> n#encoded code.local_identifier)))]]
+ (in (` (: (~ (@JSON#encoded inputT))
(function ((~ g!_) [(~+ g!members)])
- ((~! /.json) [(~+ (list\each (function (_ [g!member g!encoded])
+ ((~! /.json) [(~+ (list#each (function (_ [g!member g!encoded])
(` ((~ g!encoded) (~ g!member))))
(list.zipped/2 g!members g!encoders)))]))))))
... Type recursion
(do !
[[selfC non_recC] (<type>.recursive encoded)
.let [g! (code.local_identifier "____________")]]
- (in (` (: (~ (@JSON\encoded inputT))
+ (in (` (: (~ (@JSON#encoded inputT))
((~! ..rec_encoded) (.function ((~ g!) (~ selfC))
(~ non_recC)))))))
<type>.recursive_self
@@ -209,7 +209,7 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic encoded)]
(in (` (: (All ((~ g!_) (~+ varsC))
- (-> (~+ (list\each (function (_ varC) (` (-> (~ varC) /.JSON)))
+ (-> (~+ (list#each (function (_ varC) (` (-> (~ varC) /.JSON)))
varsC))
(-> ((~ (poly.code *env* inputT)) (~+ varsC))
/.JSON)))
@@ -226,7 +226,7 @@
[<basic> (template [<matcher> <decoder>]
[(do !
[_ <matcher>]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
(~! <decoder>)))))]
[(<type>.exactly Any) </>.null]
@@ -238,7 +238,7 @@
<time> (template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! <>.codec) (~! <codec>) (~! </>.string))))))]
... [duration.Duration duration.codec]
@@ -249,7 +249,7 @@
(do [! <>.monad]
[*env* <type>.env
.let [g!_ (code.local_identifier "_______")
- @JSON\decoded (: (-> Type Code)
+ @JSON#decoded (: (-> Type Code)
(function (_ type)
(` (</>.Parser (~ (poly.code *env* type))))))]
inputT <type>.next]
@@ -259,31 +259,31 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Qty)
<type>.any))]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! <>.codec) (~! qty_codec) (~! </>.any))))))
(do !
[[_ _ valC] (<type>.applied ($_ <>.and
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
decoded))]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! </>.dictionary) (~ valC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .Maybe)
decoded))]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! </>.nullable) (~ subC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .List)
decoded))]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! </>.array) ((~! <>.some) (~ subC)))))))
(do !
[members (<type>.variant (<>.many decoded))
.let [last (-- (list.size members))]]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
($_ ((~! <>.or))
- (~+ (list\each (function (_ [tag memberC])
+ (~+ (list#each (function (_ [tag memberC])
(if (n.= last tag)
(` (|> (~ memberC)
((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
@@ -296,13 +296,13 @@
(list.enumeration members))))))))
(do !
[g!decoders (<type>.tuple (<>.many decoded))]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! </>.array) ($_ ((~! <>.and)) (~+ g!decoders)))))))
... Type recursion
(do !
[[selfC bodyC] (<type>.recursive decoded)
.let [g! (code.local_identifier "____________")]]
- (in (` (: (~ (@JSON\decoded inputT))
+ (in (` (: (~ (@JSON#decoded inputT))
((~! <>.rec) (.function ((~ g!) (~ selfC))
(~ bodyC)))))))
<type>.recursive_self
@@ -314,7 +314,7 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic decoded)]
(in (` (: (All ((~ g!_) (~+ varsC))
- (-> (~+ (list\each (|>> (~) </>.Parser (`)) varsC))
+ (-> (~+ (list#each (|>> (~) </>.Parser (`)) varsC))
(</>.Parser ((~ (poly.code *env* inputT)) (~+ varsC)))))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))