aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-01-06 14:28:32 -0400
committerEduardo Julian2022-01-06 14:28:32 -0400
commitd37982f0af44714d95caf24d7f944e4e659b3e69 (patch)
tree1576fc83764d958f8b5f7963a4d9987cd73b641f /stdlib/source/library
parent9afaa3a3236366d57cb1c3d771b25779ee76269b (diff)
Fixes for the pure-Lux JVM compiler machinery. [Part 2]
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux60
-rw-r--r--stdlib/source/library/lux/target/lua.lux107
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux28
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux334
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux91
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux145
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux182
14 files changed, 526 insertions, 451 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 30f7bbc08..4aed1937b 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -679,7 +679,7 @@
{#Apply Text Either}}}}}
([_ val]
([_ state]
- {#Right state val})))
+ {#Right [state val]})))
#0)
("lux def" failure
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 4e450d7bc..97871977f 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -128,6 +128,40 @@
["Expected" (/stack.format expected)]
["Actual" (/stack.format actual)]))
+(def: .public (set? label)
+ (-> Label (Bytecode (Maybe [Stack Address])))
+ (function (_ state)
+ (let [[pool environment tracker] state]
+ {try.#Success [state
+ [..relative_identity
+ (case (dictionary.value label (value@ #known tracker))
+ {.#Some [expected {.#Some address}]}
+ {.#Some [expected address]}
+
+ _
+ {.#None})]]})))
+
+(def: .public (acknowledged? label)
+ (-> Label (Bytecode (Maybe Stack)))
+ (function (_ state)
+ (let [[pool environment tracker] state]
+ {try.#Success [state
+ [..relative_identity
+ (case (dictionary.value label (value@ #known tracker))
+ {.#Some [expected {.#None}]}
+ {.#Some expected}
+
+ _
+ {.#None})]]})))
+
+(def: .public stack
+ (Bytecode (Maybe Stack))
+ (function (_ state)
+ (let [[pool environment tracker] state]
+ {try.#Success [state
+ [..relative_identity
+ (value@ /environment.#stack environment)]]})))
+
(with_expansions [<success> (as_is (in [[pool
environment
(revised@ #known
@@ -165,6 +199,14 @@
(: (Monad Try))
try.monad))
+(def: .public (when_continuous it)
+ (-> (Bytecode Any) (Bytecode Any))
+ (do ..monad
+ [stack ..stack]
+ (.case stack
+ {.#None} (in [])
+ {.#Some _} it)))
+
(def: .public failure
(-> Text Bytecode)
(|>> {try.#Failure} function.constant))
@@ -186,7 +228,7 @@
(/address.move (estimator counter) counter))
(def: (bytecode consumption production registry [estimator bytecode] input)
- (All (_ a) (-> U2 U2 Registry [Estimator (-> [a] Instruction)] [a] (Bytecode Any)))
+ (All (_ a) (-> U2 U2 Registry [Estimator (-> [a] Instruction)] a (Bytecode Any)))
(function (_ [pool environment tracker])
(do [! try.monad]
[environment' (|> environment
@@ -301,14 +343,14 @@
[aload_2 $0 $1 @2 _.aload_2]
[aload_3 $0 $1 @3 _.aload_3]
- [iastore $3 $1 @_ _.iastore]
- [lastore $4 $1 @_ _.lastore]
- [fastore $3 $1 @_ _.fastore]
- [dastore $4 $1 @_ _.dastore]
- [aastore $3 $1 @_ _.aastore]
- [bastore $3 $1 @_ _.bastore]
- [castore $3 $1 @_ _.castore]
- [sastore $3 $1 @_ _.sastore]
+ [iastore $3 $0 @_ _.iastore]
+ [lastore $4 $0 @_ _.lastore]
+ [fastore $3 $0 @_ _.fastore]
+ [dastore $4 $0 @_ _.dastore]
+ [aastore $3 $0 @_ _.aastore]
+ [bastore $3 $0 @_ _.bastore]
+ [castore $3 $0 @_ _.castore]
+ [sastore $3 $0 @_ _.sastore]
[istore_0 $1 $0 @0 _.istore_0]
[istore_1 $1 $0 @1 _.istore_1]
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index 72324192f..c99893692 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -1,31 +1,31 @@
(.using
- [library
- [lux {"-" Location Code Label int if cond function or and not let ^ local comment}
- ["@" target]
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]
- ["[0]" enum]]
- [control
- [pipe {"+" case> cond> new>}]
- [parser
- ["<[0]>" code]]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" template]
- ["[0]" code]]
- [math
- [number
- ["n" nat]
- ["i" int]
- ["f" frac]]]
- [type
- abstract]]])
+ [library
+ [lux {"-" Location Code Label int if function or and not let ^ local comment}
+ ["@" target]
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]
+ ["[0]" enum]]
+ [control
+ [pipe {"+" case> cond> new>}]
+ [parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" template]
+ ["[0]" code]]
+ [math
+ [number
+ ["n" nat]
+ ["i" int]
+ ["f" frac]]]
+ [type
+ abstract]]])
... Added the carriage return for better Windows compatibility.
(def: \n+
@@ -89,7 +89,7 @@
Literal
(:abstraction "nil"))
- (def: .public bool
+ (def: .public boolean
(-> Bit Literal)
(|>> (case> #0 "false"
#1 "true")
@@ -142,7 +142,7 @@
(|>> ..safe (text.enclosed' text.double_quote) :abstraction))
(def: .public multi
- (-> (List Expression) Literal)
+ (-> (List Expression) Expression)
(|>> (list#each ..code)
(text.interposed ..input_separator)
:abstraction))
@@ -159,15 +159,15 @@
(|>> (list#each (.function (_ [key value])
(format key " = " (:representation value))))
(text.interposed ..input_separator)
- (text.enclosed ["{" "}"])
+ (text.enclosed ["({" "})"])
:abstraction))
(def: .public (item idx array)
(-> Expression Expression Access)
- (:abstraction (format (:representation array) "[" (:representation idx) "]")))
+ (:abstraction (format "(" (:representation array) ")[" (:representation idx) "]")))
(def: .public (the field table)
- (-> Text Expression Computation)
+ (-> Text Expression Access)
(:abstraction (format (:representation table) "." field)))
(def: .public length
@@ -176,7 +176,7 @@
(text.enclosed ["#(" ")"])
:abstraction))
- (def: .public (apply/* args func)
+ (def: .public (apply args func)
(-> (List Expression) Expression Computation)
(|> args
(list#each ..code)
@@ -339,9 +339,9 @@
(text.enclosed ["(" ")"])
:abstraction))
- (template [<name> <code>]
+ (template [<name> <code> <binding>]
[(def: .public (<name> name args body!)
- (-> Var (List Var) Statement Statement)
+ (-> <binding> (List Var) Statement Statement)
(:abstraction
(format <code> " " (:representation name)
(|> args
@@ -350,8 +350,8 @@
(..nested (:representation body!))
\n+ "end")))]
- [function "function"]
- [local_function "local function"]
+ [function "function" Location]
+ [local_function "local function" Var]
)
(def: .public break
@@ -372,13 +372,6 @@
(:abstraction (format "-- " commentary \n+ (:representation on))))
)
-(def: .public (cond clauses else!)
- (-> (List [Expression Statement]) Statement Statement)
- (list#mix (.function (_ [test then!] next!)
- (..if test then! next!))
- else!
- (list.reversed clauses)))
-
(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
@@ -390,37 +383,23 @@
(in (list.repeated arity (` ..Expression))))
(template [<arity> <function>+]
- [(with_expansions [<apply> (template.symbol ["apply/" <arity>])
- <inputs> (arity_inputs <arity>)
+ [(with_expansions [<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: .public (<apply> function <inputs>)
- (-> Expression <types> Computation)
- (..apply/* (.list <inputs>) function))
-
(template [<function>]
- [(`` (def: .public (~~ (template.symbol [<function> "/" <arity>]))
- (<apply> (..var <function>))))]
+ [(`` (def: .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
+ (-> <types> Computation)
+ (..apply (.list <inputs>) (..var <function>))))]
<definitions>))]
[1
[["error"]
+ ["pcall"]
["print"]
["require"]
["type"]
["ipairs"]]]
-
[2
- [["print"]
- ["error"]]]
-
- [3
- [["print"]]]
-
- [4
- []]
-
- [5
- []]
+ [["error"]]]
)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index 988b31f55..bcaa03ee6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -55,7 +55,7 @@
(/////.except extension.invalid_syntax [extension_name %synthesis input]))))
(template: (!unary function)
- [(|>> list _.apply/* (|> (_.var function)))])
+ [(|>> list _.apply (|> (_.var function)))])
(def: .public (statement expression archive synthesis)
Phase!
@@ -159,12 +159,12 @@
(/.install "/" (binary (product.uncurried //runtime.i64//division)))
(/.install "%" (binary (product.uncurried //runtime.i64//remainder)))
(/.install "f64" (unary (_./ (_.float +1.0))))
- (/.install "char" (unary (_.apply/1 (_.var "utf8.char"))))
+ (/.install "char" (unary (function (_ it) (_.apply (list it) (_.var "utf8.char")))))
)))
(def: f64//decode
(Unary Expression)
- (|>> list _.apply/* (|> (_.var "tonumber")) _.return (_.closure (list)) //runtime.lux//try))
+ (|>> list _.apply (|> (_.var "tonumber")) _.return (_.closure (list)) //runtime.lux//try))
(def: f64_procs
Bundle
@@ -174,11 +174,11 @@
(/.install "-" (binary (product.uncurried _.-)))
(/.install "*" (binary (product.uncurried _.*)))
(/.install "/" (binary (product.uncurried _./)))
- (/.install "%" (binary (product.uncurried (function.flipped (_.apply/2 (_.var "math.fmod"))))))
+ (/.install "%" (binary (product.uncurried (function (_ parameter subject) (_.apply (list subject parameter) (_.var "math.fmod"))))))
(/.install "=" (binary (product.uncurried _.=)))
(/.install "<" (binary (product.uncurried _.<)))
(/.install "i64" (unary (!unary "math.floor")))
- (/.install "encode" (unary (_.apply/2 (_.var "string.format") (_.string "%.17g"))))
+ (/.install "encode" (unary (function (_ it) (_.apply (list (_.string "%.17g") it) (_.var "string.format")))))
(/.install "decode" (unary ..f64//decode)))))
(def: (text//char [paramO subjectO])
@@ -211,7 +211,7 @@
(def: (io//log! messageO)
(Unary Expression)
- (|> (_.apply/* (list messageO) (_.var "print"))
+ (|> (_.apply (list messageO) (_.var "print"))
(_.or //runtime.unit)))
(def: io_procs
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
index 4a9997ec7..23469d067 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
@@ -109,11 +109,11 @@
(function (_ extension phase archive inputS)
(do [! ////////phase.monad]
[inputG (phase archive inputS)]
- (in (_.apply/1 (<| (_.closure (list $input))
- (_.return (|> (_.var "string.byte")
- (_.apply/* (list $input (_.int +1) (_.length $input)))
- (_.apply/1 (_.var "table.pack")))))
- inputG))))]))
+ (in (<| (_.apply (list inputG))
+ (_.closure (list $input))
+ (_.return (_.apply (list (_.apply (list $input (_.int +1) (_.length $input))
+ (_.var "string.byte")))
+ (_.var "table.pack")))))))]))
(def: utf8::decode
(custom
@@ -121,9 +121,9 @@
(function (_ extension phase archive inputS)
(do [! ////////phase.monad]
[inputG (phase archive inputS)]
- (in (|> inputG
- (_.apply/1 (_.var "table.unpack"))
- (_.apply/1 (_.var "string.char"))))))]))
+ (in (_.apply (list (_.apply (list inputG)
+ (_.var "table.unpack")))
+ (_.var "string.char")))))]))
(def: utf8
Bundle
@@ -146,7 +146,7 @@
(do [! ////////phase.monad]
[abstractionG (phase archive abstractionS)
inputsG (monad.each ! (phase archive) inputsS)]
- (in (_.apply/* inputsG abstractionG))))]))
+ (in (_.apply inputsG abstractionG))))]))
(def: lua::power
(custom
@@ -177,11 +177,11 @@
(variable "input"))
(list.repeated (.nat arity) []))]
(in (<| (_.closure g!inputs)
- _.statement
+ _.return
(case (.nat arity)
- 0 (_.apply/1 abstractionG //runtime.unit)
- 1 (_.apply/* g!inputs abstractionG)
- _ (_.apply/1 abstractionG (_.array g!inputs)))))))]))
+ 0 (_.apply (list //runtime.unit) abstractionG)
+ 1 (_.apply g!inputs abstractionG)
+ _ (_.apply (list (_.array g!inputs)) abstractionG))))))]))
(def: .public bundle
Bundle
@@ -196,5 +196,5 @@
(/.install "power" lua::power)
(/.install "import" lua::import)
(/.install "function" lua::function)
- (/.install "script universe" (nullary (function.constant (_.bool reference.universe))))
+ (/.install "script universe" (nullary (function.constant (_.boolean reference.universe))))
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
index d4f994a5d..b28f5b5a7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
@@ -23,19 +23,13 @@
["[1][0]" value]
["[1][0]" structure]
[////
- ["[0]" synthesis {"+" Path Synthesis}]
+ ["[0]" synthesis {"+" Path Fork Synthesis}]
["[0]" generation]
[///
["[0]" phase ("operation#[0]" monad)]
[reference
[variable {"+" Register}]]]]])
-(def: equals_name
- "equals")
-
-(def: equals_type
- (type.method [(list) (list //type.value) type.boolean (list)]))
-
(def: (pop_alt stack_depth)
(-> Nat (Bytecode Any))
(.case stack_depth
@@ -55,10 +49,6 @@
(-> (I64 Any) (Bytecode Any))
(|>> .int _.long))
-(def: double
- (-> Frac (Bytecode Any))
- (|>> _.double))
-
(def: peek
(Bytecode Any)
($_ _.composite
@@ -90,178 +80,240 @@
(..int lefts)
//runtime.right_projection))
-(def: (path' stack_depth @else @end phase archive path)
- (-> Nat Label Label (Generator Path))
- (.case path
- {synthesis.#Pop}
- (operation#in ..pop)
-
- {synthesis.#Bind register}
- (operation#in ($_ _.composite
- ..peek
- (_.astore register)))
+(def: equals@Object
+ (.let [class (type.class "java.lang.Object" (list))
+ method (type.method [(list) (list //type.value) type.boolean (list)])]
+ (_.invokevirtual class "equals" method)))
- {synthesis.#Then bodyS}
- (do phase.monad
- [bodyG (phase archive bodyS)]
- (in ($_ _.composite
- (..pop_alt stack_depth)
- bodyG
- (_.goto @end))))
-
- (^template [<pattern> <right?>]
- [(^ (<pattern> lefts))
- (operation#in
- (do _.monad
- [@success _.new_label
- @fail _.new_label]
+(def: (path|bind register)
+ (-> Register (Operation (Bytecode Any)))
+ (operation#in ($_ _.composite
+ ..peek
+ (_.astore register))))
+
+(def: (path|bit_fork again @else [when thenP elseP])
+ (-> (-> Path (Operation (Bytecode Any)))
+ Label [Bit Path (Maybe Path)]
+ (Operation (Bytecode Any)))
+ (do phase.monad
+ [then! (again thenP)
+ else! (.case elseP
+ {.#Some elseP}
+ (again elseP)
+
+ {.#None}
+ (in (_.goto @else)))
+ .let [if! (.if when _.ifeq _.ifne)]]
+ (in (do _.monad
+ [@else _.new_label]
($_ _.composite
..peek
- (_.checkcast //type.variant)
- (//structure.lefts lefts <right?>)
- (//structure.right? <right?>)
- //runtime.case
- _.dup
- (_.ifnull @fail)
- (_.goto @success)
- (_.set_label @fail)
- _.pop
- (_.goto @else)
- (_.set_label @success)
- //runtime.push)))])
- ([synthesis.side/left false]
- [synthesis.side/right true])
+ (//value.unwrap type.boolean)
+ (if! @else)
+ then!
+ (_.set_label @else)
+ else!)))))
- (^template [<pattern> <projection>]
- [(^ (<pattern> lefts))
- (operation#in ($_ _.composite
- ..peek
- (<projection> lefts)
- //runtime.push))])
- ([synthesis.member/left ..left_projection]
- [synthesis.member/right ..right_projection])
+(template [<name> <type> <unwrap> <dup> <pop> <test> <comparison> <if>]
+ [(def: (<name> again @else cons)
+ (-> (-> Path (Operation (Bytecode Any)))
+ Label (Fork <type> Path)
+ (Operation (Bytecode Any)))
+ (do [! phase.monad]
+ [fork! (monad.mix ! (function (_ [test thenP] else!)
+ (do !
+ [then! (again thenP)]
+ (in (do _.monad
+ [@else _.new_label]
+ ($_ _.composite
+ <dup>
+ (<test> test)
+ <comparison>
+ (<if> @else)
+ <pop>
+ then!
+ (_.set_label @else)
+ else!)))))
+ ($_ _.composite
+ <pop>
+ (_.goto @else))
+ {.#Item cons})]
+ (in ($_ _.composite
+ ..peek
+ <unwrap>
+ fork!))))]
- ... Extra optimization
- (^ (synthesis.path/seq
- (synthesis.member/left 0)
- (synthesis.!bind_top register thenP)))
- (do phase.monad
- [thenG (path' stack_depth @else @end phase archive thenP)]
- (in ($_ _.composite
- ..peek
- (_.checkcast //type.tuple)
- _.iconst_0
- _.aaload
- (_.astore register)
- thenG)))
+ [path|i64_fork (I64 Any) (//value.unwrap type.long) _.dup2 _.pop2 ..long _.lcmp _.ifne]
+ [path|f64_fork Frac (//value.unwrap type.double) _.dup2 _.pop2 _.double _.dcmpl _.ifne]
+ [path|text_fork Text (# _.monad in []) _.dup _.pop _.string ..equals@Object _.ifeq]
+ )
+
+(def: (path' stack_depth @else @end phase archive)
+ (-> Nat Label Label (Generator Path))
+ (function (again path)
+ (.case path
+ {synthesis.#Pop}
+ (operation#in ..pop)
+
+ {synthesis.#Bind register}
+ (..path|bind register)
+
+ (^template [<tag> <path>]
+ [{<tag> it}
+ (<path> again @else it)])
+ ([synthesis.#Bit_Fork ..path|bit_fork]
+ [synthesis.#I64_Fork ..path|i64_fork]
+ [synthesis.#F64_Fork ..path|f64_fork]
+ [synthesis.#Text_Fork ..path|text_fork])
- ... Extra optimization
- (^template [<pm> <projection>]
- [(^ (synthesis.path/seq
- (<pm> lefts)
- (synthesis.!bind_top register thenP)))
- (do phase.monad
- [then! (path' stack_depth @else @end phase archive thenP)]
- (in ($_ _.composite
- ..peek
- (_.checkcast //type.tuple)
- (..int lefts)
- <projection>
- (_.astore register)
- then!)))])
- ([synthesis.member/left //runtime.left_projection]
- [synthesis.member/right //runtime.right_projection])
+ {synthesis.#Then bodyS}
+ (do phase.monad
+ [body! (phase archive bodyS)]
+ (in ($_ _.composite
+ (..pop_alt stack_depth)
+ body!
+ (_.when_continuous (_.goto @end)))))
+
+ (^template [<right?> <pattern>]
+ [(^ (<pattern> lefts))
+ (operation#in
+ (do _.monad
+ [@success _.new_label]
+ ($_ _.composite
+ ..peek
+ (_.checkcast //type.variant)
+ (//structure.lefts lefts)
+ (//structure.right? <right?>)
+ //runtime.case
+ _.dup
+ (_.ifnonnull @success)
+ _.pop
+ (_.goto @else)
+ (_.set_label @success)
+ //runtime.push)))])
+ ([#0 synthesis.side/left]
+ [#1 synthesis.side/right])
- {synthesis.#Alt leftP rightP}
- (do phase.monad
- [@alt_else //runtime.forge_label
- left! (path' (++ stack_depth) @alt_else @end phase archive leftP)
- right! (path' stack_depth @else @end phase archive rightP)]
- (in ($_ _.composite
- _.dup
- left!
- (_.set_label @alt_else)
- _.pop
- right!)))
-
- {synthesis.#Seq leftP rightP}
- (do phase.monad
- [left! (path' stack_depth @else @end phase archive leftP)
- right! (path' stack_depth @else @end phase archive rightP)]
- (in ($_ _.composite
- left!
- right!)))
+ (^template [<pattern> <projection>]
+ [(^ (<pattern> lefts))
+ (operation#in ($_ _.composite
+ ..peek
+ (<projection> lefts)
+ //runtime.push))
- _
- (undefined)
- ))
+ ... Extra optimization
+ (^ (synthesis.path/seq
+ (<pattern> lefts)
+ (synthesis.!bind_top register thenP)))
+ (do phase.monad
+ [then! (path' stack_depth @else @end phase archive thenP)]
+ (in ($_ _.composite
+ ..peek
+ (<projection> lefts)
+ (_.astore register)
+ then!)))])
+ ([synthesis.member/left ..left_projection]
+ [synthesis.member/right ..right_projection])
+
+ {synthesis.#Seq leftP rightP}
+ (do phase.monad
+ [left! (path' stack_depth @else @end phase archive leftP)
+ right! (path' stack_depth @else @end phase archive rightP)]
+ (in ($_ _.composite
+ left!
+ right!)))
+
+ {synthesis.#Alt leftP rightP}
+ (do phase.monad
+ [@alt_else //runtime.forge_label
+ left! (path' (++ stack_depth) @alt_else @end phase archive leftP)
+ right! (path' stack_depth @else @end phase archive rightP)]
+ (in ($_ _.composite
+ _.dup
+ left!
+ (_.set_label @alt_else)
+ _.pop
+ right!)))
+ )))
(def: (path @end phase archive path)
(-> Label (Generator Path))
(do phase.monad
[@else //runtime.forge_label
- pathG (..path' 1 @else @end phase archive path)]
+ path! (..path' 1 @else @end phase archive path)]
(in ($_ _.composite
- pathG
- (_.set_label @else)
- _.pop
- //runtime.pm_failure
- _.aconst_null
- (_.goto @end)))))
+ path!
+ (do _.monad
+ [?@else (_.acknowledged? @else)]
+ (.case ?@else
+ {.#None}
+ (in [])
+
+ {.#Some _}
+ ($_ _.composite
+ (_.set_label @else)
+ _.pop ... TODO: Comment this line
+ //runtime.pm_failure
+ _.aconst_null ... TODO: Comment this line
+ (_.goto @end)
+ )))
+ ))))
-(def: .public (if phase archive [conditionS thenS elseS])
+(def: .public (if phase archive [testS thenS elseS])
(Generator [Synthesis Synthesis Synthesis])
(do phase.monad
- [conditionG (phase archive conditionS)
- thenG (phase archive thenS)
- elseG (phase archive elseS)]
+ [test! (phase archive testS)
+ then! (phase archive thenS)
+ else! (phase archive elseS)]
(in (do _.monad
[@else _.new_label
@end _.new_label]
($_ _.composite
- conditionG
+ test!
(//value.unwrap type.boolean)
(_.ifeq @else)
- thenG
- (_.goto @end)
+ then!
+ (_.when_continuous (_.goto @end))
(_.set_label @else)
- elseG
+ else!
(_.set_label @end))))))
(def: .public (let phase archive [inputS register bodyS])
(Generator [Synthesis Register Synthesis])
(do phase.monad
- [inputG (phase archive inputS)
- bodyG (phase archive bodyS)]
+ [input! (phase archive inputS)
+ body! (phase archive bodyS)]
(in ($_ _.composite
- inputG
+ input!
(_.astore register)
- bodyG))))
+ body!))))
(def: .public (get phase archive [path recordS])
(Generator [(List synthesis.Member) Synthesis])
(do phase.monad
- [recordG (phase archive recordS)]
- (in (list#mix (function (_ step so_far)
- (.let [next (.case step
- {.#Left lefts}
- (..left_projection lefts)
-
- {.#Right lefts}
- (..right_projection lefts))]
- (_.composite so_far next)))
- recordG
+ [record! (phase archive recordS)]
+ (in (list#mix (function (_ step so_far!)
+ (.let [next! (.case step
+ {.#Left lefts}
+ (..left_projection lefts)
+
+ {.#Right lefts}
+ (..right_projection lefts))]
+ ($_ _.composite
+ so_far!
+ next!)))
+ record!
(list.reversed path)))))
(def: .public (case phase archive [valueS path])
(Generator [Synthesis Path])
(do phase.monad
[@end //runtime.forge_label
- valueG (phase archive valueS)
- pathG (..path @end phase archive path)]
+ value! (phase archive valueS)
+ path! (..path @end phase archive path)]
(in ($_ _.composite
_.aconst_null
- valueG
+ value!
//runtime.push
- pathG
+ path!
(_.set_label @end)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
index 050ca318a..a7f0d7ac6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
@@ -149,7 +149,7 @@
current_partials
(..inputs ..this_offset apply_arity)
missing_partials
- (_.invokevirtual class //init.name (//init.type environment function_arity))
+ (_.invokespecial class //init.name (//init.type environment function_arity))
_.areturn)))))))
(monad.all _.monad))]]
($_ _.composite
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
index 664e0fbc8..6c8a9ee75 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
@@ -35,7 +35,7 @@
{.#Some ($_ _.composite
(_.set_label @begin)
body
- _.areturn
+ (_.when_continuous _.areturn)
)}))
(def: .public method
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
index cf9f6b02e..5a1ec9ea6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
@@ -55,8 +55,8 @@
_ (_.anewarray $Object)]
(monad.all ! membersI))))))
-(def: .public (lefts lefts right?)
- (-> Nat Bit (Bytecode Any))
+(def: .public (lefts lefts)
+ (-> Nat (Bytecode Any))
(case lefts
0 _.iconst_0
1 _.iconst_1
@@ -87,7 +87,7 @@
(do phase.monad
[valueI (phase archive valueS)]
(in (do _.monad
- [_ (..lefts lefts right?)
+ [_ (..lefts lefts)
_ (..right? right?)
_ valueI]
(_.invokestatic //runtime.class "variant"
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 3afa582f0..16c8d5c19 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -1,34 +1,34 @@
(.using
- [library
- [lux {"-" case let if}
- [abstract
- ["[0]" monad {"+" do}]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]
- ["[0]" set]]]
- [target
- ["_" lua {"+" Expression Var Statement}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}]
+ [library
+ [lux {"-" case let if}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]
+ ["[0]" set]]]
+ [target
+ ["_" lua {"+" Expression Var Statement}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}]
+ ["[1][0]" reference]
+ ["[1][0]" primitive]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" primitive]
["/[1]" // "_"
- ["[1][0]" reference]
+ ["[1][0]" synthesis "_"
+ ["[1]/[0]" case]]
["/[1]" // "_"
- ["[1][0]" synthesis "_"
- ["[1]/[0]" case]]
- ["/[1]" // "_"
- ["[1][0]" synthesis {"+" Member Synthesis Path}]
- ["[1][0]" generation]
- ["//[1]" /// "_"
- [reference
- ["[1][0]" variable {"+" Register}]]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [meta
- [archive {"+" Archive}]]]]]]])
+ ["[1][0]" synthesis {"+" Member Synthesis Path}]
+ ["[1][0]" generation]
+ ["//[1]" /// "_"
+ [reference
+ ["[1][0]" variable {"+" Register}]]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [meta
+ [archive {"+" Archive}]]]]]]])
(def: .public register
(-> Register Var)
@@ -47,7 +47,7 @@
(in (|> bodyO
_.return
(_.closure (list (..register register)))
- (_.apply/* (list valueO))))))
+ (_.apply (list valueO))))))
(def: .public (let! statement expression archive [valueS register bodyS])
(Generator! [Synthesis Register Synthesis])
@@ -83,7 +83,7 @@
(_.return thenO)
(_.return elseO))
(_.closure (list))
- (_.apply/* (list))))))
+ (_.apply (list))))))
(def: .public (if! statement expression archive [testS thenS elseS])
(Generator! [Synthesis Synthesis Synthesis])
@@ -101,11 +101,11 @@
(def: (push! value)
(-> Expression Statement)
- (_.statement (|> (_.var "table.insert") (_.apply/* (list @cursor value)))))
+ (_.statement (|> (_.var "table.insert") (_.apply (list @cursor value)))))
(def: peek_and_pop
Expression
- (|> (_.var "table.remove") (_.apply/* (list @cursor))))
+ (|> (_.var "table.remove") (_.apply (list @cursor))))
(def: pop!
Statement
@@ -118,17 +118,17 @@
(def: save!
Statement
(_.statement (|> (_.var "table.insert")
- (_.apply/* (list @savepoint
- (_.apply/* (list @cursor
- (_.int +1)
- (_.length @cursor)
- (_.int +1)
- (_.table (list)))
- (_.var "table.move")))))))
+ (_.apply (list @savepoint
+ (_.apply (list @cursor
+ (_.int +1)
+ (_.length @cursor)
+ (_.int +1)
+ (_.table (list)))
+ (_.var "table.move")))))))
(def: restore!
Statement
- (_.set (list @cursor) (|> (_.var "table.remove") (_.apply/* (list @savepoint)))))
+ (_.set (list @cursor) (|> (_.var "table.remove") (_.apply (list @savepoint)))))
(def: fail! _.break)
@@ -152,7 +152,7 @@
(def: (alternation pre! post!)
(-> Statement Statement Statement)
($_ _.then
- (_.while (_.bool true)
+ (_.while (_.boolean true)
($_ _.then
..save!
pre!))
@@ -200,7 +200,10 @@
..peek)
then!])))
{.#Item item})]
- (in (_.cond clauses ..fail!)))])
+ (in (list#mix (function (_ [when then!] else!)
+ (_.if when then! else!))
+ ..fail!
+ clauses)))])
([/////synthesis.#I64_Fork (<| _.int .int)]
[/////synthesis.#F64_Fork _.float]
[/////synthesis.#Text_Fork _.string])
@@ -244,9 +247,9 @@
(do ///////phase.monad
[pattern_matching! (pattern_matching' statement expression archive pathP)]
(in ($_ _.then
- (_.while (_.bool true)
+ (_.while (_.boolean true)
pattern_matching!)
- (_.statement (|> (_.var "error") (_.apply/* (list (_.string ////synthesis/case.pattern_matching_error)))))))))
+ (_.statement (|> (_.var "error") (_.apply (list (_.string ////synthesis/case.pattern_matching_error)))))))))
(def: .public dependencies
(-> Path (List Var))
@@ -278,4 +281,4 @@
(..case! statement expression archive)
(# ///////phase.monad each
(|>> (_.closure (list))
- (_.apply/* (list))))))
+ (_.apply (list))))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index 649692ccc..5ce1e0b7a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -1,43 +1,43 @@
(.using
- [library
- [lux {"-" Tuple Variant Label function}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- pipe]
- [data
- ["[0]" product]
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [target
- ["_" lua {"+" Var Expression Label Statement}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Phase! Generator}]
+ [library
+ [lux {"-" Tuple Variant Label function}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ pipe]
+ [data
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [target
+ ["_" lua {"+" Var Expression Label Statement}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Phase! Generator}]
+ ["[1][0]" reference]
+ ["[1][0]" case]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" case]
- ["/[1]" // "_"
- ["[1][0]" reference]
+ ["//[1]" /// "_"
+ [analysis {"+" Variant Tuple Abstraction Application Analysis}]
+ [synthesis {"+" Synthesis}]
+ ["[1][0]" generation {"+" Context}]
["//[1]" /// "_"
- [analysis {"+" Variant Tuple Abstraction Application Analysis}]
- [synthesis {"+" Synthesis}]
- ["[1][0]" generation {"+" Context}]
- ["//[1]" /// "_"
- [arity {"+" Arity}]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [meta
- [archive
- ["[0]" dependency]]]
- [reference
- [variable {"+" Register Variable}]]]]]])
+ [arity {"+" Arity}]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [meta
+ [archive
+ ["[0]" dependency]]]
+ [reference
+ [variable {"+" Register Variable}]]]]]])
(def: .public (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
(do [! ///////phase.monad]
[functionO (expression archive functionS)
argsO+ (monad.each ! (expression archive) argsS+)]
- (in (_.apply/* argsO+ functionO))))
+ (in (_.apply argsO+ functionO))))
(def: capture
(-> Register Var)
@@ -57,7 +57,7 @@
($_ _.then
(_.local_function @self @args body!)
(_.return @self)))
- (_.apply/* inits @self)])))
+ (_.apply inits @self)])))
(def: input
(|>> ++ //case.register))
@@ -90,51 +90,52 @@
initialize_self!
(list.indices arity))
pack (|>> (list) _.array)
- unpack (_.apply/1 (_.var "table.unpack"))
+ unpack (: (-> Expression Expression)
+ (.function (_ it)
+ (_.apply (list it) (_.var "table.unpack"))))
@var_args (_.var "...")]
.let [[definition instantiation] (with_closure closureO+ @self (list @var_args)
($_ _.then
(_.local/1 @curried (pack @var_args))
(_.local/1 @num_args (_.length @curried))
- (_.cond (list [(|> @num_args (_.= arityO))
- ($_ _.then
- initialize!
- (_.set_label @scope)
- body!)]
- [(|> @num_args (_.> arityO))
- (let [arity_inputs (_.apply/5 (_.var "table.move")
- @curried
- (_.int +1)
- arityO
- (_.int +1)
- (_.array (list)))
- extra_inputs (_.apply/5 (_.var "table.move")
- @curried
- (_.+ (_.int +1) arityO)
- @num_args
- (_.int +1)
- (_.array (list)))]
- (_.return (|> @self
- (_.apply/* (list (unpack arity_inputs)))
- (_.apply/* (list (unpack extra_inputs))))))])
- ... (|> @num_args (_.< arityO))
- (_.return (_.closure (list @var_args)
- (let [@extra_args (_.var "extra_args")]
- ($_ _.then
- (_.local/1 @extra_args (pack @var_args))
- (_.return (|> (_.array (list))
- (_.apply/5 (_.var "table.move")
- @curried
- (_.int +1)
- @num_args
- (_.int +1))
- (_.apply/5 (_.var "table.move")
- @extra_args
- (_.int +1)
- (_.length @extra_args)
- (_.+ (_.int +1) @num_args))
- unpack
- (_.apply/1 @self))))))))
+ (<| (_.if (|> @num_args (_.= arityO))
+ ($_ _.then
+ initialize!
+ (_.set_label @scope)
+ body!))
+ (_.if (|> @num_args (_.> arityO))
+ (let [arity_inputs (_.apply (list @curried
+ (_.int +1)
+ arityO
+ (_.int +1)
+ (_.array (list)))
+ (_.var "table.move"))
+ extra_inputs (_.apply (list @curried
+ (_.+ (_.int +1) arityO)
+ @num_args
+ (_.int +1)
+ (_.array (list)))
+ (_.var "table.move"))]
+ (_.return (|> @self
+ (_.apply (list (unpack arity_inputs)))
+ (_.apply (list (unpack extra_inputs)))))))
+ ... (|> @num_args (_.< arityO))
+ (_.return (_.closure (list @var_args)
+ (let [@extra_args (_.var "extra_args")]
+ ($_ _.then
+ (_.local/1 @extra_args (pack @var_args))
+ (_.return (_.apply (list (unpack (_.apply (list @extra_args
+ (_.int +1)
+ (_.length @extra_args)
+ (_.+ (_.int +1) @num_args)
+ (_.apply (list @curried
+ (_.int +1)
+ @num_args
+ (_.int +1)
+ (_.array (list)))
+ (_.var "table.move")))
+ (_.var "table.move"))))
+ @self)))))))
))]
_ (/////generation.execute! definition)
_ (/////generation.save! (product.right function_name) {.#None} definition)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
index c58a5d476..06135b240 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
@@ -108,10 +108,10 @@
scope!)
(_.return @loop)
))
- (|> @context (_.apply/* foreigns))])))]
+ (_.apply foreigns @context)])))]
_ (/////generation.execute! directive)
_ (/////generation.save! artifact_id {.#None} directive)]
- (in (|> instantiation (_.apply/* initsO+))))))
+ (in (_.apply initsO+ instantiation)))))
(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux
index 3c879b684..556371e6a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux
@@ -9,7 +9,7 @@
(-> <type> Literal)
<implementation>)]
- [bit Bit _.bool]
+ [bit Bit _.boolean]
[i64 (I64 Any) (|>> .int _.int)]
[f64 Frac _.float]
[text Text _.string]
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 f20a6cb12..40525dd00 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
@@ -1,42 +1,42 @@
(.using
- [library
- [lux {"-" Label Location}
- ["[0]" meta]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["<>" parser
- ["<[0]>" code]]]
- [data
- ["[0]" product]
- ["[0]" text ("[1]#[0]" hash)
- ["%" format {"+" format}]
- [encoding
- ["[0]" utf8]]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]
- ["[0]" sequence]]]
- ["[0]" macro
- [syntax {"+" syntax:}]
- ["[0]" code]]
- [math
- [number {"+" hex}
- ["[0]" i64]]]
- ["@" target
- ["_" lua {"+" Expression Location Var Computation Literal Label Statement}]]]]
- ["[0]" /// "_"
- ["[1][0]" reference]
- ["//[1]" /// "_"
- ["[1][0]" synthesis {"+" Synthesis}]
- ["[1][0]" generation]
- ["//[1]" ///
- ["[1][0]" phase]
- [reference
- [variable {"+" Register}]]
- [meta
- [archive {"+" Output Archive}
- ["[0]" artifact {"+" Registry}]]]]]])
+ [library
+ [lux {"-" Label Location}
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["<>" parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" product]
+ ["[0]" text ("[1]#[0]" hash)
+ ["%" format {"+" format}]
+ [encoding
+ ["[0]" utf8]]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]
+ ["[0]" sequence]]]
+ ["[0]" macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]
+ [math
+ [number {"+" hex}
+ ["[0]" i64]]]
+ ["@" target
+ ["_" lua {"+" Expression Location Var Computation Literal Label Statement}]]]]
+ ["[0]" /// "_"
+ ["[1][0]" reference]
+ ["//[1]" /// "_"
+ ["[1][0]" synthesis {"+" Synthesis}]
+ ["[1][0]" generation]
+ ["//[1]" ///
+ ["[1][0]" phase]
+ [reference
+ [variable {"+" Register}]]
+ [meta
+ [archive {"+" Output Archive}
+ ["[0]" artifact {"+" Registry}]]]]]])
(template [<name> <base>]
[(type: .public <name>
@@ -148,7 +148,7 @@
inputs)]
(in (list (` (def: .public ((~ g!name) (~+ inputsC))
(-> (~+ inputs_typesC) Computation)
- (_.apply/* (list (~+ inputsC)) (~ runtime_name))))
+ (_.apply (list (~+ inputsC)) (~ runtime_name))))
(` (def: (~ (code.local_symbol (format "@" name)))
Statement
@@ -170,7 +170,7 @@
(_.set (list tuple) (..item last_index_right tuple))))]
(runtime: (tuple//left lefts tuple)
(with_vars [last_index_right]
- (<| (_.while (_.bool true))
+ (<| (_.while (_.boolean true))
($_ _.then
(_.local/1 last_index_right (..last_index tuple))
(_.if (_.> lefts last_index_right)
@@ -181,21 +181,21 @@
(runtime: (tuple//right lefts tuple)
(with_vars [last_index_right right_index]
- (<| (_.while (_.bool true))
+ (<| (_.while (_.boolean true))
($_ _.then
(_.local/1 last_index_right (..last_index tuple))
(_.local/1 right_index (_.+ (_.int +1) lefts))
- (_.cond (list [(_.= last_index_right right_index)
- (_.return (..item right_index tuple))]
- [(_.> last_index_right right_index)
- ... Needs recursion.
- <recur>])
- (_.return (_.apply/* (list tuple
- (_.+ (_.int +1) right_index)
- (_.length tuple)
- (_.int +1)
- (_.array (list)))
- (_.var "table.move"))))
+ (<| (_.if (_.= last_index_right right_index)
+ (_.return (..item right_index tuple)))
+ (_.if (_.> last_index_right right_index)
+ ... Needs recursion.
+ <recur>)
+ (_.return (_.apply (list tuple
+ (_.+ (_.int +1) right_index)
+ (_.length tuple)
+ (_.int +1)
+ (_.array (list)))
+ (_.var "table.move"))))
)))))
(runtime: (sum//get sum expected##right? expected##lefts)
@@ -208,24 +208,22 @@
(_.- actual##lefts)
(_.- (_.int +1))))
(_.set (list sum) actual##value))]
- (<| (_.while (_.bool true))
- (_.cond (list [(_.= expected##lefts actual##lefts)
- (_.if (_.= expected##right? actual##right?)
- (_.return actual##value)
- mismatch!)]
-
- [(_.< expected##lefts actual##lefts)
- (_.if (_.= ..unit actual##right?)
- recur!
- mismatch!)]
-
- [(_.= ..unit expected##right?)
- (_.return (variant' (|> actual##lefts
- (_.- expected##lefts)
- (_.- (_.int +1)))
- actual##right?
- actual##value))])
- mismatch!))))
+ (<| (_.while (_.boolean true))
+ (_.if (_.= expected##lefts actual##lefts)
+ (_.if (_.= expected##right? actual##right?)
+ (_.return actual##value)
+ mismatch!))
+ (_.if (_.< expected##lefts actual##lefts)
+ (_.if (_.= ..unit actual##right?)
+ recur!
+ mismatch!))
+ (_.if (_.= ..unit expected##right?)
+ (_.return (variant' (|> actual##lefts
+ (_.- expected##lefts)
+ (_.- (_.int +1)))
+ actual##right?
+ actual##value)))
+ mismatch!)))
(def: runtime//adt
Statement
@@ -238,9 +236,9 @@
(runtime: (lux//try risky)
(with_vars [success value]
($_ _.then
- (_.let (list success value) (|> risky (_.apply/* (list ..unit))
+ (_.let (list success value) (|> risky (_.apply (list ..unit))
_.return (_.closure (list))
- list _.apply/* (|> (_.var "pcall"))))
+ list _.apply (|> (_.var "pcall"))))
(_.if success
(_.return (..right value))
(_.return (..left value))))))
@@ -306,18 +304,17 @@
(def: (find_byte_index subject param start)
(-> Expression Expression Expression Expression)
- (_.apply/4 (_.var "string.find") subject param start (_.bool #1)))
+ (_.apply (list subject param start (_.boolean #1))
+ (_.var "string.find")))
(def: (char_index subject byte_index)
(-> Expression Expression Expression)
- (|> byte_index
- (_.apply/3 (_.var "utf8.len") subject (_.int +1))))
+ (_.apply (list subject (_.int +1) byte_index)
+ (_.var "utf8.len")))
(def: (byte_index subject char_index)
(-> Expression Expression Expression)
- (|> char_index
- (_.+ (_.int +1))
- (_.apply/2 (_.var "utf8.offset") subject)))
+ (_.apply (list subject (_.+ (_.int +1) char_index)) (_.var "utf8.offset")))
(def: lux_index
(-> Expression Expression)
@@ -352,22 +349,23 @@
<normal>)))))
(runtime: (text//clip text offset length)
- (with_expansions [<rembulan> (_.return (_.apply/3 (_.var "string.sub") text (_.+ (_.int +1) offset) (_.+ offset length)))
- <normal> (_.return (_.apply/3 (_.var "string.sub")
- text
- (..byte_index text offset)
- (|> (_.+ offset length)
- ... (_.+ (_.int +1))
- (..byte_index text)
- (_.- (_.int +1)))))]
+ (with_expansions [<rembulan> (_.return (_.apply (list text (_.+ (_.int +1) offset) (_.+ offset length))
+ (_.var "string.sub")))
+ <normal> (_.return (_.apply (list text
+ (..byte_index text offset)
+ (|> (_.+ offset length)
+ ... (_.+ (_.int +1))
+ (..byte_index text)
+ (_.- (_.int +1))))
+ (_.var "string.sub")))]
(for [@.lua <normal>]
(_.if ..on_rembulan?
<rembulan>
<normal>))))
(runtime: (text//size subject)
- (with_expansions [<rembulan> (_.return (_.apply/1 (_.var "string.len") subject))
- <normal> (_.return (_.apply/1 (_.var "utf8.len") subject))]
+ (with_expansions [<rembulan> (_.return (_.apply (list subject) (_.var "string.len")))
+ <normal> (_.return (_.apply (list subject) (_.var "utf8.len")))]
(for [@.lua <normal>]
(_.if ..on_rembulan?
<rembulan>
@@ -376,17 +374,17 @@
(runtime: (text//char idx text)
(with_expansions [<rembulan> (with_vars [char]
($_ _.then
- (_.local/1 char (_.apply/* (list text idx)
- (_.var "string.byte")))
+ (_.local/1 char (_.apply (list text idx)
+ (_.var "string.byte")))
(_.if (_.= _.nil char)
(_.statement (_.error/1 (_.string "[Lux Error] Cannot get char from text.")))
(_.return char))))
<normal> (with_vars [offset char]
($_ _.then
- (_.local/1 offset (_.apply/2 (_.var "utf8.offset") text idx))
+ (_.local/1 offset (_.apply (list text idx) (_.var "utf8.offset")))
(_.if (_.= _.nil offset)
(_.statement (_.error/1 (_.string "[Lux Error] Cannot get char from text.")))
- (_.return (_.apply/2 (_.var "utf8.codepoint") text offset)))))]
+ (_.return (_.apply (list text offset) (_.var "utf8.codepoint"))))))]
(for [@.lua <normal>]
(_.if ..on_rembulan?
<rembulan>