diff options
author | Eduardo Julian | 2022-07-02 05:38:27 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-07-02 05:38:27 -0400 |
commit | b96beb587c11fcfbce86ce2d62351600cf6cad1b (patch) | |
tree | c9a558ab1391ac97cb11e8777ea78299f1ab5555 /stdlib/source/library/lux/tool/compiler | |
parent | 104130efba46a875eba566384578f8aa8593ad37 (diff) |
More traditional names for unquoting macros.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
21 files changed, 223 insertions, 223 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 2d149643e..13d0ba6ed 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -178,13 +178,13 @@ (syntax (_ [content <code>.any]) (in (list (` (.<| {..#Reference} <tag> - (~ content)))))))] + (, content)))))))] [variable {reference.#Variable}] [constant {reference.#Constant}] - [local ((~! reference.local))] - [foreign ((~! reference.foreign))] + [local ((,! reference.local))] + [foreign ((,! reference.foreign))] ) (with_template [<name> <tag>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index e13058163..bbffab2a0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -224,8 +224,8 @@ list.reversed)) (with_template [<name> <types> <inputs> <exception> <when> <then>] - [(`` (def .public (<name> (~~ (template.spliced <inputs>)) complex) - (-> (~~ (template.spliced <types>)) Type (Operation Type)) + [(`` (def .public (<name> (,, (template.spliced <inputs>)) complex) + (-> (,, (template.spliced <types>)) Type (Operation Type)) (loop (again [depth 0 it complex]) (case it diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index b8067a964..bd46c3d8c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -251,9 +251,9 @@ (phase.except ..no_buffer_for_saving_code [artifact_id])))) (with_template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>] - [(`` (def .public (<name> it (~~ (template.spliced <inputs>)) dependencies) + [(`` (def .public (<name> it (,, (template.spliced <inputs>)) dependencies) (All (_ anchor expression declaration) - (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression declaration artifact.ID))) + (-> <type> (,, (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression declaration artifact.ID))) (function (_ (^.let stateE [bundle state])) (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))] {try.#Success [[bundle (has #registry registry' state)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index adabb8621..5882c78f4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -111,25 +111,25 @@ [.#Int /simple.int] [.#Rev /simple.rev]) - (^.` [(~+ elems)]) + (^.` [(,* elems)]) (/complex.record analysis archive elems) - (^.` {(~ [_ {.#Symbol tag}]) (~+ values)}) + (^.` {(, [_ {.#Symbol tag}]) (,* values)}) (..variant_analysis analysis archive tag values) - (^.` ({(~+ branches)} (~ input))) + (^.` ({(,* branches)} (, input))) (..case_analysis analysis archive input branches code) - (^.` ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body))) + (^.` ([(, [_ {.#Symbol ["" function_name]}]) (, [_ {.#Symbol ["" arg_name]}])] (, body))) (/function.function analysis function_name arg_name archive body) - (^.` ((~ [_ {.#Text extension_name}]) (~+ extension_args))) + (^.` ((, [_ {.#Text extension_name}]) (,* extension_args))) (//extension.apply archive analysis [extension_name extension_args]) - (^.` ((~ functionC) (~+ argsC+))) + (^.` ((, functionC) (,* argsC+))) (..apply_analysis expander analysis archive functionC argsC+) - (^.` {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)}) + (^.` {(, [_ {.#Nat lefts}]) (, [_ {.#Bit right?}]) (,* values)}) (..sum_analysis analysis archive lefts right? values) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index db181d050..7301f6b8e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -301,9 +301,9 @@ (n.= (-- num_cases) idx)) (pattern_analysis {.#None} (type.variant (list.after (-- num_cases) flat_sum)) - (` [(~+ values)]) + (` [(,* values)]) next) - (pattern_analysis {.#None} caseT (` [(~+ values)]) next)) + (pattern_analysis {.#None} caseT (` [(,* values)]) next)) _ (/type.check (monad.each check.monad check.forget! @ex_var+))] (in [(/pattern.variant [lefts right? testP]) nextA])) @@ -331,7 +331,7 @@ [idx group variantT] (///extension.lifted (meta.tag tag)) _ (/type.check (check.check :input: variantT)) .let [[lefts right?] (/complex.choice (list.size group) idx)]] - (pattern_analysis {.#Some (list.size group)} :input: (` {(~ (code.nat lefts)) (~ (code.bit right?)) (~+ values)}) next))) + (pattern_analysis {.#Some (list.size group)} :input: (` {(, (code.nat lefts)) (, (code.bit right?)) (,* values)}) next))) _ (/.except ..invalid [pattern]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 4328de2b2..2ee8cae7d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -46,7 +46,7 @@ members (List Code)]) (exception.report "Type" (%.type type) - "Expression" (%.code (` [(~+ members)]))))] + "Expression" (%.code (` [(,* members)]))))] [invalid_tuple_type] [cannot_analyse_tuple] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 42e4d3e3c..54592b36b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -539,7 +539,7 @@ (/////analysis.except ..non_parameter objectT) {.#Primitive name parameters} - (`` (cond (or (~~ (with_template [<type>] + (`` (cond (or (,, (with_template [<type>] [(text#= (..reflection <type>) name)] [jvm.boolean] @@ -597,7 +597,7 @@ (-> .Type (Operation (Type Value))) (case objectT {.#Primitive name {.#End}} - (`` (cond (~~ (with_template [<type>] + (`` (cond (,, (with_template [<type>] [(text#= (..reflection <type>) name) (phase#in <type>)] @@ -610,7 +610,7 @@ [jvm.double] [jvm.char])) - (~~ (with_template [<type>] + (,, (with_template [<type>] [(text#= (..reflection (jvm.array <type>)) name) (phase#in (jvm.array <type>))] @@ -986,7 +986,7 @@ (analyse archive fromC)) source_name (at ! each ..reflection (check_jvm fromT)) can_cast? (is (Operation Bit) - (`` (cond (~~ (with_template [<primitive> <object>] + (`` (cond (,, (with_template [<primitive> <object>] [(let [=primitive (reflection.reflection <primitive>)] (or (and (text#= =primitive source_name) (or (text#= <object> target_name) @@ -1175,7 +1175,7 @@ (list#each (|>> again (as (Type Parameter)))) (jvm.class name)) {.#None}) - (~~ (with_template [<read> <as> <write>] + (,, (with_template [<read> <as> <write>] [(case (<read> it) {.#Some :sub:} (<write> (as (Type <as>) (again :sub:))) @@ -1258,8 +1258,8 @@ (with_template [<name> <type> <params>] [(`` (def <name> - (-> (<type> (~~ (template.spliced <params>))) (List (Type Class))) - (|>> (~~ (template.symbol [<type> "::getExceptionTypes"])) + (-> (<type> (,, (template.spliced <params>))) (List (Type Class))) + (|>> (,, (template.symbol [<type> "::getExceptionTypes"])) (array.list {.#None}) (list#each ..lux_class))))] @@ -2508,7 +2508,7 @@ (^.with_template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad - [constant (`` (|> value (~~ (template.spliced <constant>)))) + [constant (`` (|> value (,, (template.spliced <constant>)))) attribute (attribute.constant constant)] (field.field ..constant::modifier name #1 <type> (sequence.sequence attribute)))]) ([.#Bit jvm.boolean [(pipe.case #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux index 556a622be..9f74950cb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux @@ -113,7 +113,7 @@ (def visibility' (<text>.Parser (Modifier field.Field)) (`` (all <>.either - (~~ (with_template [<label> <modifier>] + (,, (with_template [<label> <modifier>] [(<>.after (<text>.this <label>) (<>#in <modifier>))] ["public" field.public] @@ -128,7 +128,7 @@ (def inheritance (Parser (Modifier class.Class)) (`` (all <>.either - (~~ (with_template [<label> <modifier>] + (,, (with_template [<label> <modifier>] [(<>.after (<code>.this_text <label>) (<>#in <modifier>))] ["final" class.final] @@ -138,7 +138,7 @@ (def state (Parser (Modifier field.Field)) (`` (all <>.either - (~~ (with_template [<label> <modifier>] + (,, (with_template [<label> <modifier>] [(<>.after (<code>.this_text <label>) (<>#in <modifier>))] ["volatile" field.volatile] @@ -235,7 +235,7 @@ (^.with_template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad - [constant (`` (|> value (~~ (template.spliced <constant>)))) + [constant (`` (|> value (,, (template.spliced <constant>)))) attribute (attribute.constant constant)] (field.field ..constant::modifier name #1 <type> (sequence.sequence attribute)))]) ([.#Bit type.boolean [(pipe.case #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] @@ -431,7 +431,7 @@ (<load> jvm_register) (value.wrap <type>) (_.astore lux_register))]]] - (`` (cond (~~ (with_template [<shift> <load> <type>] + (`` (cond (,, (with_template [<shift> <load> <type>] [(at type.equivalence = <type> argumentT) (wrap_primitive <shift> <load> <type>)] @@ -517,7 +517,7 @@ [(all _.composite (value.unwrap <type>) <return>)]] - (`` (cond (~~ (with_template [<return> <type>] + (`` (cond (,, (with_template [<return> <type>] [(at type.equivalence = <type> returnT) (unwrap_primitive <return> <type>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index 73c27d038..13662d1c3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -608,7 +608,7 @@ (function (_ extension_name generate archive [from to valueS]) (do //////.monad [valueG (generate archive valueS)] - (in (`` (cond (~~ (with_template [<object> <type>] + (in (`` (cond (,, (with_template [<object> <type>] [(and (text#= (..reflection <type>) from) (text#= <object> to)) (all _.composite @@ -1181,7 +1181,7 @@ [(all _.composite (///value.unwrap <type>) <return>)]] - (`` (cond (~~ (with_template [<return> <type>] + (`` (cond (,, (with_template [<return> <type>] [(at type.equivalence = <type> returnT) (unwrap_primitive <return> <type>)] @@ -1236,7 +1236,7 @@ (<load> jvm_register) (///value.wrap <type>) (_.astore lux_register))]]] - (`` (cond (~~ (with_template [<shift> <load> <type>] + (`` (cond (,, (with_template [<shift> <load> <type>] [(at type.equivalence = <type> argumentT) (wrap_primitive <shift> <load> <type>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index 5667e47db..434d214e0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -92,13 +92,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def runtime (syntax (_ [declaration (<>.or <code>.local @@ -109,18 +109,18 @@ [runtime_id meta.seed] (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.var (~ (code.text (%.code runtime)))))] + runtime_name (` (_.var (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (let [g!name (code.local name) code_nameC (code.local (format "@" name))] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) _.Var/1 - (~ runtime_name))) + (, runtime_name))) - (` (def (~ code_nameC) + (` (def (, code_nameC) (_.Expression Any) - (_.defparameter (~ runtime_name) (~ code))))))) + (_.defparameter (, runtime_name) (, code))))))) {.#Right [name inputs]} (let [g!name (code.local name) @@ -129,15 +129,15 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) (_.Computation Any)) - (_.call/* (~ runtime_name) (list (~+ inputsC))))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) (_.Computation Any)) + (_.call/* (, runtime_name) (list (,* inputsC))))) - (` (def (~ code_nameC) + (` (def (, code_nameC) (_.Expression Any) - (..with_vars [(~+ inputsC)] - (_.defun (~ runtime_name) (_.args (list (~+ inputsC))) - (~ code)))))))))))))) + (..with_vars [(,* inputsC)] + (_.defun (, runtime_name) (_.args (list (,* inputsC))) + (, code)))))))))))))) (runtime (lux//try op) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 0f8d68aea..0ccc9cbd3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -22,7 +22,7 @@ (def Vector (syntax (_ [size <code>.nat elemT <code>.any]) - (in (list (` [(~+ (list.repeated size elemT))]))))) + (in (list (` [(,* (list.repeated size elemT))]))))) (def Arity (template (_ arity) @@ -34,24 +34,24 @@ (with_symbols [g!_ g!extension g!name g!phase g!archive g!inputs g!anchor g!expression g!declaration] (do [! meta.monad] [g!input+ (monad.all ! (list.repeated arity (macro.symbol "input")))] - (in (list (` (is (All ((~ g!_) (~ g!anchor) (~ g!expression) (~ g!declaration)) - (-> ((Arity (~ (code.nat arity))) (~ g!expression)) - (generation.Handler (~ g!anchor) (~ g!expression) (~ g!declaration)))) - (function ((~ g!_) (~ g!extension)) - (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!archive) (~ g!inputs)) - (case (~ g!inputs) - (pattern (list (~+ g!input+))) + (in (list (` (is (All ((, g!_) (, g!anchor) (, g!expression) (, g!declaration)) + (-> ((Arity (, (code.nat arity))) (, g!expression)) + (generation.Handler (, g!anchor) (, g!expression) (, g!declaration)))) + (function ((, g!_) (, g!extension)) + (function ((, g!_) (, g!name) (, g!phase) (, g!archive) (, g!inputs)) + (case (, g!inputs) + (pattern (list (,* g!input+))) (do ///.monad - [(~+ (|> g!input+ + [(,* (|> g!input+ (list#each (function (_ g!input) - (list g!input (` ((~ g!phase) (~ g!archive) (~ g!input)))))) + (list g!input (` ((, g!phase) (, g!archive) (, g!input)))))) list.together))] - ((~' in) ((~ g!extension) [(~+ g!input+)]))) + ((,' in) ((, g!extension) [(,* g!input+)]))) - (~ g!_) - (///.except ///extension.incorrect_arity [(~ g!name) - (~ (code.nat arity)) - (list.size (~ g!inputs))])) + (, g!_) + (///.except ///extension.incorrect_arity [(, g!name) + (, (code.nat arity)) + (list.size (, g!inputs))])) )))))))))) (with_template [<arity> <type> <term>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index cc2e746e4..75762cc34 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -86,13 +86,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def runtime (syntax (_ [declaration (<>.or <code>.local @@ -100,35 +100,35 @@ (<>.some <code>.local)))) code <code>.any]) (macro.with_symbols [g!_ runtime] - (let [runtime_name (` (_.var (~ (code.text (%.code runtime)))))] + (let [runtime_name (` (_.var (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) Var - (~ runtime_name))) + (, runtime_name))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!name)) - (~ code)))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!name)) + (, code)))))))) {.#Right [name inputs]} (let [g!name (code.local name) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) Computation) - (_.apply (~ runtime_name) (list (~+ inputsC))))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) Computation) + (_.apply (, runtime_name) (list (,* inputsC))))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!_)) - (..with_vars [(~+ inputsC)] - (_.function (~ g!_) (list (~+ inputsC)) - (~ code))))))))))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!_)) + (..with_vars [(,* inputsC)] + (_.function (, g!_) (list (,* inputsC)) + (, code))))))))))))))) (def length (-> Expression Computation) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux index 365da0d4d..d44068070 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux @@ -13,7 +13,7 @@ (with_template [<name> <boolean> <byte> <short> <int> <long> <float> <double> <char>] [(def (<name> type) (-> (Type Primitive) Text) - (`` (cond (~~ (with_template [<type> <output>] + (`` (cond (,, (with_template [<type> <output>] [(type#= <type> type) <output>] [type.boolean <boolean>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index 1c22af9cc..0d3d0f783 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -108,13 +108,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def module_id 0) @@ -128,20 +128,20 @@ [runtime_id meta.seed] (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.var (~ (code.text (%.code runtime)))))] + runtime_name (` (_.var (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (macro.with_symbols [g!_] (let [g!name (code.local name)] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) Var - (~ runtime_name))) + (, runtime_name))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!name)) - (_.set (~ g!name) (~ code)))))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!name)) + (_.set (, g!name) (, code)))))))))) {.#Right [name inputs]} (macro.with_symbols [g!_] @@ -149,17 +149,17 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) Computation) - (_.apply (list (~+ inputsC)) (~ runtime_name)))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) Computation) + (_.apply (list (,* inputsC)) (, runtime_name)))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!_)) - (..with_vars [(~+ inputsC)] - (_.function (~ g!_) (list (~+ inputsC)) - (~ code))))))))))))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!_)) + (..with_vars [(,* inputsC)] + (_.function (, g!_) (list (,* inputsC)) + (, code))))))))))))))))) (def (item index table) (-> Expression Expression Location) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index fa45c35b0..2e525be79 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -75,13 +75,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def module_id 0) @@ -95,20 +95,20 @@ [runtime_id meta.seed] (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.constant (~ (code.text (%.code runtime)))))] + runtime_name (` (_.constant (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (macro.with_symbols [g!_] (let [g!name (code.local name)] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) Var - (~ runtime_name))) + (, runtime_name))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!name)) - (_.define (~ g!name) (~ code)))))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!name)) + (_.define (, g!name) (, code)))))))))) {.#Right [name inputs]} (macro.with_symbols [g!_] @@ -116,18 +116,18 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) Computation) - (_.apply (list (~+ inputsC)) (~ runtime_name)))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) Computation) + (_.apply (list (,* inputsC)) (, runtime_name)))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..feature (~ runtime_name) - (function ((~ g!_) (~ g!_)) - (..with_vars [(~+ inputsC)] - (_.define_function (~ g!_) - (list (~+ (list#each (|>> (~) [false] (`)) inputsC))) - (~ code))))))))))))))))) + (..feature (, runtime_name) + (function ((, g!_) (, g!_)) + (..with_vars [(,* inputsC)] + (_.define_function (, g!_) + (list (,* (list#each (|>> (,) [false] (`)) inputsC))) + (, code))))))))))))))))) (runtime (io//log! message) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 93f0477c7..19c967248 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -114,13 +114,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def runtime (syntax (_ [declaration (<>.or <code>.local @@ -132,32 +132,32 @@ (macro.with_symbols [g!_] (let [nameC (code.local name) code_nameC (code.local (format "@" name)) - runtime_nameC (` (runtime_name (~ (code.text name))))] - (in (list (` (def .public (~ nameC) SVar (~ runtime_nameC))) - (` (def (~ code_nameC) + runtime_nameC (` (runtime_name (, (code.text name))))] + (in (list (` (def .public (, nameC) SVar (, runtime_nameC))) + (` (def (, code_nameC) (Statement Any) - (..feature (~ runtime_nameC) - (function ((~ g!_) (~ g!_)) - (_.set (list (~ g!_)) (~ code)))))))))) + (..feature (, runtime_nameC) + (function ((, g!_) (, g!_)) + (_.set (list (, g!_)) (, code)))))))))) {.#Right [name inputs]} (macro.with_symbols [g!_] (let [nameC (code.local name) code_nameC (code.local (format "@" name)) - runtime_nameC (` (runtime_name (~ (code.text name)))) + runtime_nameC (` (runtime_name (, (code.text name)))) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def .public ((~ nameC) (~+ inputsC)) - (-> (~+ inputs_typesC) (Computation Any)) - (_.apply (list (~+ inputsC)) (~ runtime_nameC)))) - (` (def (~ code_nameC) + (in (list (` (def .public ((, nameC) (,* inputsC)) + (-> (,* inputs_typesC) (Computation Any)) + (_.apply (list (,* inputsC)) (, runtime_nameC)))) + (` (def (, code_nameC) (Statement Any) - (..feature (~ runtime_nameC) - (function ((~ g!_) (~ g!_)) - (..with_vars [(~+ inputsC)] - (_.def (~ g!_) (list (~+ inputsC)) - (~ code)))))))))))))) + (..feature (, runtime_nameC) + (function ((, g!_) (, g!_)) + (..with_vars [(,* inputsC)] + (_.def (, g!_) (list (,* inputsC)) + (, code)))))))))))))) (runtime (lux::try op) @@ -292,7 +292,7 @@ (runtime (i64::64 input) (with_vars [temp] - (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (,, (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (all _.then (_.set (list temp) (_.% <iteration> input)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index b0d02c095..49dfb21af 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -81,13 +81,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def runtime (syntax (_ [declaration (<>.or <code>.local @@ -98,33 +98,33 @@ [runtime_id meta.seed] (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.var (~ (code.text (%.code runtime)))))] + runtime_name (` (_.var (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) _.SVar - (~ runtime_name))) + (, runtime_name))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) _.Expression - (_.set! (~ runtime_name) (~ code))))))) + (_.set! (, runtime_name) (, code))))))) {.#Right [name inputs]} (let [g!name (code.local name) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) _.Expression) - (_.apply (list (~+ inputsC)) (~ runtime_name)))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) _.Expression) + (_.apply (list (,* inputsC)) (, runtime_name)))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) _.Expression - (..with_vars [(~+ inputsC)] - (_.set! (~ runtime_name) - (_.function (list (~+ inputsC)) - (~ code))))))))))))))) + (..with_vars [(,* inputsC)] + (_.set! (, runtime_name) + (_.function (list (,* inputsC)) + (, code))))))))))))))) (def .public variant_tag_field "luxVT") (def .public variant_flag_field "luxVF") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index a3d1fe4ab..6684e6a59 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -73,13 +73,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.local (~ (code.text (format "v" (%.nat id))))))))) + (` (_.local (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def module_id 0) @@ -116,41 +116,41 @@ {.#Left name} (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.constant (~ (code.text (%.code runtime))))) + runtime_name (` (_.constant (, (code.text (%.code runtime))))) g!name (code.local name)] - (in (list (` (def .public (~ g!name) _.CVar (~ runtime_name))) - (` (def (~ (code.local (format "@" name))) + (in (list (` (def .public (, g!name) _.CVar (, runtime_name))) + (` (def (, (code.local (format "@" name))) Statement - (~ (list#mix (function (_ [when then] else) - (` (_.if (~ when) - (_.set (list (~ runtime_name)) (~ then)) - (~ else)))) - (` (_.set (list (~ runtime_name)) (~ default_implementation))) + (, (list#mix (function (_ [when then] else) + (` (_.if (, when) + (_.set (list (, runtime_name)) (, then)) + (, else)))) + (` (_.set (list (, runtime_name)) (, default_implementation))) conditional_implementations)))))))) {.#Right [name inputs]} (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.local (~ (code.text (%.code runtime))))) + runtime_name (` (_.local (, (code.text (%.code runtime))))) g!name (code.local name) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) Computation) - (_.apply (list (~+ inputsC)) {.#None} - (~ runtime_name)))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) Computation) + (_.apply (list (,* inputsC)) {.#None} + (, runtime_name)))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) Statement - (..with_vars [(~+ inputsC)] - (~ (list#mix (function (_ [when then] else) - (` (_.if (~ when) - (_.function (~ runtime_name) (list (~+ inputsC)) - (~ then)) - (~ else)))) - (` (_.function (~ runtime_name) (list (~+ inputsC)) - (~ default_implementation))) + (..with_vars [(,* inputsC)] + (, (list#mix (function (_ [when then] else) + (` (_.if (, when) + (_.function (, runtime_name) (list (,* inputsC)) + (, then)) + (, else)))) + (` (_.function (, runtime_name) (list (,* inputsC)) + (, default_implementation))) conditional_implementations)))))))))))))) (def tuple_size @@ -295,7 +295,7 @@ (i64::i64 input) [..mruby? (_.return input)] (with_vars [temp] - (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (,, (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (all _.then (_.set (list temp) (_.% <iteration> input)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index 215e6af9a..1bf3f72eb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -63,13 +63,13 @@ body <code>.any]) (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] - (in (list (` (let [(~+ (|> vars + (in (list (` (let [(,* (|> vars (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) - (` (_.var (~ (code.text (format "v" (%.nat id))))))))) + (` (_.var (, (code.text (format "v" (%.nat id))))))))) list.together))] - (~ body)))))))) + (, body)))))))) (def runtime (syntax (_ [declaration (<>.or <code>.local @@ -80,32 +80,32 @@ [runtime_id meta.seed] (macro.with_symbols [g!_] (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) - runtime_name (` (_.var (~ (code.text (%.code runtime)))))] + runtime_name (` (_.var (, (code.text (%.code runtime)))))] (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def .public (~ g!name) + (in (list (` (def .public (, g!name) Var - (~ runtime_name))) + (, runtime_name))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) _.Computation - (_.define_constant (~ runtime_name) (~ code))))))) + (_.define_constant (, runtime_name) (, code))))))) {.#Right [name inputs]} (let [g!name (code.local name) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def .public ((~ g!name) (~+ inputsC)) - (-> (~+ inputs_typesC) _.Computation) - (_.apply (list (~+ inputsC)) (~ runtime_name)))) + (in (list (` (def .public ((, g!name) (,* inputsC)) + (-> (,* inputs_typesC) _.Computation) + (_.apply (list (,* inputsC)) (, runtime_name)))) - (` (def (~ (code.local (format "@" name))) + (` (def (, (code.local (format "@" name))) _.Computation - (..with_vars [(~+ inputsC)] - (_.define_function (~ runtime_name) [(list (~+ inputsC)) {.#None}] - (~ code)))))))))))))) + (..with_vars [(,* inputsC)] + (_.define_function (, runtime_name) [(list (,* inputsC)) {.#None}] + (, code)))))))))))))) (def last_index (-> Expression Computation) @@ -263,7 +263,7 @@ (runtime (i64//64 input) (with_vars [temp] - (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (,, (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (_.let (list [temp (_.remainder/2 <iteration> input)]) (_.if (|> temp <scenario>) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index a3872dfa5..cba888c44 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -64,7 +64,7 @@ [(for @.python (def <declaration> <type> <body>) ... TODO: No longer skip inlining Lua after Rembulan isn't being used anymore. @.lua (def <declaration> <type> <body>) - (`` (def (~~ (..declaration_name <declaration>)) + (`` (def (,, (..declaration_name <declaration>)) (template <declaration> [<body>]))))])) @@ -297,7 +297,7 @@ (with_expansions [<digits> (these "0" "1" "2" "3" "4" "5" "6" "7" "8" "9") <non_symbol_chars> (with_template [<char>] - [(~~ (static <char>))] + [(,, (static <char>))] [text.space] [text.new_line] [text.carriage_return] @@ -322,7 +322,7 @@ [[<digits> <digit_separator>] @then - (~~ (template.spliced @else_options))] + (,, (template.spliced @else_options))] ... else @else))])) @@ -372,7 +372,7 @@ <failure> (!failure ..frac_parser where offset source_code) <frac_separator> (static ..frac_separator) <signs> (with_template [<sign>] - [(~~ (static <sign>))] + [(,, (static <sign>))] [..positive_sign] [..negative_sign])] @@ -463,7 +463,7 @@ (-> Nat Text (Parser Symbol)) (<| (!with_char+ source_code//size source_code offset/0 char/0 (!end_of_file where offset/0 source_code current_module)) - (if (!n/= (char (~~ (static ..symbol_separator))) char/0) + (if (!n/= (char (,, (static ..symbol_separator))) char/0) (<| (let [offset/1 (!++ offset/0)]) (!with_char+ source_code//size source_code offset/1 char/1 (!end_of_file where offset/1 source_code current_module)) @@ -482,7 +482,7 @@ (..symbol_part_parser start where offset source_code))) (let [[where' offset' source_code'] source']) (!with_char source_code' offset' char/separator <simple>) - (if (!n/= (char (~~ (static ..symbol_separator))) char/separator) + (if (!n/= (char (,, (static ..symbol_separator))) char/separator) (<| (let [offset'' (!++ offset')]) (!letE [source'' complex] (..symbol_part_parser offset'' (!forward 1 where') offset'' source_code')) (if ("lux text =" "" complex) @@ -530,10 +530,10 @@ (<| (!with_char+ source_code//size source_code offset/0 char/0 (!end_of_file where offset/0 source_code current_module)) (with_expansions [<composites> (with_template [<open> <close> <parser>] - [[(~~ (static <open>))] + [[(,, (static <open>))] (<parser> <again> <consume_1>) - [(~~ (static <close>))] + [(,, (static <close>))] (!close <close>)] [..open_form ..close_form form_parser] @@ -541,23 +541,23 @@ [..open_tuple ..close_tuple tuple_parser] )] (`` ("lux syntax char case!" char/0 - [[(~~ (static text.space)) - (~~ (static text.carriage_return))] + [[(,, (static text.space)) + (,, (static text.carriage_return))] (again (!horizontal where offset/0 source_code)) ... New line - [(~~ (static text.new_line))] + [(,, (static text.new_line))] (again (!vertical where offset/0 source_code)) <composites> ... Text - [(~~ (static ..text_delimiter))] + [(,, (static ..text_delimiter))] (text_parser where (!++ offset/0) source_code) ... Coincidentally (= ..symbol_separator ..frac_separator) - [(~~ (static ..symbol_separator)) - ... (~~ (static ..frac_separator)) + [(,, (static ..symbol_separator)) + ... (,, (static ..frac_separator)) ] ... It's either a Rev, a symbol, or a comment. (with_expansions [<rev_parser> (rev_parser source_code//size offset/0 where (!++ offset/1) source_code) @@ -576,13 +576,13 @@ <rev_parser> ... It's either a symbol, or a comment. ("lux syntax char case!" char/1 - [[(~~ (static ..symbol_separator))] + [[(,, (static ..symbol_separator))] ... It's either a symbol, or a comment. (<| (let [offset/2 (!++ offset/1)]) (!with_char+ source_code//size source_code offset/2 char/2 (!end_of_file where offset/2 source_code current_module)) ("lux syntax char case!" char/2 - [[(~~ (static ..symbol_separator))] + [[(,, (static ..symbol_separator))] ... It's a comment. <comment_parser>] ... It's a symbol. @@ -590,17 +590,17 @@ ... It's a symbol. <short_symbol_parser>)))) - [(~~ (static ..positive_sign)) - (~~ (static ..negative_sign))] + [(,, (static ..positive_sign)) + (,, (static ..negative_sign))] (!signed_parser source_code//size offset/0 where source_code aliases (!end_of_file where offset/0 source_code current_module)) - [(~~ (static ..sigil))] + [(,, (static ..sigil))] (<| (let [offset/1 (!++ offset/0)]) (!with_char+ source_code//size source_code offset/1 char/1 (!end_of_file where offset/1 source_code current_module)) ("lux syntax char case!" char/1 - [(~~ (with_template [<char> <bit>] + [(,, (with_template [<char> <bit>] [[<char>] (..bit_syntax <bit> [where offset/0 source_code])] diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 9f4b502c8..c4a64ae2e 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -81,7 +81,7 @@ (`` (def .public self (template (self) - [(..variable (~~ (/variable.self)))]))) + [(..variable (,, (/variable.self)))]))) (def .public format (Format Reference) |