aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2021-02-10 19:04:18 -0400
committerEduardo Julian2021-02-10 19:04:18 -0400
commita5e2f99430384fff580646a553b1e8ae27e07acd (patch)
tree185681c6b41cec359a20cbb094e33048cbec921b /stdlib/source/lux/tool
parentd99c47989a1047cd24019fd5ce434e701b5d3519 (diff)
Continuing with Lua
Diffstat (limited to 'stdlib/source/lux/tool')
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux5
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux217
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux9
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux49
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux197
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux7
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux29
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux26
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux17
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux7
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux72
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux83
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux113
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux76
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux66
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/syntax.lux2
18 files changed, 738 insertions, 245 deletions
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
index b15f22be5..860badea3 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
@@ -207,10 +207,11 @@
Bundle
(<| (bundle.prefix "js")
(|> bundle.empty
+ (dictionary.merge bundle::array)
+ (dictionary.merge bundle::object)
+
(bundle.install "constant" js::constant)
(bundle.install "apply" js::apply)
(bundle.install "type-of" js::type_of)
(bundle.install "function" js::function)
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
index b431dc39b..596000060 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
@@ -27,8 +27,225 @@
[///
["." phase]]]]]])
+(def: Nil
+ (for {@.lua
+ host.Nil}
+ Any))
+
+(def: Object
+ (for {@.lua (type (host.Object Any))}
+ Any))
+
+(def: Function
+ (for {@.lua host.Function}
+ Any))
+
+(def: array::new
+ Handler
+ (custom
+ [<c>.any
+ (function (_ extension phase archive lengthC)
+ (do phase.monad
+ [lengthA (analysis/type.with_type Nat
+ (phase archive lengthC))
+ [var_id varT] (analysis/type.with_env check.var)
+ _ (analysis/type.infer (type (Array varT)))]
+ (wrap (#analysis.Extension extension (list lengthA)))))]))
+
+(def: array::length
+ Handler
+ (custom
+ [<c>.any
+ (function (_ extension phase archive arrayC)
+ (do phase.monad
+ [[var_id varT] (analysis/type.with_env check.var)
+ arrayA (analysis/type.with_type (type (Array varT))
+ (phase archive arrayC))
+ _ (analysis/type.infer Nat)]
+ (wrap (#analysis.Extension extension (list arrayA)))))]))
+
+(def: array::read
+ Handler
+ (custom
+ [(<>.and <c>.any <c>.any)
+ (function (_ extension phase archive [indexC arrayC])
+ (do phase.monad
+ [indexA (analysis/type.with_type Nat
+ (phase archive indexC))
+ [var_id varT] (analysis/type.with_env check.var)
+ arrayA (analysis/type.with_type (type (Array varT))
+ (phase archive arrayC))
+ _ (analysis/type.infer varT)]
+ (wrap (#analysis.Extension extension (list indexA arrayA)))))]))
+
+(def: array::write
+ Handler
+ (custom
+ [($_ <>.and <c>.any <c>.any <c>.any)
+ (function (_ extension phase archive [indexC valueC arrayC])
+ (do phase.monad
+ [indexA (analysis/type.with_type Nat
+ (phase archive indexC))
+ [var_id varT] (analysis/type.with_env check.var)
+ valueA (analysis/type.with_type varT
+ (phase archive valueC))
+ arrayA (analysis/type.with_type (type (Array varT))
+ (phase archive arrayC))
+ _ (analysis/type.infer (type (Array varT)))]
+ (wrap (#analysis.Extension extension (list indexA valueA arrayA)))))]))
+
+(def: array::delete
+ Handler
+ (custom
+ [($_ <>.and <c>.any <c>.any)
+ (function (_ extension phase archive [indexC arrayC])
+ (do phase.monad
+ [indexA (analysis/type.with_type Nat
+ (phase archive indexC))
+ [var_id varT] (analysis/type.with_env check.var)
+ arrayA (analysis/type.with_type (type (Array varT))
+ (phase archive arrayC))
+ _ (analysis/type.infer (type (Array varT)))]
+ (wrap (#analysis.Extension extension (list indexA arrayA)))))]))
+
+(def: bundle::array
+ Bundle
+ (<| (bundle.prefix "array")
+ (|> bundle.empty
+ (bundle.install "new" array::new)
+ (bundle.install "length" array::length)
+ (bundle.install "read" array::read)
+ (bundle.install "write" array::write)
+ (bundle.install "delete" array::delete)
+ )))
+
+(def: object::get
+ Handler
+ (custom
+ [($_ <>.and <c>.text <c>.any)
+ (function (_ extension phase archive [fieldC objectC])
+ (do phase.monad
+ [objectA (analysis/type.with_type ..Object
+ (phase archive objectC))
+ _ (analysis/type.infer .Any)]
+ (wrap (#analysis.Extension extension (list (analysis.text fieldC)
+ objectA)))))]))
+
+(def: object::do
+ Handler
+ (custom
+ [($_ <>.and <c>.text <c>.any (<>.some <c>.any))
+ (function (_ extension phase archive [methodC objectC inputsC])
+ (do {! phase.monad}
+ [objectA (analysis/type.with_type ..Object
+ (phase archive objectC))
+ inputsA (monad.map ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC)
+ _ (analysis/type.infer .Any)]
+ (wrap (#analysis.Extension extension (list& (analysis.text methodC)
+ objectA
+ inputsA)))))]))
+
+(def: bundle::object
+ Bundle
+ (<| (bundle.prefix "object")
+ (|> bundle.empty
+ (bundle.install "get" object::get)
+ (bundle.install "do" object::do)
+ (bundle.install "nil" (/.nullary ..Nil))
+ (bundle.install "nil?" (/.unary Any Bit))
+ )))
+
+(template [<name> <fromT> <toT>]
+ [(def: <name>
+ Handler
+ (custom
+ [<c>.any
+ (function (_ extension phase archive inputC)
+ (do {! phase.monad}
+ [inputA (analysis/type.with_type (type <fromT>)
+ (phase archive inputC))
+ _ (analysis/type.infer (type <toT>))]
+ (wrap (#analysis.Extension extension (list inputA)))))]))]
+
+ [utf8::encode Text (array.Array (I64 Any))]
+ [utf8::decode (array.Array (I64 Any)) Text]
+ )
+
+(def: bundle::utf8
+ Bundle
+ (<| (bundle.prefix "utf8")
+ (|> bundle.empty
+ (bundle.install "encode" utf8::encode)
+ (bundle.install "decode" utf8::decode)
+ )))
+
+(def: lua::constant
+ Handler
+ (custom
+ [<c>.text
+ (function (_ extension phase archive name)
+ (do phase.monad
+ [_ (analysis/type.infer Any)]
+ (wrap (#analysis.Extension extension (list (analysis.text name))))))]))
+
+(def: lua::apply
+ Handler
+ (custom
+ [($_ <>.and <c>.any (<>.some <c>.any))
+ (function (_ extension phase archive [abstractionC inputsC])
+ (do {! phase.monad}
+ [abstractionA (analysis/type.with_type ..Function
+ (phase archive abstractionC))
+ inputsA (monad.map ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC)
+ _ (analysis/type.infer Any)]
+ (wrap (#analysis.Extension extension (list& abstractionA inputsA)))))]))
+
+(def: lua::power
+ Handler
+ (custom
+ [($_ <>.and <c>.any <c>.any)
+ (function (_ extension phase archive [powerC baseC])
+ (do {! phase.monad}
+ [powerA (analysis/type.with_type Frac
+ (phase archive powerC))
+ baseA (analysis/type.with_type Frac
+ (phase archive baseC))
+ _ (analysis/type.infer Frac)]
+ (wrap (#analysis.Extension extension (list powerA baseA)))))]))
+
+(def: lua::import
+ Handler
+ (custom
+ [<c>.text
+ (function (_ extension phase archive name)
+ (do phase.monad
+ [_ (analysis/type.infer ..Object)]
+ (wrap (#analysis.Extension extension (list (analysis.text name))))))]))
+
+(def: python::function
+ Handler
+ (custom
+ [($_ <>.and <c>.nat <c>.any)
+ (function (_ extension phase archive [arity abstractionC])
+ (do phase.monad
+ [#let [inputT (type.tuple (list.repeat arity Any))]
+ abstractionA (analysis/type.with_type (-> inputT Any)
+ (phase archive abstractionC))
+ _ (analysis/type.infer ..Function)]
+ (wrap (#analysis.Extension extension (list (analysis.nat arity)
+ abstractionA)))))]))
+
(def: #export bundle
Bundle
(<| (bundle.prefix "lua")
(|> bundle.empty
+ (dictionary.merge bundle::array)
+ (dictionary.merge bundle::object)
+ (dictionary.merge bundle::utf8)
+
+ (bundle.install "constant" lua::constant)
+ (bundle.install "apply" lua::apply)
+ (bundle.install "power" lua::power)
+ (bundle.install "import" lua::import)
+ (bundle.install "function" python::function)
)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
index c81705f24..45fb3e5d2 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
@@ -114,9 +114,7 @@
(custom
[<s>.text
(function (_ extension phase archive name)
- (do ////////phase.monad
- []
- (wrap (_.var name))))]))
+ (\ ////////phase.monad wrap (_.var name)))]))
(def: js::apply
(custom
@@ -151,10 +149,11 @@
Bundle
(<| (/.prefix "js")
(|> /.empty
+ (dictionary.merge ..array)
+ (dictionary.merge ..object)
+
(/.install "constant" js::constant)
(/.install "apply" js::apply)
(/.install "type-of" (unary _.type_of))
(/.install "function" js::function)
- (dictionary.merge ..array)
- (dictionary.merge ..object)
)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
index b64cf2427..ab0d0d555 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
@@ -5,6 +5,7 @@
["." dictionary]]]]
["." / #_
["#." common]
+ ["#." host]
[////
[generation
[lua
@@ -12,4 +13,5 @@
(def: #export bundle
Bundle
- /common.bundle)
+ (dictionary.merge /common.bundle
+ /host.bundle))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index 7d7ce2fbf..e619e76f8 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -3,24 +3,49 @@
[abstract
["." monad (#+ do)]]
[control
- ["." function]]
+ ["." function]
+ ["." try]
+ ["<>" parser
+ ["<s>" synthesis (#+ Parser)]]]
[data
["." product]
+ ["." text
+ ["%" format (#+ format)]]
[collection
- ["." dictionary]]]
+ ["." dictionary]
+ ["." list ("#\." functor fold)]]]
[math
[number
["f" frac]]]
[target
- ["_" lua (#+ Expression Literal)]]]
- [////
+ ["_" lua (#+ Expression)]]]
+ ["." //// #_
["/" bundle]
- [//
+ ["/#" // #_
+ ["." extension]
[generation
[extension (#+ Nullary Unary Binary Trinary
nullary unary binary trinary)]
["//" lua #_
- ["#." runtime (#+ Operation Phase Handler Bundle)]]]]])
+ ["#." runtime (#+ Operation Phase Handler Bundle Generator)]]]
+ [//
+ [synthesis (#+ %synthesis)]
+ ["." generation]
+ [///
+ ["#" phase]]]]])
+
+(def: #export (custom [parser handler])
+ (All [s]
+ (-> [(Parser s)
+ (-> Text (Generator s))]
+ Handler))
+ (function (_ extension_name phase archive input)
+ (case (<s>.run parser input)
+ (#try.Success input')
+ (handler extension_name phase archive input')
+
+ (#try.Failure error)
+ (/////.throw extension.invalid_syntax [extension_name %synthesis input]))))
(template: (!unary function)
(|>> list _.apply/* (|> (_.var function))))
@@ -70,9 +95,9 @@
(/.install "encode" (unary (!unary "tostring")))
(/.install "decode" (unary ..f64//decode)))))
-(def: (text//char [subjectO paramO])
+(def: (text//char [paramO subjectO])
(Binary Expression)
- (//runtime.text//char subjectO paramO))
+ (//runtime.text//char (_.+ (_.int +1) paramO) subjectO))
(def: (text//clip [paramO extraO subjectO])
(Trinary Expression)
@@ -80,7 +105,7 @@
(def: (text//index [startO partO textO])
(Trinary Expression)
- (//runtime.text//index textO partO startO))
+ (//runtime.text//index textO partO (_.+ (_.int +1) startO)))
(def: text_procs
Bundle
@@ -89,10 +114,10 @@
(/.install "=" (binary (product.uncurry _.=)))
(/.install "<" (binary (product.uncurry _.<)))
(/.install "concat" (binary (product.uncurry (function.flip _.concat))))
- (/.install "index" (trinary text//index))
+ (/.install "index" (trinary ..text//index))
(/.install "size" (unary (|>> list _.apply/* (|> (_.var "string.len")))))
- (/.install "char" (binary (product.uncurry //runtime.text//char)))
- (/.install "clip" (trinary text//clip))
+ (/.install "char" (binary ..text//char))
+ (/.install "clip" (trinary ..text//clip))
)))
(def: (io//log! messageO)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
new file mode 100644
index 000000000..03600ab57
--- /dev/null
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
@@ -0,0 +1,197 @@
+(.module:
+ [lux #*
+ [abstract
+ ["." monad (#+ do)]]
+ [control
+ ["." function]
+ ["<>" parser
+ ["<s>" synthesis (#+ Parser)]]]
+ [data
+ [collection
+ ["." dictionary]
+ ["." list]]
+ [text
+ ["%" format (#+ format)]]]
+ [target
+ ["_" lua (#+ Var Expression)]]]
+ ["." // #_
+ ["#." common (#+ custom)]
+ ["//#" /// #_
+ ["/" bundle]
+ ["/#" // #_
+ ["." extension]
+ [generation
+ [extension (#+ Nullary Unary Binary Trinary
+ nullary unary binary trinary)]
+ ["//" lua #_
+ ["#." runtime (#+ Operation Phase Handler Bundle
+ with_vars)]]]
+ ["/#" // #_
+ ["." generation]
+ ["//#" /// #_
+ ["#." phase]]]]]])
+
+(def: array::new
+ (Unary Expression)
+ (|>> ["n"] list _.table))
+
+(def: array::length
+ (Unary Expression)
+ (_.the "n"))
+
+(def: (array::read [indexG arrayG])
+ (Binary Expression)
+ (_.nth (_.+ (_.int +1) indexG) arrayG))
+
+(def: (array::write [indexG valueG arrayG])
+ (Trinary Expression)
+ (//runtime.array//write indexG valueG arrayG))
+
+(def: (array::delete [indexG arrayG])
+ (Binary Expression)
+ (//runtime.array//write indexG _.nil arrayG))
+
+(def: array
+ Bundle
+ (<| (/.prefix "array")
+ (|> /.empty
+ (/.install "new" (unary array::new))
+ (/.install "length" (unary array::length))
+ (/.install "read" (binary array::read))
+ (/.install "write" (trinary array::write))
+ (/.install "delete" (binary array::delete))
+ )))
+
+(def: object::get
+ Handler
+ (custom
+ [($_ <>.and <s>.text <s>.any)
+ (function (_ extension phase archive [fieldS objectS])
+ (do ////////phase.monad
+ [objectG (phase archive objectS)]
+ (wrap (_.the fieldS objectG))))]))
+
+(def: object::do
+ Handler
+ (custom
+ [($_ <>.and <s>.text <s>.any (<>.some <s>.any))
+ (function (_ extension phase archive [methodS objectS inputsS])
+ (do {! ////////phase.monad}
+ [objectG (phase archive objectS)
+ inputsG (monad.map ! (phase archive) inputsS)]
+ (wrap (_.do methodS inputsG objectG))))]))
+
+(template [<!> <?> <unit>]
+ [(def: <!> (Nullary Expression) (function.constant <unit>))
+ (def: <?> (Unary Expression) (_.= <unit>))]
+
+ [object::nil object::nil? _.nil]
+ )
+
+(def: object
+ Bundle
+ (<| (/.prefix "object")
+ (|> /.empty
+ (/.install "get" object::get)
+ (/.install "do" object::do)
+ (/.install "nil" (nullary object::nil))
+ (/.install "nil?" (unary object::nil?))
+ )))
+
+(def: $input
+ (_.var "input"))
+
+(def: utf8::encode
+ (custom
+ [<s>.any
+ (function (_ extension phase archive inputS)
+ (do {! ////////phase.monad}
+ [inputG (phase archive inputS)]
+ (wrap (_.apply/1 (<| (_.closure (list $input))
+ (_.return (|> (_.var "string.byte")
+ (_.apply/* (list $input (_.int +1) (_.length $input)))
+ (_.apply/1 (_.var "table.pack")))))
+ inputG))))]))
+
+(def: utf8::decode
+ (custom
+ [<s>.any
+ (function (_ extension phase archive inputS)
+ (do {! ////////phase.monad}
+ [inputG (phase archive inputS)]
+ (wrap (|> inputG
+ (_.apply/1 (_.var "table.unpack"))
+ (_.apply/1 (_.var "string.char"))))))]))
+
+(def: utf8
+ Bundle
+ (<| (/.prefix "utf8")
+ (|> /.empty
+ (/.install "encode" utf8::encode)
+ (/.install "decode" utf8::decode)
+ )))
+
+(def: lua::constant
+ (custom
+ [<s>.text
+ (function (_ extension phase archive name)
+ (\ ////////phase.monad wrap (_.var name)))]))
+
+(def: lua::apply
+ (custom
+ [($_ <>.and <s>.any (<>.some <s>.any))
+ (function (_ extension phase archive [abstractionS inputsS])
+ (do {! ////////phase.monad}
+ [abstractionG (phase archive abstractionS)
+ inputsG (monad.map ! (phase archive) inputsS)]
+ (wrap (_.apply/* inputsG abstractionG))))]))
+
+(def: lua::power
+ (custom
+ [($_ <>.and <s>.any <s>.any)
+ (function (_ extension phase archive [powerS baseS])
+ (do {! ////////phase.monad}
+ [powerG (phase archive powerS)
+ baseG (phase archive baseS)]
+ (wrap (_.^ powerG baseG))))]))
+
+(def: lua::import
+ (custom
+ [<s>.text
+ (function (_ extension phase archive module)
+ (\ ////////phase.monad wrap
+ (_.require/1 (_.string module))))]))
+
+(def: lua::function
+ (custom
+ [($_ <>.and <s>.i64 <s>.any)
+ (function (_ extension phase archive [arity abstractionS])
+ (do {! ////////phase.monad}
+ [abstractionG (phase archive abstractionS)
+ #let [variable (: (-> Text (Operation Var))
+ (|>> generation.gensym
+ (\ ! map _.var)))]
+ g!inputs (monad.map ! (function (_ _)
+ (variable "input"))
+ (list.repeat (.nat arity) []))]
+ (wrap (<| (_.closure g!inputs)
+ _.statement
+ (case (.nat arity)
+ 0 (_.apply/1 abstractionG //runtime.unit)
+ 1 (_.apply/* g!inputs abstractionG)
+ _ (_.apply/1 abstractionG (_.array g!inputs)))))))]))
+
+(def: #export bundle
+ Bundle
+ (<| (/.prefix "lua")
+ (|> /.empty
+ (dictionary.merge ..array)
+ (dictionary.merge ..object)
+ (dictionary.merge ..utf8)
+
+ (/.install "constant" lua::constant)
+ (/.install "apply" lua::apply)
+ (/.install "power" lua::power)
+ (/.install "import" lua::import)
+ (/.install "function" lua::function)
+ )))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux
index 03913b84b..ab89ff708 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux
@@ -26,8 +26,6 @@
[reference (#+)
[variable (#+)]]]]]]])
-(exception: #export cannot-recur-as-an-expression)
-
(def: (statement expression archive synthesis)
Phase!
(case synthesis
@@ -64,6 +62,8 @@
(//////phase\map _.return (/function.function statement expression archive abstraction))
))
+(exception: #export cannot-recur-as-an-expression)
+
(def: (expression archive synthesis)
Phase
(case synthesis
@@ -109,8 +109,7 @@
(/function.apply expression archive application)
(#synthesis.Extension extension)
- (///extension.apply archive expression extension)
- ))
+ (///extension.apply archive expression extension)))
(def: #export generate
Phase
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index 1bcd569c7..50e3ba008 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -34,11 +34,11 @@
(-> Register Var)
(|>> (///reference.local //reference.system) :assume))
-(def: #export (let generate archive [valueS register bodyS])
+(def: #export (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
(do ///////phase.monad
- [valueO (generate archive valueS)
- bodyO (generate archive bodyS)]
+ [valueO (expression archive valueS)
+ bodyO (expression archive bodyS)]
## TODO: Find some way to do 'let' without paying the price of the closure.
(wrap (_.apply/* (_.closure (list (..register register))
(_.return bodyO))
@@ -49,15 +49,16 @@
(do ///////phase.monad
[valueO (expression archive valueS)
bodyO (statement expression archive bodyS)]
- (wrap (_.then (_.define (..register register) valueO)
- bodyO))))
+ (wrap ($_ _.then
+ (_.define (..register register) valueO)
+ bodyO))))
-(def: #export (if generate archive [testS thenS elseS])
+(def: #export (if expression archive [testS thenS elseS])
(Generator [Synthesis Synthesis Synthesis])
(do ///////phase.monad
- [testO (generate archive testS)
- thenO (generate archive thenS)
- elseO (generate archive elseS)]
+ [testO (expression archive testS)
+ thenO (expression archive thenS)
+ elseO (expression archive elseS)]
(wrap (_.? testO thenO elseO))))
(def: #export (if! statement expression archive [testS thenS elseS])
@@ -70,10 +71,10 @@
thenO
elseO))))
-(def: #export (get generate archive [pathP valueS])
+(def: #export (get expression archive [pathP valueS])
(Generator [(List Member) Synthesis])
(do ///////phase.monad
- [valueO (generate archive valueS)]
+ [valueO (expression archive valueS)]
(wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
@@ -223,6 +224,9 @@
#.None
(.case pathP
+ (#/////synthesis.Then bodyS)
+ (statement expression archive bodyS)
+
#/////synthesis.Pop
(///////phase\wrap pop_cursor!)
@@ -269,9 +273,6 @@
([#/////synthesis.F64_Fork //primitive.f64]
[#/////synthesis.Text_Fork //primitive.text])
- (#/////synthesis.Then bodyS)
- (statement expression archive bodyS)
-
(^template [<complex> <choice>]
[(^ (<complex> idx))
(///////phase\wrap (<choice> false idx))])
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
index 89fd86bb6..4d403e22e 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
@@ -26,28 +26,30 @@
[reference
[variable (#+ Register Variable)]]]]]])
-(def: #export (apply generate archive [functionS argsS+])
+(def: #export (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
(do {! ///////phase.monad}
- [functionO (generate archive functionS)
- argsO+ (monad.map ! (generate archive) argsS+)]
+ [functionO (expression archive functionS)
+ argsO+ (monad.map ! (expression archive) argsS+)]
(wrap (_.apply/* functionO argsO+))))
-(def: (with_closure @self inits function_body)
+(def: capture
+ (-> Register Var)
+ (|>> (///reference.foreign //reference.system) :assume))
+
+(def: (with_closure @self inits body!)
(-> Var (List Expression) Statement [Statement Expression])
(case inits
#.Nil
- [(_.function! @self (list) function_body)
+ [(_.function! @self (list) body!)
@self]
_
- (let [capture (: (-> Register Var)
- (|>> (///reference.foreign //reference.system) :assume))]
- [(_.function! @self
- (|> (list.enumeration inits)
- (list\map (|>> product.left capture)))
- (_.return (_.function @self (list) function_body)))
- (_.apply/* @self inits)])))
+ [(_.function! @self
+ (|> (list.enumeration inits)
+ (list\map (|>> product.left ..capture)))
+ (_.return (_.function @self (list) body!)))
+ (_.apply/* @self inits)]))
(def: @curried
(_.var "curried"))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
index bbeaca725..135cfeb74 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
@@ -69,20 +69,11 @@
## true loop
_
(do {! ///////phase.monad}
- [@scope (\ ! map ..@scope /////generation.next)
- initsO+ (monad.map ! (expression archive) initsS+)
- body! (/////generation.with_anchor [start @scope]
- (statement expression archive bodyS))
- #let [closure (_.closure
- (|> initsS+
- list.enumeration
- (list\map (|>> product.left (n.+ start) //case.register)))
- (_.with_label (_.label @scope)
- (_.do_while (_.boolean true)
- body!)))]]
- (wrap (_.apply/* closure initsO+)))))
+ [loop! (scope! statement expression archive [start initsS+ bodyS])]
+ (wrap (_.apply/* (_.closure (list) loop!) (list))))))
-(def: @temp (_.var "lux_recur_values"))
+(def: @temp
+ (_.var "lux_recur_values"))
(def: #export (recur! statement expression archive argsS+)
(Generator! (List Synthesis))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index f62b04c4e..53213d3f1 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -682,9 +682,10 @@
..none
(..some (i64//from_number idx)))))))
-(runtime: (text//clip start end text)
- (_.return (|> text (_.do "substring" (list (_.the ..i64_low_field start)
- (_.the ..i64_low_field end))))))
+(runtime: (text//clip offset length text)
+ (_.return (|> text (_.do "substring" (list (_.the ..i64_low_field offset)
+ (_.+ (_.the ..i64_low_field offset)
+ (_.the ..i64_low_field length)))))))
(runtime: (text//char idx text)
(with_vars [result]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
index 2e3369915..7f16a8d5f 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
@@ -1,7 +1,11 @@
(.module:
[lux #*
[abstract
- [monad (#+ do)]]]
+ [monad (#+ do)]]
+ [control
+ ["." exception (#+ exception:)]]
+ [target
+ ["_" lua]]]
["." / #_
[runtime (#+ Phase Phase!)]
["#." primitive]
@@ -22,7 +26,45 @@
[reference (#+)
[variable (#+)]]]]]]])
-(def: #export (generate archive synthesis)
+(def: (statement expression archive synthesis)
+ Phase!
+ (case synthesis
+ (^template [<tag>]
+ [(^ (<tag> value))
+ (//////phase\map _.return (expression archive synthesis))])
+ ([synthesis.bit]
+ [synthesis.i64]
+ [synthesis.f64]
+ [synthesis.text]
+ [synthesis.variant]
+ [synthesis.tuple]
+ [#synthesis.Reference]
+ [synthesis.branch/get]
+ [synthesis.function/apply]
+ [#synthesis.Extension])
+
+ (^ (synthesis.branch/case case))
+ (/case.case! statement expression archive case)
+
+ (^ (synthesis.branch/let let))
+ (/case.let! statement expression archive let)
+
+ (^ (synthesis.branch/if if))
+ (/case.if! statement expression archive if)
+
+ (^ (synthesis.loop/scope scope))
+ (/loop.scope! statement expression archive scope)
+
+ (^ (synthesis.loop/recur updates))
+ (/loop.recur! statement expression archive updates)
+
+ (^ (synthesis.function/abstraction abstraction))
+ (//////phase\map _.return (/function.function statement expression archive abstraction))
+ ))
+
+(exception: #export cannot-recur-as-an-expression)
+
+(def: (expression archive synthesis)
Phase
(case synthesis
(^template [<tag> <generator>]
@@ -34,37 +76,41 @@
[synthesis.text /primitive.text])
(^ (synthesis.variant variantS))
- (/structure.variant generate archive variantS)
+ (/structure.variant expression archive variantS)
(^ (synthesis.tuple members))
- (/structure.tuple generate archive members)
+ (/structure.tuple expression archive members)
(#synthesis.Reference value)
(//reference.reference /reference.system archive value)
(^ (synthesis.branch/case case))
- (/case.case generate archive case)
+ (/case.case ..statement expression archive case)
(^ (synthesis.branch/let let))
- (/case.let generate archive let)
+ (/case.let expression archive let)
(^ (synthesis.branch/if if))
- (/case.if generate archive if)
+ (/case.if expression archive if)
(^ (synthesis.branch/get get))
- (/case.get generate archive get)
+ (/case.get expression archive get)
(^ (synthesis.loop/scope scope))
- (/loop.scope generate archive scope)
+ (/loop.scope ..statement expression archive scope)
(^ (synthesis.loop/recur updates))
- (/loop.recur generate archive updates)
+ (//////phase.throw ..cannot-recur-as-an-expression [])
(^ (synthesis.function/abstraction abstraction))
- (/function.function generate archive abstraction)
+ (/function.function ..statement expression archive abstraction)
(^ (synthesis.function/apply application))
- (/function.apply generate archive application)
+ (/function.apply expression archive application)
(#synthesis.Extension extension)
- (///extension.apply archive generate extension)))
+ (///extension.apply archive expression extension)))
+
+(def: #export generate
+ Phase
+ ..expression)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 3c56c2dfa..818575720 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -37,21 +37,30 @@
(-> Register Var)
(|>> (///reference.foreign //reference.system) :assume))
-(def: #export (let generate archive [valueS register bodyS])
+(def: #export (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
(do ///////phase.monad
- [valueO (generate archive valueS)
- bodyO (generate archive bodyS)]
+ [valueO (expression archive valueS)
+ bodyO (expression archive bodyS)]
## TODO: Find some way to do 'let' without paying the price of the closure.
(wrap (|> bodyO
_.return
(_.closure (list (..register register)))
(_.apply/* (list valueO))))))
-(def: #export (get generate archive [pathP valueS])
+(def: #export (let! statement expression archive [valueS register bodyS])
+ (Generator! [Synthesis Register Synthesis])
+ (do ///////phase.monad
+ [valueO (expression archive valueS)
+ bodyO (statement expression archive bodyS)]
+ (wrap ($_ _.then
+ (_.local/1 (..register register) valueO)
+ bodyO))))
+
+(def: #export (get expression archive [pathP valueS])
(Generator [(List Member) Synthesis])
(do ///////phase.monad
- [valueO (generate archive valueS)]
+ [valueO (expression archive valueS)]
(wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
@@ -63,18 +72,28 @@
valueO
(list.reverse pathP)))))
-(def: #export (if generate archive [testS thenS elseS])
+(def: #export (if expression archive [testS thenS elseS])
(Generator [Synthesis Synthesis Synthesis])
(do ///////phase.monad
- [testO (generate archive testS)
- thenO (generate archive thenS)
- elseO (generate archive elseS)]
+ [testO (expression archive testS)
+ thenO (expression archive thenS)
+ elseO (expression archive elseS)]
(wrap (|> (_.if testO
(_.return thenO)
(_.return elseO))
(_.closure (list))
(_.apply/* (list))))))
+(def: #export (if! statement expression archive [testS thenS elseS])
+ (Generator! [Synthesis Synthesis Synthesis])
+ (do ///////phase.monad
+ [testO (expression archive testS)
+ thenO (statement expression archive thenS)
+ elseO (statement expression archive elseS)]
+ (wrap (_.if testO
+ thenO
+ elseO))))
+
(def: @savepoint (_.var "lux_pm_savepoint"))
(def: @cursor (_.var "lux_pm_cursor"))
(def: @temp (_.var "lux_pm_temp"))
@@ -134,12 +153,12 @@
..restore!
post!)))
-(def: (pattern_matching' generate archive)
- (-> Phase Archive Path (Operation Statement))
+(def: (pattern_matching' statement expression archive)
+ (-> Phase! Phase Archive Path (Operation Statement))
(function (recur pathP)
(.case pathP
(#/////synthesis.Then bodyS)
- (///////phase\map _.return (generate archive bodyS))
+ (statement expression archive bodyS)
#/////synthesis.Pop
(///////phase\wrap ..pop!)
@@ -213,10 +232,10 @@
([/////synthesis.path/seq _.then]
[/////synthesis.path/alt ..alternation]))))
-(def: (pattern_matching generate archive pathP)
- (-> Phase Archive Path (Operation Statement))
+(def: (pattern_matching statement expression archive pathP)
+ (-> Phase! Phase Archive Path (Operation Statement))
(do ///////phase.monad
- [pattern_matching! (pattern_matching' generate archive pathP)]
+ [pattern_matching! (pattern_matching' statement expression archive pathP)]
(wrap ($_ _.then
(_.while (_.bool true)
pattern_matching!)
@@ -235,21 +254,21 @@
(#///////variable.Foreign register)
(..capture register))))))
-(def: #export (case generate archive [valueS pathP])
- (Generator [Synthesis Path])
+(def: #export (case! statement expression archive [valueS pathP])
+ (Generator! [Synthesis Path])
(do ///////phase.monad
- [initG (generate archive valueS)
- [[case_module case_artifact] pattern_matching!] (/////generation.with_new_context archive
- (pattern_matching generate archive pathP))
- #let [@case (_.var (///reference.artifact [case_module case_artifact]))
- @dependencies+ (..dependencies (/////synthesis.path/seq (/////synthesis.path/then valueS)
- pathP))
- directive (_.function @case @dependencies+
- ($_ _.then
- (_.local (list @temp))
- (_.local/1 @cursor (_.array (list initG)))
- (_.local/1 @savepoint (_.array (list)))
- pattern_matching!))]
- _ (/////generation.execute! directive)
- _ (/////generation.save! (%.nat case_artifact) directive)]
- (wrap (_.apply/* @dependencies+ @case))))
+ [stack_init (expression archive valueS)
+ pattern_matching! (pattern_matching statement expression archive pathP)]
+ (wrap ($_ _.then
+ (_.local (list @temp))
+ (_.local/1 @cursor (_.array (list stack_init)))
+ (_.local/1 @savepoint (_.array (list)))
+ pattern_matching!))))
+
+(def: #export (case statement expression archive [valueS pathP])
+ (-> Phase! (Generator [Synthesis Path]))
+ (|> [valueS pathP]
+ (..case! statement expression archive)
+ (\ ///////phase.monad map
+ (|>> (_.closure (list))
+ (_.apply/* (list))))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index c7fe7f51c..3aa3a9ca7 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -11,7 +11,7 @@
[collection
["." list ("#\." functor fold)]]]
[target
- ["_" lua (#+ Var Expression Statement)]]]
+ ["_" lua (#+ Var Expression Label Statement)]]]
["." // #_
["#." runtime (#+ Operation Phase Phase! Generator)]
["#." reference]
@@ -28,58 +28,55 @@
[reference
[variable (#+ Register Variable)]]]]]])
-(def: #export (apply generate archive [functionS argsS+])
+(def: #export (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
(do {! ///////phase.monad}
- [functionO (generate archive functionS)
- argsO+ (monad.map ! (generate archive) argsS+)]
+ [functionO (expression archive functionS)
+ argsO+ (monad.map ! (expression archive) argsS+)]
(wrap (_.apply/* argsO+ functionO))))
-(def: #export capture
+(def: capture
(-> Register Var)
(|>> (///reference.foreign //reference.system) :assume))
-(def: (with_closure function_name inits @function @args @body)
- (-> Text (List Expression) Var (List Var) Statement (Operation Expression))
+(def: (with_closure inits @self @args body!)
+ (-> (List Expression) Var (List Var) Statement [Statement Expression])
(case inits
#.Nil
- (do ///////phase.monad
- [#let [function_definition (_.function @function @args @body)]
- _ (/////generation.execute! function_definition)
- _ (/////generation.save! function_name function_definition)]
- (wrap (_.var function_name)))
+ [(_.function @self @args body!)
+ @self]
_
- (do {! ///////phase.monad}
- [#let [@closure (_.var (format function_name "_closure"))
- directive (_.function @closure
- (|> (list.enumeration inits)
- (list\map (|>> product.left ..capture)))
- ($_ _.then
- (_.local_function @function @args @body)
- (_.return (_.var function_name))))]
- _ (/////generation.execute! directive)
- _ (/////generation.save! (_.code @closure) directive)]
- (wrap (_.apply/* inits @closure)))))
+ (let [@inits (|> (list.enumeration inits)
+ (list\map (|>> product.left ..capture)))]
+ [(_.function @self @inits
+ ($_ _.then
+ (_.local_function @self @args body!)
+ (_.return @self)))
+ (_.apply/* inits @self)])))
(def: input
(|>> inc //case.register))
-(def: #export (function generate archive [environment arity bodyS])
- (Generator (Abstraction Synthesis))
+(def: (@scope function_name)
+ (-> Context Label)
+ (_.label (format (///reference.artifact function_name) "_scope")))
+
+(def: #export (function statement expression archive [environment arity bodyS])
+ (-> Phase! (Generator (Abstraction Synthesis)))
(do {! ///////phase.monad}
- [[function_name bodyO] (/////generation.with_new_context archive
+ [[function_name body!] (/////generation.with_new_context archive
(do !
- [function_name (\ ! map ///reference.artifact
- (/////generation.context archive))]
- (/////generation.with_anchor (_.var function_name)
- (generate archive bodyS))))
- closureO+ (monad.map ! (generate archive) environment)
- #let [function_name (///reference.artifact function_name)
- @curried (_.var "curried")
+ [@scope (\ ! map ..@scope
+ (/////generation.context archive))]
+ (/////generation.with_anchor [1 @scope]
+ (statement expression archive bodyS))))
+ closureO+ (monad.map ! (expression archive) environment)
+ #let [@curried (_.var "curried")
arityO (|> arity .int _.int)
@num_args (_.var "num_args")
- @self (_.var function_name)
+ @scope (..@scope function_name)
+ @self (_.var (///reference.artifact function_name))
initialize_self! (_.local/1 (//case.register 0) @self)
initialize! (list\fold (.function (_ post pre!)
($_ _.then
@@ -89,26 +86,28 @@
(list.indices arity))
pack (|>> (list) _.array)
unpack (|>> (list) _.apply/* (|> (_.var "table.unpack")))
- @var_args (_.var "...")]]
- (with_closure function_name closureO+
- @self (list @var_args)
- ($_ _.then
- (_.local/1 @curried (pack @var_args))
- (_.local/1 @num_args (_.length @curried))
- (_.cond (list [(|> @num_args (_.= (_.int +0)))
- (_.return @self)]
- [(|> @num_args (_.= arityO))
- ($_ _.then
- initialize!
- (_.return bodyO))]
- [(|> @num_args (_.> arityO))
- (let [arity_inputs (//runtime.array//sub (_.int +0) arityO @curried)
- extra_inputs (//runtime.array//sub arityO @num_args @curried)]
- (_.return (|> @self
- (_.apply/* (list (unpack arity_inputs)))
- (_.apply/* (list (unpack extra_inputs))))))])
- ## (|> @num_args (_.< arityO))
- (_.return (_.closure (list @var_args)
- (_.return (|> @self (_.apply/* (list (unpack (//runtime.array//concat @curried (pack @var_args))))))))))
- ))
- ))
+ @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 (_.= (_.int +0)))
+ (_.return @self)]
+ [(|> @num_args (_.= arityO))
+ ($_ _.then
+ initialize!
+ (_.set_label @scope)
+ body!)]
+ [(|> @num_args (_.> arityO))
+ (let [arity_inputs (//runtime.array//sub (_.int +0) arityO @curried)
+ extra_inputs (//runtime.array//sub arityO @num_args @curried)]
+ (_.return (|> @self
+ (_.apply/* (list (unpack arity_inputs)))
+ (_.apply/* (list (unpack extra_inputs))))))])
+ ## (|> @num_args (_.< arityO))
+ (_.return (_.closure (list @var_args)
+ (_.return (|> @self (_.apply/* (list (unpack (//runtime.array//concat @curried (pack @var_args))))))))))
+ ))]
+ _ (/////generation.execute! definition)
+ _ (/////generation.save! (%.nat (product.right function_name)) definition)]
+ (wrap instantiation)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
index b1b8a47cb..7fc7ebbfd 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
@@ -13,7 +13,7 @@
[number
["n" nat]]]
[target
- ["_" lua (#+ Var Expression Statement)]]]
+ ["_" lua (#+ Var Expression Label Statement)]]]
["." // #_
[runtime (#+ Operation Phase Phase! Generator Generator!)]
["#." case]
@@ -27,29 +27,53 @@
[reference
[variable (#+ Register)]]]]]])
-(def: loop_name
- (-> Nat Var)
- (|>> %.nat (format "loop") _.var))
+(def: @scope
+ (-> Nat Label)
+ (|>> %.nat (format "scope") _.label))
-(def: #export (scope generate archive [start initsS+ bodyS])
- (Generator (Scope Synthesis))
+(def: (setup initial? offset bindings body)
+ (-> Bit Register (List Expression) Statement Statement)
+ (let [variables (|> bindings
+ list.enumeration
+ (list\map (|>> product.left (n.+ offset) //case.register)))]
+ ($_ _.then
+ (if initial?
+ (_.let variables (_.multi bindings))
+ (_.set variables (_.multi bindings)))
+ body)))
+
+(def: #export (scope! statement expression archive [start initsS+ bodyS])
+ (Generator! (Scope Synthesis))
+ (case initsS+
+ ## function/false/non-independent loop
+ #.Nil
+ (statement expression archive bodyS)
+
+ ## true loop
+ _
+ (do {! ///////phase.monad}
+ [@scope (\ ! map ..@scope /////generation.next)
+ initsO+ (monad.map ! (expression archive) initsS+)
+ body! (/////generation.with_anchor [start @scope]
+ (statement expression archive bodyS))]
+ (wrap (..setup true start initsO+
+ ($_ _.then
+ (_.set_label @scope)
+ body!))))))
+
+(def: #export (scope statement expression archive [start initsS+ bodyS])
+ (-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
#.Nil
- (generate archive bodyS)
+ (expression archive bodyS)
## true loop
_
(do {! ///////phase.monad}
- [@loop (\ ! map ..loop_name /////generation.next)
- initsO+ (monad.map ! (generate archive) initsS+)
- [loop_name bodyO] (/////generation.with_new_context archive
- (do !
- [@loop (\ ! map (|>> ///reference.artifact _.var)
- (/////generation.context archive))]
- (/////generation.with_anchor @loop
- (generate archive bodyS))))
- #let [@loop (_.var (///reference.artifact loop_name))
+ [[[artifact_module artifact_id] scope!] (/////generation.with_new_context archive
+ (scope! statement expression archive [start initsS+ bodyS]))
+ #let [@loop (_.var (///reference.artifact [artifact_module artifact_id]))
locals (|> initsS+
list.enumeration
(list\map (|>> product.left (n.+ start) //case.register)))
@@ -61,25 +85,25 @@
set.to_list)
#.Nil
[(_.function @loop locals
- (_.return bodyO))
+ scope!)
@loop]
foreigns
- (let [@context (_.var (format (///reference.artifact loop_name) "_context"))]
+ (let [@context (_.var (format (_.code @loop) "_context"))]
[(_.function @context foreigns
($_ _.then
(<| (_.local_function @loop locals)
- (_.return bodyO))
+ scope!)
(_.return @loop)
))
(_.apply/* foreigns @context)])))]
_ (/////generation.execute! directive)
- _ (/////generation.save! (_.code @loop) directive)]
- (wrap (_.apply/* initsO+ instantiation)))))
+ _ (/////generation.save! (%.nat artifact_id) directive)]
+ (wrap instantiation))))
-(def: #export (recur generate archive argsS+)
- (Generator (List Synthesis))
+(def: #export (recur! statement expression archive argsS+)
+ (Generator! (List Synthesis))
(do {! ///////phase.monad}
- [@scope /////generation.anchor
- argsO+ (monad.map ! (generate archive) argsS+)]
- (wrap (_.apply/* argsO+ @scope))))
+ [[offset @scope] /////generation.anchor
+ argsO+ (monad.map ! (expression archive) argsS+)]
+ (wrap (..setup false offset argsO+ (_.go_to @scope)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
index d7b0f1cd3..46911bcc4 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
@@ -22,7 +22,7 @@
[number (#+ hex)
["." i64]]]
[target
- ["_" lua (#+ Expression Location Var Computation Literal Statement)]]]
+ ["_" lua (#+ Expression Location Var Computation Literal Label Statement)]]]
["." /// #_
["#." reference]
["//#" /// #_
@@ -38,7 +38,7 @@
(template [<name> <base>]
[(type: #export <name>
- (<base> Var Expression Statement))]
+ (<base> [Register Label] Expression Statement))]
[Operation /////generation.Operation]
[Phase /////generation.Phase]
@@ -295,22 +295,23 @@
(runtime: (text//index subject param start)
(with_vars [idx]
($_ _.then
- (_.let (list idx) (_.apply/* (list subject param start (_.bool #1))
- (_.var "string.find")))
+ (_.local/1 idx (_.apply/* (list subject param start (_.bool #1))
+ (_.var "string.find")))
(_.if (_.= _.nil idx)
(_.return ..none)
- (_.return (..some idx))))))
+ (_.return (..some (_.- (_.int +1) idx)))))))
-(runtime: (text//clip text from to)
- (_.return (_.apply/* (list text from to) (_.var "string.sub"))))
+(runtime: (text//clip text offset length)
+ (_.return (_.apply/* (list text (_.+ (_.int +1) offset) (_.+ offset length))
+ (_.var "string.sub"))))
(runtime: (text//char idx text)
(with_vars [char]
($_ _.then
- (_.let (list char) (_.apply/* (list text idx) (_.var "string.byte")))
+ (_.local/1 char (_.apply/* (list text idx)
+ (_.var "string.byte")))
(_.if (_.= _.nil char)
- (_.statement (_.apply/* (list (_.string "[Lux Error] Cannot get char from text."))
- (_.var "error")))
+ (_.statement (_.error/1 (_.string "[Lux Error] Cannot get char from text.")))
(_.return char)))))
(def: runtime//text
@@ -321,24 +322,7 @@
@text//char
))
-(runtime: (array//new size)
- (with_vars [output idx]
- ($_ _.then
- (_.let (list output) (_.array (list)))
- (_.for_step idx (_.int +1) size (_.int +1)
- (_.statement (_.apply/* (list output ..unit) (_.var "table.insert"))))
- (_.return output))))
-
-(runtime: (array//get array idx)
- (with_vars [temp]
- ($_ _.then
- (_.let (list temp) (..nth idx array))
- (_.if (_.or (_.= _.nil temp)
- (_.= ..unit temp))
- (_.return ..none)
- (_.return (..some temp))))))
-
-(runtime: (array//put array idx value)
+(runtime: (array//write idx value array)
($_ _.then
(_.set (list (..nth idx array)) value)
(_.return array)))
@@ -346,31 +330,17 @@
(def: runtime//array
Statement
($_ _.then
- @array//new
- @array//get
- @array//put
- ))
-
-(runtime: (box//write value box)
- ($_ _.then
- (_.set (list (_.nth (_.int +1) box)) value)
- (_.return ..unit)))
-
-(def: runtime//box
- Statement
- ($_ _.then
- @box//write
+ @array//write
))
(def: runtime
Statement
($_ _.then
- runtime//adt
- runtime//lux
- runtime//i64
- runtime//text
- runtime//array
- runtime//box
+ ..runtime//adt
+ ..runtime//lux
+ ..runtime//i64
+ ..runtime//text
+ ..runtime//array
))
(def: #export artifact ..prefix)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
index 132ec3c98..a2e18808a 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
@@ -378,8 +378,8 @@
(_.and (|> value (_.>= (_.int +0)))
(|> value (_.< top))))
-(runtime: (text//clip @from @to @text)
- (_.return (|> @text (_.slice @from @to))))
+(runtime: (text//clip @offset @length @text)
+ (_.return (|> @text (_.slice @offset (_.+ @offset @length)))))
(runtime: (text//char idx text)
(_.if (|> idx (within? (_.len/1 text)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
index 8362c7054..488738c00 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
@@ -79,7 +79,7 @@
)
(template: (!clip from to text)
- ("lux text clip" from to text))
+ ("lux text clip" from (n.- from to) text))
(template [<name> <extension>]
[(template: (<name> reference subject)