aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux.lux
diff options
context:
space:
mode:
authorEduardo Julian2022-07-02 05:38:27 -0400
committerEduardo Julian2022-07-02 05:38:27 -0400
commitb96beb587c11fcfbce86ce2d62351600cf6cad1b (patch)
treec9a558ab1391ac97cb11e8777ea78299f1ab5555 /stdlib/source/library/lux.lux
parent104130efba46a875eba566384578f8aa8593ad37 (diff)
More traditional names for unquoting macros.
Diffstat (limited to 'stdlib/source/library/lux.lux')
-rw-r--r--stdlib/source/library/lux.lux328
1 files changed, 164 insertions, 164 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index d142387b3..2e875d426 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -2041,7 +2041,7 @@
(def' .public literal_quote Macro ')
-(def' .public ~
+(def' .public ,
UnQuote
(..unquote
(macro (_ tokens)
@@ -2051,12 +2051,12 @@
it))))
_
- (failure (wrong_syntax_error [..prelude "~"]))}
+ (failure (wrong_syntax_error [..prelude ","]))}
tokens))))
-(def' .public but UnQuote ~)
+(def' .public but UnQuote ,)
-(def' .public ~!
+(def' .public ,!
UnQuote
(..unquote
(macro (_ tokens)
@@ -2070,12 +2070,12 @@
independent))))))))
_
- (failure (wrong_syntax_error [..prelude "~!"]))}
+ (failure (wrong_syntax_error [..prelude ",!"]))}
tokens))))
-(def' .public specifically UnQuote ~!)
+(def' .public specifically UnQuote ,!)
-(def' .public ~'
+(def' .public ,'
UnQuote
(..unquote
(macro (_ tokens)
@@ -2086,12 +2086,12 @@
(in (list it)))
_
- (failure (wrong_syntax_error [..prelude "~'"]))}
+ (failure (wrong_syntax_error [..prelude ",'"]))}
tokens))))
-(def' .public literally UnQuote ~')
+(def' .public literally UnQuote ,')
-(def' .public ~+
+(def' .public ,*
Spliced_UnQuote
(let' [g!list#composite (form$ (list (text$ "lux in-module")
(text$ ..prelude)
@@ -2102,10 +2102,10 @@
(meta#in (list (form$ (list g!list#composite (|List<Code>| it) tail))))
_
- (failure (wrong_syntax_error [..prelude "~+"]))}
+ (failure (wrong_syntax_error [..prelude ",*"]))}
tokens)))))
-(def' .public also Spliced_UnQuote ~+)
+(def' .public also Spliced_UnQuote ,*)
(def' .public |>
Macro
@@ -2123,7 +2123,7 @@
(form$ (list#composite parts (list acc)))
_
- (` ((~ app) (~ acc)))}
+ (` ((, app) (, acc)))}
app)))
init
apps)))
@@ -2148,7 +2148,7 @@
(form$ (list#composite parts (list acc)))
_
- (` ((~ app) (~ acc)))}
+ (` ((, app) (, acc)))}
app)))
init
apps)))
@@ -2613,12 +2613,12 @@
({[_ {#Variant {#Item [_ {#Symbol symbol}] parts}}]
(do meta#monad
[parts (monad#each meta#monad normal_type parts)]
- (in (` {(~ (symbol$ symbol)) (~+ parts)})))
+ (in (` {(, (symbol$ symbol)) (,* parts)})))
[_ {#Tuple members}]
(do meta#monad
[members (monad#each meta#monad normal_type members)]
- (in (` (Tuple (~+ members)))))
+ (in (` (Tuple (,* members)))))
[_ {#Form {#Item [_ {#Text "lux in-module"}]
{#Item [_ {#Text module}]
@@ -2626,9 +2626,9 @@
{#End}}}}}]
(do meta#monad
[type' (normal_type type')]
- (in (` ("lux in-module" (~ (text$ module)) (~ type')))))
+ (in (` ("lux in-module" (, (text$ module)) (, type')))))
- [_ {#Form {#Item [_ {#Symbol ["" "~"]}] {#Item expression {#End}}}}]
+ [_ {#Form {#Item [_ {#Symbol ["" ","]}] {#Item expression {#End}}}}]
(meta#in expression)
[_0 {#Form {#Item [_1 {#Variant {#Item binding {#Item body {#End}}}}]
@@ -2658,7 +2658,7 @@
[type_fn (normal_type type_fn)
args (monad#each meta#monad normal_type args)]
(in (list#mix ("lux type check" (-> Code Code Code)
- (function' [arg type_fn] (` {.#Apply (~ arg) (~ type_fn)})))
+ (function' [arg type_fn] (` {.#Apply (, arg) (, type_fn)})))
type_fn
args)))
@@ -2764,8 +2764,8 @@
(macro (_ tokens)
({{#Item type {#Item value {#End}}}
(meta#in (list (` ("lux type check"
- (..type_literal (~ type))
- (~ value)))))
+ (..type_literal (, type))
+ (, value)))))
_
(failure (wrong_syntax_error [..prelude "is"]))}
@@ -2776,8 +2776,8 @@
(macro (_ tokens)
({{#Item type {#Item value {#End}}}
(meta#in (list (` ("lux type as"
- (..type_literal (~ type))
- (~ value)))))
+ (..type_literal (, type))
+ (, value)))))
_
(failure (wrong_syntax_error [..prelude "as"]))}
@@ -2821,8 +2821,8 @@
({{#Item value actions}
(let' [dummy (local$ "")]
(meta#in (list (list#mix ("lux type check" (-> Code Code Code)
- (function' [pre post] (` ({(~ dummy) (~ post)}
- (~ pre)))))
+ (function' [pre post] (` ({(, dummy) (, post)}
+ (, pre)))))
value
actions))))
@@ -2869,7 +2869,7 @@
({{#Item value branches}
(do meta#monad
[expansion (case_expansion branches)]
- (in (list (` ((~ (variant$ expansion)) (~ value))))))
+ (in (list (` ((, (variant$ expansion)) (, value))))))
_
(failure "Wrong syntax for case")}
@@ -2914,7 +2914,7 @@
(macro (_ tokens)
(case tokens
(pattern (list [_ {#Symbol [module name]}]))
- (meta#in (list (` [(~ (text$ module)) (~ (text$ name))])))
+ (meta#in (list (` [(, (text$ module)) (, (text$ name))])))
_
(failure (..wrong_syntax_error [..prelude "symbol"])))))
@@ -2941,8 +2941,8 @@
(function' [lr body']
(let' [[l r] lr]
(if (symbol? l)
- (` ({(~ l) (~ body')} (~ r)))
- (` (case (~ r) (~ l) (~ body')))))))
+ (` ({(, l) (, body')} (, r)))
+ (` (case (, r) (, l) (, body')))))))
body)
list
meta#in)
@@ -2969,9 +2969,9 @@
(function' [g!name]
(function' [arg body']
(if (symbol? arg)
- (` ([(~ g!name) (~ arg)] (~ body')))
- (` ([(~ g!name) (~ g!blank)]
- (.case (~ g!blank) (~ arg) (~ body'))))))))]
+ (` ([(, g!name) (, arg)] (, body')))
+ (` ([(, g!name) (, g!blank)]
+ (.case (, g!blank) (, arg) (, body'))))))))]
(meta#in (list (nest (..local$ g!name) head
(list#mix (nest g!blank) body (list#reversed tail))))))
@@ -3270,18 +3270,18 @@
body
_
- (` (function ((~ (..local$ name)) (~+ parameters))
- (~ body))))
+ (` (function ((, (..local$ name)) (,* parameters))
+ (, body))))
body (case ?type
{#Some type}
- (` (is (~ type)
- (~ body)))
+ (` (is (, type)
+ (, body)))
{#None}
body)]
- (meta#in (list (` ("lux def" (~ (..local$ name))
- (~ body)
- (~ export_policy))))))
+ (meta#in (list (` ("lux def" (, (..local$ name))
+ (, body)
+ (, export_policy))))))
{#None}
(failure (..wrong_syntax_error (symbol ..def))))))
@@ -3299,8 +3299,8 @@
_
(failure <message>))))]
- [and (if (~ pre) (~ post) #0) "'and' requires >=1 clauses."]
- [or (if (~ pre) #1 (~ post)) "'or' requires >=1 clauses."])
+ [and (if (, pre) (, post) #0) "'and' requires >=1 clauses."]
+ [or (if (, pre) #1 (, post)) "'or' requires >=1 clauses."])
(def (index part text)
(-> Text Text (Maybe Nat))
@@ -3315,12 +3315,12 @@
(case tokens
(pattern (list else maybe))
(let [g!temp (is Code [dummy_location {#Symbol ["" ""]}])
- code (` (case (~ maybe)
- {.#Some (~ g!temp)}
- (~ g!temp)
+ code (` (case (, maybe)
+ {.#Some (, g!temp)}
+ (, g!temp)
{.#None}
- (~ else)))]
+ (, else)))]
{#Right [state (list code)]})
_
@@ -3684,7 +3684,7 @@
{#Some [tokens' [niladic (` .Any)]]}
(pattern (partial_list [_ {#Variant (partial_list [_ {#Symbol ["" polyadic]}] caseT)}] tokens'))
- {#Some [tokens' [polyadic (` (..Tuple (~+ caseT)))]]}
+ {#Some [tokens' [polyadic (` (..Tuple (,* caseT)))]]}
_
{#None}))
@@ -3693,7 +3693,7 @@
(macro (_ tokens)
(case (everyP caseP tokens)
{#Some cases}
- (meta#in (list (` (..Union (~+ (list#each product#right cases))))
+ (meta#in (list (` (..Union (,* (list#each product#right cases))))
(variant$ (list#each (function (_ case)
(text$ (product#left case)))
cases))))
@@ -3716,7 +3716,7 @@
(pattern (list [_ {#Tuple record}]))
(case (everyP slotP record)
{#Some slots}
- (meta#in (list (` (..Tuple (~+ (list#each product#right slots))))
+ (meta#in (list (` (..Tuple (,* (list#each product#right slots))))
(tuple$ (list#each (function (_ slot)
(text$ (product#left slot)))
slots))))
@@ -3793,30 +3793,30 @@
{#Some type}
_
- {#Some (` (.All ((~ type_name) (~+ (list#each local$ args)))
- (~ type)))}))]]
+ {#Some (` (.All ((, type_name) (,* (list#each local$ args)))
+ (, type)))}))]]
(case type'
{#Some type''}
- (let [typeC (` {.#Named [(~ (text$ module_name))
- (~ (text$ name))]
- (..type_literal (~ type''))})]
+ (let [typeC (` {.#Named [(, (text$ module_name))
+ (, (text$ name))]
+ (..type_literal (, type''))})]
(meta#in (list (case labels??
{#Some labels}
- (` ("lux def type tagged" (~ type_name)
- (~ typeC)
- (~ (case labels
+ (` ("lux def type tagged" (, type_name)
+ (, typeC)
+ (, (case labels
{#Left tags}
- (` {(~+ (list#each text$ tags))})
+ (` {(,* (list#each text$ tags))})
{#Right slots}
- (` [(~+ (list#each text$ slots))])))
- (~ export_policy)))
+ (` [(,* (list#each text$ slots))])))
+ (, export_policy)))
_
- (` ("lux def" (~ type_name)
+ (` ("lux def" (, type_name)
("lux type check type"
- (~ typeC))
- (~ export_policy)))))))
+ (, typeC))
+ (, export_policy)))))))
{#None}
(failure (..wrong_syntax_error (symbol ..type)))))
@@ -4116,7 +4116,7 @@
(def (alias_definition imported_module def)
(-> Text Text Code)
- (` ("lux def alias" (~ (local$ def)) (~ (symbol$ [imported_module def])))))
+ (` ("lux def alias" (, (local$ def)) (, (symbol$ [imported_module def])))))
(def .public only
(macro (_ tokens)
@@ -4140,14 +4140,14 @@
(do meta#monad
[g!_ (..generated_symbol "_")
g!arg (..generated_symbol "arg")]
- (meta#in (list (` (function ((~ g!_) (~ g!arg)) (|> (~ g!arg) (~+ tokens)))))))))
+ (meta#in (list (` (function ((, g!_) (, g!arg)) (|> (, g!arg) (,* tokens)))))))))
(def .public <<|
(macro (_ tokens)
(do meta#monad
[g!_ (..generated_symbol "_")
g!arg (..generated_symbol "arg")]
- (meta#in (list (` (function ((~ g!_) (~ g!arg)) (<| (~+ tokens) (~ g!arg)))))))))
+ (meta#in (list (` (function ((, g!_) (, g!arg)) (<| (,* tokens) (, g!arg)))))))))
(def .public except
(macro (_ tokens)
@@ -4265,7 +4265,7 @@
(pattern (partial_list [_ {#Form (list [_ {#Text alias}])}] body branches))
(do meta#monad
[g!temp (..generated_symbol "temp")]
- (in (partial_list g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches)))
+ (in (partial_list g!temp (` (..open (, g!temp) (, (text$ alias)) (, body))) branches)))
(pattern (list [_ {#Symbol name}] [_ {#Text alias}] body))
(do meta#monad
@@ -4309,7 +4309,7 @@
(in enhanced_target))))
target
(zipped_2 locals members))]
- (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source)))))))))
+ (in (` ({(, pattern) (, enhanced_target)} (, (symbol$ source)))))))))
name tags&members body)]
(in (list full_body)))))
@@ -4325,7 +4325,7 @@
(meta#in (list (list#mix (is (-> [Code Code] Code Code)
(function (_ branch else)
(let [[then ?] branch]
- (` (if (~ ?) (~ then) (~ else))))))
+ (` (if (, ?) (, then) (, else))))))
else
branches')))
@@ -4371,7 +4371,7 @@
g!_)))))
list#conjoint
tuple$)]
- (meta#in (list (` ({(~ pattern) (~ g!output)} (~ record))))))
+ (meta#in (list (` ({(, pattern) (, g!output)} (, record))))))
_
(failure "the can only use records.")))
@@ -4379,7 +4379,7 @@
(pattern (list [_ {#Tuple slots}] record))
(meta#in (list (list#mix (is (-> Code Code Code)
(function (_ slot inner)
- (` (..the (~ slot) (~ inner)))))
+ (` (..the (, slot) (, inner)))))
record
slots)))
@@ -4387,7 +4387,7 @@
(do meta#monad
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!record)) (..the (~ selector) (~ g!record)))))))
+ (in (list (` (function ((, g!_) (, g!record)) (..the (, selector) (, g!record)))))))
_
(failure (..wrong_syntax_error (symbol ..the))))))
@@ -4405,7 +4405,7 @@
g!output
g!_)))
tuple$)
- source+ (` ({(~ pattern) (~ g!output)} (~ source)))]]
+ source+ (` ({(, pattern) (, g!output)} (, source)))]]
(case output
{#Some [tags' members']}
(do meta#monad
@@ -4417,8 +4417,8 @@
(in (list#conjoint decls')))
_
- (in (list (` ("lux def" (~ (local$ (..module_alias (list short imported_module) alias)))
- (~ source+)
+ (in (list (` ("lux def" (, (local$ (..module_alias (list short imported_module) alias)))
+ (, source+)
#0)))))))
(def (implementation_declarations imported_module alias implementation)
@@ -4490,18 +4490,18 @@
_
(do meta#monad
[g!implementation (..generated_symbol "implementation")]
- (in [{#Item (` ("lux def" (~ g!implementation) (~ it) #0)) pre_defs}
+ (in [{#Item (` ("lux def" (, g!implementation) (, it) #0)) pre_defs}
{#Item g!implementation implementations}]))))
[(list) (list)]
implementations))
.let [[pre_defs implementations] pre_defs,implementations]]
(in (|> pre_defs
{#Item (` (..use
- (~ (text$ current_module))
- (~ (text$ imported_module))
- (~ (text$ import_alias))
- (~ (text$ alias))
- (~+ implementations)))}
+ (, (text$ current_module))
+ (, (text$ imported_module))
+ (, (text$ import_alias))
+ (, (text$ alias))
+ (,* implementations)))}
list#reversed)))))
@@ -4545,11 +4545,11 @@
[referrals (..referrals imported_module options)
current_module ..current_module_name]
(in (list#each (function (_ [macro parameters])
- (` ((~ (symbol$ macro))
- (~ (text$ current_module))
- (~ (text$ imported_module))
- (~ (text$ alias))
- (~+ parameters))))
+ (` ((, (symbol$ macro))
+ (, (text$ current_module))
+ (, (text$ imported_module))
+ (, (text$ alias))
+ (,* parameters))))
referrals)))
_
@@ -4560,8 +4560,8 @@
(case (..parsed (..andP ..anyP ..anyP)
tokens)
{.#Some [implementation expression]}
- (meta#in (list (` (..let [(..open (~ (text$ (alias_stand_in 0)))) (~ implementation)]
- (~ expression)))))
+ (meta#in (list (` (..let [(..open (, (text$ (alias_stand_in 0)))) (, implementation)]
+ (, expression)))))
{.#None}
(failure (..wrong_syntax_error (symbol ..with))))))
@@ -4570,10 +4570,10 @@
(macro (_ tokens)
(case tokens
(pattern (list implementation [_ {#Symbol member}]))
- (meta#in (list (` (..with (~ implementation) (~ (symbol$ member))))))
+ (meta#in (list (` (..with (, implementation) (, (symbol$ member))))))
(pattern (partial_list struct member args))
- (meta#in (list (` ((..at (~ struct) (~ member)) (~+ args)))))
+ (meta#in (list (` ((..at (, struct) (, member)) (,* args)))))
_
(failure (..wrong_syntax_error (symbol ..at))))))
@@ -4612,7 +4612,7 @@
r_var)))))
list#conjoint
tuple$)]
- (meta#in (list (` ({(~ pattern) (~ output)} (~ record)))))))
+ (meta#in (list (` ({(, pattern) (, output)} (, record)))))))
_
(failure "has can only use records.")))
@@ -4631,33 +4631,33 @@
.let [pairs (zipped_2 slots bindings)
update_expr (list#mix (is (-> [Code Code] Code Code)
(function (_ [s b] v)
- (` (..has (~ s) (~ v) (~ b)))))
+ (` (..has (, s) (, v) (, b)))))
value
(list#reversed pairs))
[_ accesses'] (list#mix (is (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))])
(function (_ [new_slot new_binding] [old_record accesses'])
- [(` (the (~ new_slot) (~ new_binding)))
+ [(` (the (, new_slot) (, new_binding)))
{#Item (list new_binding old_record) accesses'}]))
[record (is (List (List Code)) {#End})]
pairs)
accesses (list#conjoint (list#reversed accesses'))]]
- (in (list (` (let [(~+ accesses)]
- (~ update_expr)))))))
+ (in (list (` (let [(,* accesses)]
+ (, update_expr)))))))
(pattern (list selector value))
(do meta#monad
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!record))
- (..has (~ selector) (~ value) (~ g!record)))))))
+ (in (list (` (function ((, g!_) (, g!record))
+ (..has (, selector) (, value) (, g!record)))))))
(pattern (list selector))
(do meta#monad
[g!_ (..generated_symbol "_")
g!value (..generated_symbol "value")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!value) (~ g!record))
- (..has (~ selector) (~ g!value) (~ g!record)))))))
+ (in (list (` (function ((, g!_) (, g!value) (, g!record))
+ (..has (, selector) (, g!value) (, g!record)))))))
_
(failure (..wrong_syntax_error (symbol ..has))))))
@@ -4692,11 +4692,11 @@
(function (_ [r_slot_name r_idx r_var])
(list (symbol$ r_slot_name)
(if ("lux i64 =" idx r_idx)
- (` ((~ fun) (~ r_var)))
+ (` ((, fun) (, r_var)))
r_var)))))
list#conjoint
tuple$)]
- (meta#in (list (` ({(~ pattern) (~ output)} (~ record)))))))
+ (meta#in (list (` ({(, pattern) (, output)} (, record)))))))
_
(failure "revised can only use records.")))
@@ -4710,24 +4710,24 @@
(do meta#monad
[g!record (..generated_symbol "record")
g!temp (..generated_symbol "temp")]
- (in (list (` (let [(~ g!record) (~ record)
- (~ g!temp) (the [(~+ slots)] (~ g!record))]
- (has [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record))))))))
+ (in (list (` (let [(, g!record) (, record)
+ (, g!temp) (the [(,* slots)] (, g!record))]
+ (has [(,* slots)] ((, fun) (, g!temp)) (, g!record))))))))
(pattern (list selector fun))
(do meta#monad
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!record))
- (..revised (~ selector) (~ fun) (~ g!record)))))))
+ (in (list (` (function ((, g!_) (, g!record))
+ (..revised (, selector) (, fun) (, g!record)))))))
(pattern (list selector))
(do meta#monad
[g!_ (..generated_symbol "_")
g!fun (..generated_symbol "fun")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!fun) (~ g!record))
- (..revised (~ selector) (~ g!fun) (~ g!record)))))))
+ (in (list (` (function ((, g!_) (, g!fun) (, g!record))
+ (..revised (, selector) (, g!fun) (, g!record)))))))
_
(failure (..wrong_syntax_error (symbol ..revised))))))
@@ -4791,31 +4791,31 @@
(-> Type Code)
(case type
{#Primitive name params}
- (` {.#Primitive (~ (text$ name)) (~ (untemplated_list (list#each type_code params)))})
+ (` {.#Primitive (, (text$ name)) (, (untemplated_list (list#each type_code params)))})
(with_template#pattern [<tag>]
[{<tag> left right}
- (` {<tag> (~ (type_code left)) (~ (type_code right))})])
+ (` {<tag> (, (type_code left)) (, (type_code right))})])
([.#Sum] [.#Product]
[.#Function]
[.#Apply])
(with_template#pattern [<tag>]
[{<tag> id}
- (` {<tag> (~ (nat$ id))})])
+ (` {<tag> (, (nat$ id))})])
([.#Parameter] [.#Var] [.#Ex])
(with_template#pattern [<tag>]
[{<tag> env type}
(let [env' (untemplated_list (list#each type_code env))]
- (` {<tag> (~ env') (~ (type_code type))}))])
+ (` {<tag> (, env') (, (type_code type))}))])
([.#UnivQ] [.#ExQ])
{#Named [module name] anonymous}
... TODO: Generate the explicit type definition instead of using
... the "symbol$" shortcut below.
- ... (` {.#Named [(~ (text$ module)) (~ (text$ name))]
- ... (~ (type_code anonymous))})
+ ... (` {.#Named [(, (text$ module)) (, (text$ name))]
+ ... (, (type_code anonymous))})
(symbol$ [module name])))
(def .public loop
@@ -4841,19 +4841,19 @@
init_types (monad#each meta#monad type_definition inits')
expected ..expected_type]
(meta#in (list (` (("lux type check"
- (-> (~+ (list#each type_code init_types))
- (~ (type_code expected)))
- (function ((~ name) (~+ vars))
- (~ body)))
- (~+ inits))))))
+ (-> (,* (list#each type_code init_types))
+ (, (type_code expected)))
+ (function ((, name) (,* vars))
+ (, body)))
+ (,* inits))))))
(do meta#monad
[aliases (monad#each meta#monad
(is (-> Code (Meta Code))
(function (_ _) (..generated_symbol "")))
inits)]
- (meta#in (list (` (..let [(~+ (..interleaved aliases inits))]
- (..loop ((~ name) [(~+ (..interleaved vars aliases))])
- (~ body)))))))))
+ (meta#in (list (` (..let [(,* (..interleaved aliases inits))]
+ (..loop ((, name) [(,* (..interleaved vars aliases))])
+ (, body)))))))))
{#None}
(failure (..wrong_syntax_error (symbol ..loop))))
@@ -5020,14 +5020,14 @@
_
#0)]
- (` (case (~ calculation)
- (~ pattern)
- (~ success)
+ (` (case (, calculation)
+ (, pattern)
+ (, success)
- (~+ (if bind?
+ (,* (if bind?
(list)
(list g!_ (` {.#None}))))))))
- (` {.#Some (~ body)})
+ (` {.#Some (, body)})
(is (List [Code Code]) (list#reversed levels)))]
(list init_pattern inner_pattern_body)))
@@ -5046,17 +5046,17 @@
expected ..expected_type
g!temp (..generated_symbol "temp")]
(in (list g!temp
- (` ({{.#Some (~ g!temp)}
- (~ g!temp)
+ (` ({{.#Some (, g!temp)}
+ (, g!temp)
{.#None}
- (case (~ g!temp)
- (~+ next_branches))}
- ("lux type check" {.#Apply (~ (type_code expected)) Maybe}
- (case (~ g!temp)
- (~+ (multi_level_case$ g!temp [mlc body]))
+ (case (, g!temp)
+ (,* next_branches))}
+ ("lux type check" {.#Apply (, (type_code expected)) Maybe}
+ (case (, g!temp)
+ (,* (multi_level_case$ g!temp [mlc body]))
- (~+ (if initial_bind?
+ (,* (if initial_bind?
(list)
(list g!temp (` {.#None})))))))))))
@@ -5074,7 +5074,7 @@
(pattern (list expr))
(do meta#monad
[type ..expected_type]
- (in (list (` ("lux type as" (~ (type_code type)) (~ expr))))))
+ (in (list (` ("lux type as" (, (type_code type)) (, expr))))))
_
(failure (..wrong_syntax_error (symbol ..as_expected))))))
@@ -5093,7 +5093,7 @@
.let [[module line column] location
location (all "lux text concat" (text#encoded module) "," (nat#encoded line) "," (nat#encoded column))
message (all "lux text concat" "Undefined behavior @ " location)]]
- (in (list (` (..panic! (~ (text$ message)))))))
+ (in (list (` (..panic! (, (text$ message)))))))
_
(failure (..wrong_syntax_error (symbol ..undefined))))))
@@ -5109,8 +5109,8 @@
(pattern (list expression))
(do meta#monad
[g!temp (..generated_symbol "g!temp")]
- (in (list (` (let [(~ g!temp) (~ expression)]
- (..type_of (~ g!temp)))))))
+ (in (list (` (let [(, g!temp) (, expression)]
+ (..type_of (, g!temp)))))))
_
(failure (..wrong_syntax_error (symbol ..type_of))))))
@@ -5134,19 +5134,19 @@
g!compiler (..generated_symbol "compiler")
g!_ (..generated_symbol "_")
.let [rep_env (list#each (function (_ arg)
- [arg (` ((~' ~) (~ (local$ arg))))])
+ [arg (` ((,' ,) (, (local$ arg))))])
args)]
this_module current_module_name]
- (in (list (` (..macro ((~ (local$ name)) (~ g!tokens) (~ g!compiler))
- (case (~ g!tokens)
- (pattern (list (~+ (list#each local$ args))))
- {.#Right [(~ g!compiler)
- (list (~+ (list#each (function (_ template)
- (` (`' (~ (with_replacements rep_env
+ (in (list (` (..macro ((, (local$ name)) (, g!tokens) (, g!compiler))
+ (case (, g!tokens)
+ (pattern (list (,* (list#each local$ args))))
+ {.#Right [(, g!compiler)
+ (list (,* (list#each (function (_ template)
+ (` (`' (, (with_replacements rep_env
template)))))
input_templates)))]}
- (~ g!_)
+ (, g!_)
{.#Left "Invalid syntax."}))))))
{#None}
@@ -5259,7 +5259,7 @@
[stvs ..scope_type_vars]
(case (..item idx (list#reversed stvs))
{#Some var_id}
- (in (list (` {.#Ex (~ (nat$ var_id))})))
+ (in (list (` {.#Ex (, (nat$ var_id))})))
{#None}
(failure (text#composite "Indexed-type does not exist: " (nat#encoded idx)))))
@@ -5270,11 +5270,11 @@
(def (refer_code imported_module alias referrals)
(-> Text Text (List Referral) Code)
- (` ((~! ..refer)
- (~ (text$ imported_module))
- (~ (text$ alias))
- (~+ (list#each (function (_ [macro parameters])
- (` ((~ (symbol$ macro)) (~+ parameters))))
+ (` ((,! ..refer)
+ (, (text$ imported_module))
+ (, (text$ alias))
+ (,* (list#each (function (_ [macro parameters])
+ (` ((, (symbol$ macro)) (,* parameters))))
referrals)))))
(def .public require
@@ -5285,13 +5285,13 @@
.let [=imports (|> imports
(list#each (is (-> Importation Code)
(function (_ [module_name m_alias =refer])
- (` [(~ (text$ module_name)) (~ (text$ (..maybe#else "" m_alias)))]))))
+ (` [(, (text$ module_name)) (, (text$ (..maybe#else "" m_alias)))]))))
tuple$)
=refers (list#each (is (-> Importation Code)
(function (_ [module_name m_alias =refer])
(refer_code module_name (..maybe#else "" m_alias) =refer)))
imports)
- =module (` ("lux def module" (~ =imports)))]
+ =module (` ("lux def module" (, =imports)))]
g!_ (..generated_symbol "")]
(in {#Item =module
(for "Python"
@@ -5300,7 +5300,7 @@
... {library/lux/tool/compiler/language/lux/generation.no_buffer_for_saving_code}
... Artifact ID: 0
... Which only ever happens for the Python compiler.
- (partial_list (` ("lux def" (~ g!_) [] #0))
+ (partial_list (` ("lux def" (, g!_) [] #0))
=refers)
=refers)}))))
@@ -5315,7 +5315,7 @@
(-> Immediate_UnQuote Macro')
(|>> (as Macro')))
-(def .public ~~
+(def .public ,,
(..immediate_unquote
(macro (_ it)
(case it
@@ -5323,7 +5323,7 @@
(meta#in (list it))
_
- (failure (wrong_syntax_error (symbol ..~~)))))))
+ (failure (wrong_syntax_error (symbol ..,,)))))))
(def aggregate_embedded_expansions
(template (_ embedded_expansions <@> <tag> <*>)
@@ -5390,8 +5390,8 @@
(do meta#monad
[=raw (..embedded_expansions raw)
.let [[labels labelled] =raw]]
- (in (list (` (with_expansions [(~+ labels)]
- (~ labelled))))))
+ (in (list (` (with_expansions [(,* labels)]
+ (, labelled))))))
_
(failure (..wrong_syntax_error (symbol ..``))))))
@@ -5410,8 +5410,8 @@
(do meta#monad
[g!_ (..generated_symbol "g!_")]
(in (list (` ("lux try"
- (.function ((~ g!_) (~ g!_))
- (~ expression)))))))
+ (.function ((, g!_) (, g!_))
+ (, expression)))))))
_
(..failure (..wrong_syntax_error (symbol ..try))))))
@@ -5434,7 +5434,7 @@
[methods' (monad#each meta#monad expansion tokens)]
(case (everyP methodP (list#conjoint methods'))
{#Some methods}
- (in (list (` (..Tuple (~+ (list#each product#right methods))))
+ (in (list (` (..Tuple (,* (list#each product#right methods))))
(tuple$ (list#each (|>> product#left text$) methods))))
{#None}
@@ -5443,8 +5443,8 @@
(def (recursive_type g!self g!dummy name body)
(-> Code Code Text Code Code)
(` {.#Apply (..Primitive "")
- (.All ((~ g!self) (~ g!dummy))
- (~ (let$ (local$ name) (` {.#Apply (..Primitive "") (~ g!self)})
+ (.All ((, g!self) (, g!dummy))
+ (, (let$ (local$ name) (` {.#Apply (..Primitive "") (, g!self)})
body)))}))
(def .public Rec