aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool/compiler/phase/generation
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/case.lux76
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux48
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/function.lux23
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux9
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/reference.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux63
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux24
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux31
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux9
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux26
13 files changed, 176 insertions, 181 deletions
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux
index 11869fa7b..8dba99feb 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux
@@ -11,19 +11,19 @@
["." list ("#/." functor fold)]]]
[host
["_" js (#+ Expression Computation Var Statement)]]]
- [//
- ["//." runtime (#+ Operation Phase)]
- ["//." reference]
- ["//." primitive]
- [//
- ["." reference]
- ["//." // ("#/." monad)
- [//
+ ["." // #_
+ ["#." runtime (#+ Operation Phase)]
+ ["#." reference]
+ ["#." primitive]
+ ["#/" // #_
+ ["#." reference]
+ ["#/" // ("#/." monad)
+ ["#/" // #_
[reference (#+ Register)]
- ["." synthesis (#+ Synthesis Path)]]]]])
+ ["#." synthesis (#+ Synthesis Path)]]]]])
(def: #export register
- (reference.local _.var))
+ (///reference.local _.var))
(def: #export (let generate [valueS register bodyS])
(-> Phase [Synthesis Register Synthesis]
@@ -101,8 +101,8 @@
(def: (count-pops path)
(-> Path [Nat Path])
(.case path
- (^ ($_ synthesis.path/seq
- #synthesis.Pop
+ (^ ($_ /////synthesis.path/seq
+ #/////synthesis.Pop
path'))
(.let [[pops post-pops] (count-pops path')]
[(inc pops) post-pops])
@@ -121,25 +121,25 @@
(def: (pattern-matching' generate pathP)
(-> Phase Path (Operation Statement))
(.case pathP
- (^ (synthesis.path/then bodyS))
+ (^ (/////synthesis.path/then bodyS))
(do ////.monad
[body! (generate bodyS)]
(wrap (_.return body!)))
- #synthesis.Pop
+ #/////synthesis.Pop
(/////wrap pop-cursor!)
- (#synthesis.Bind register)
+ (#/////synthesis.Bind register)
(/////wrap (_.define (..register register) ..peek-cursor))
(^template [<tag> <format> <=>]
(^ (<tag> value))
(/////wrap (_.when (|> value <format> (<=> ..peek-cursor) _.not)
fail-pm!)))
- ([synthesis.path/bit //primitive.bit _.=]
- [synthesis.path/i64 (<| //primitive.i64 .int) //runtime.i64//=]
- [synthesis.path/f64 //primitive.f64 _.=]
- [synthesis.path/text //primitive.text _.=])
+ ([/////synthesis.path/bit //primitive.bit _.=]
+ [/////synthesis.path/i64 (<| //primitive.i64 .int) //runtime.i64//=]
+ [/////synthesis.path/f64 //primitive.f64 _.=]
+ [/////synthesis.path/text //primitive.text _.=])
(^template [<pm> <flag> <prep>]
(^ (<pm> idx))
@@ -148,18 +148,18 @@
(_.if (_.= _.null @temp)
fail-pm!
(push-cursor! @temp)))))
- ([synthesis.side/left _.null (<|)]
- [synthesis.side/right (_.string "") inc])
+ ([/////synthesis.side/left _.null (<|)]
+ [/////synthesis.side/right (_.string "") inc])
(^template [<pm> <getter> <prep>]
(^ (<pm> idx))
(/////wrap (|> idx <prep> .int _.i32 (<getter> ..peek-cursor) push-cursor!)))
- ([synthesis.member/left //runtime.product//left (<|)]
- [synthesis.member/right //runtime.product//right inc])
+ ([/////synthesis.member/left //runtime.product//left (<|)]
+ [/////synthesis.member/right //runtime.product//right inc])
- (^ ($_ synthesis.path/seq
- (#synthesis.Bind register)
- #synthesis.Pop
+ (^ ($_ /////synthesis.path/seq
+ (#/////synthesis.Bind register)
+ #/////synthesis.Pop
thenP))
(do ////.monad
[then! (pattern-matching' generate thenP)]
@@ -167,9 +167,9 @@
(_.define (..register register) ..peek-and-pop-cursor)
then!)))
- (^ ($_ synthesis.path/seq
- #synthesis.Pop
- #synthesis.Pop
+ (^ ($_ /////synthesis.path/seq
+ #/////synthesis.Pop
+ #/////synthesis.Pop
nextP))
(.let [[extra-pops nextP'] (count-pops nextP)]
(do ////.monad
@@ -184,15 +184,15 @@
[left! (pattern-matching' generate leftP)
right! (pattern-matching' generate rightP)]
(wrap <computation>)))
- ([synthesis.path/seq (_.then left! right!)]
- [synthesis.path/alt ($_ _.then
- (_.do-while _.false
- ($_ _.then
- ..save-cursor!
- left!))
- ($_ _.then
- ..restore-cursor!
- right!))])
+ ([/////synthesis.path/seq (_.then left! right!)]
+ [/////synthesis.path/alt ($_ _.then
+ (_.do-while _.false
+ ($_ _.then
+ ..save-cursor!
+ left!))
+ ($_ _.then
+ ..restore-cursor!
+ right!))])
_
(////.throw unrecognized-path [])))
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux
index 98ef827a8..cbac2ca3f 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux
@@ -15,14 +15,14 @@
["s" syntax (#+ syntax:)]]
[host (#+ import:)
["_" js (#+ Expression Computation)]]]
- [///
- ["///." runtime (#+ Operation Phase Handler Bundle)]
- ["///." primitive]
- ["//." ///
- ["." extension
+ ["." /// #_
+ ["#." runtime (#+ Operation Phase Handler Bundle)]
+ ["#." primitive]
+ ["#//" ///
+ ["#." extension
["." bundle]]
- [//
- ["." synthesis (#+ Synthesis)]]]])
+ ["#/" // #_
+ [synthesis (#+ Synthesis)]]]])
(syntax: (Vector {size s.nat} elemT)
(wrap (list (` [(~+ (list.repeat size elemT))]))))
@@ -51,7 +51,7 @@
((~' wrap) ((~ g!extension) [(~+ g!input+)])))
(~' _)
- (/////.throw extension.incorrect-arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
+ (/////.throw /////extension.incorrect-arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
(arity: nullary 0)
(arity: unary 1)
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux
index 519852967..f623242a0 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux
@@ -8,15 +8,15 @@
["." dictionary]]]
[host
["_" js]]]
- [//
- ["." common (#+ Nullary Binary Trinary Variadic)]
- [//
- ["///." runtime (#+ Handler Bundle)]
- ["//." ///
- ["." extension
+ ["." // #_
+ ["#." common (#+ Nullary Binary Trinary Variadic)]
+ ["#/" // #_
+ ["#." runtime (#+ Handler Bundle)]
+ ["#//" ///
+ ["#." extension
["." bundle]]
- [//
- ["." synthesis]]]]])
+ ["#/" // #_
+ ["#." synthesis]]]]])
(do-template [<name> <js>]
[(def: (<name> _) Nullary <js>)]
@@ -29,11 +29,11 @@
(def: (js//global name generate inputs)
Handler
(case inputs
- (^ (list (synthesis.text global)))
+ (^ (list (//////synthesis.text global)))
(:: /////.monad wrap (_.var global))
_
- (/////.throw extension.incorrect-syntax name)))
+ (/////.throw /////extension.incorrect-syntax name)))
(def: (js//call name generate inputs)
Handler
@@ -45,15 +45,15 @@
(wrap (_.apply/* functionJS argsJS+)))
_
- (/////.throw extension.incorrect-syntax name)))
+ (/////.throw /////extension.incorrect-syntax name)))
(def: js
Bundle
(|> bundle.empty
- (bundle.install "null" (common.nullary js//null))
- (bundle.install "undefined" (common.nullary js//undefined))
- (bundle.install "object" (common.nullary js//object))
- (bundle.install "array" (common.variadic _.array))
+ (bundle.install "null" (//common.nullary js//null))
+ (bundle.install "undefined" (//common.nullary js//undefined))
+ (bundle.install "object" (//common.nullary js//object))
+ (bundle.install "array" (//common.variadic _.array))
(bundle.install "global" js//global)
(bundle.install "call" js//call)))
@@ -67,7 +67,7 @@
(wrap (_.new constructorJS argsJS+)))
_
- (/////.throw extension.incorrect-syntax name)))
+ (/////.throw /////extension.incorrect-syntax name)))
(def: (object//call name generate inputs)
Handler
@@ -82,7 +82,7 @@
(_.do "apply" (list& objectJS argsJS+)))))
_
- (/////.throw extension.incorrect-syntax name)))
+ (/////.throw /////extension.incorrect-syntax name)))
(def: (object//set [fieldJS valueJS objectJS])
Trinary
@@ -94,9 +94,9 @@
(|> bundle.empty
(bundle.install "new" object//new)
(bundle.install "call" object//call)
- (bundle.install "read" (common.binary (product.uncurry ///runtime.js//get)))
- (bundle.install "write" (common.trinary object//set))
- (bundle.install "delete" (common.binary (product.uncurry ///runtime.js//delete)))
+ (bundle.install "read" (//common.binary (product.uncurry ///runtime.js//get)))
+ (bundle.install "write" (//common.trinary object//set))
+ (bundle.install "delete" (//common.binary (product.uncurry ///runtime.js//delete)))
)))
(def: (array//write [indexJS valueJS arrayJS])
@@ -107,10 +107,10 @@
Bundle
(<| (bundle.prefix "array")
(|> bundle.empty
- (bundle.install "read" (common.binary (product.uncurry ///runtime.array//read)))
- (bundle.install "write" (common.trinary array//write))
- (bundle.install "delete" (common.binary (product.uncurry ///runtime.array//delete)))
- (bundle.install "length" (common.unary (_.the "length")))
+ (bundle.install "read" (//common.binary (product.uncurry ///runtime.array//read)))
+ (bundle.install "write" (//common.trinary array//write))
+ (bundle.install "delete" (//common.binary (product.uncurry ///runtime.array//delete)))
+ (bundle.install "length" (//common.unary (_.the "length")))
)))
(def: #export bundle
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux
index ca647a81a..1d74112e2 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux
@@ -11,18 +11,17 @@
["." list ("#/." functor fold)]]]
[host
["_" js (#+ Expression Computation Var)]]]
- [//
- ["." runtime (#+ Operation Phase)]
- ["." reference]
- ["//." case]
- ["/." //
- ["common-." reference]
- ["//." // ("#/." monad)
- [//
+ ["." // #_
+ [runtime (#+ Operation Phase)]
+ ["#." reference]
+ ["#." case]
+ ["#/" //
+ ["#." reference]
+ ["#/" // ("#/." monad)
+ ["." // #_
[reference (#+ Register Variable)]
[analysis (#+ Variant Tuple Environment Arity Abstraction Application Analysis)]
- [synthesis (#+ Synthesis)]
- ["." name]]]]])
+ [synthesis (#+ Synthesis)]]]]])
(def: #export (apply generate [functionS argsS+])
(-> Phase (Application Synthesis) (Operation Computation))
@@ -32,7 +31,7 @@
(wrap (_.apply/* functionO argsO+))))
(def: #export capture
- (common-reference.foreign _.var))
+ (///reference.foreign _.var))
(def: (with-closure inits function-definition)
(-> (List Expression) Computation (Operation Computation))
@@ -63,7 +62,7 @@
(///.with-anchor (_.var function-name)
(generate bodyS))))
closureO+ (: (Operation (List Expression))
- (monad.map @ (:: reference.system variable) environment))
+ (monad.map @ (:: //reference.system variable) environment))
#let [arityO (|> arity .int _.i32)
@num-args (_.var "num_args")
@self (_.var function-name)
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux
index 4e3c7d8a9..ba12e4c03 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux
@@ -10,12 +10,11 @@
["." list ("#/." functor)]]]
[host
["_" js (#+ Computation Var)]]]
- [//
+ ["." // #_
[runtime (#+ Operation Phase)]
- ["." reference]
- ["//." case]
- ["/." //
- ["//." //
+ ["#." case]
+ ["#/" //
+ ["#/" //
[//
[synthesis (#+ Scope Synthesis)]]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux
index 139fcb191..1eb6141f9 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux
@@ -7,8 +7,8 @@
["." frac]]]
[host
["_" js (#+ Computation)]]]
- [//
- ["//." runtime]])
+ ["." // #_
+ ["#." runtime]])
(def: #export bit
(-> Bit Computation)
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux
index 623516cdb..c6b413afb 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux
@@ -4,19 +4,19 @@
["." monad (#+ do)]]
[host
["_" js (#+ Expression)]]]
- [//
- ["//." runtime (#+ Operation Phase)]
- ["//." primitive]
- ["/." ///
- [//
+ ["." // #_
+ ["#." runtime (#+ Operation Phase)]
+ ["#." primitive]
+ ["#//" ///
+ ["#/" // #_
[analysis (#+ Variant Tuple)]
- ["." synthesis (#+ Synthesis)]]]])
+ ["#." synthesis (#+ Synthesis)]]]])
(def: #export (tuple generate elemsS+)
(-> Phase (Tuple Synthesis) (Operation Expression))
(case elemsS+
#.Nil
- (:: ////.monad wrap (//primitive.text synthesis.unit))
+ (:: ////.monad wrap (//primitive.text /////synthesis.unit))
(#.Cons singletonS #.Nil)
(generate singletonS)
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/reference.lux b/stdlib/source/lux/tool/compiler/phase/generation/reference.lux
index 878d96e83..f8c875ccc 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/reference.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/reference.lux
@@ -7,10 +7,10 @@
format]]
[type (#+ :share)]]
["." //
- ["/." // ("#/." monad)
- [//
+ ["#/" // ("#/." monad)
+ ["#/" // #_
[synthesis (#+ Synthesis)]
- ["." reference (#+ Register Variable Reference)]]]])
+ ["#." reference (#+ Register Variable Reference)]]]])
(signature: #export (System expression)
(: (-> Register expression)
@@ -56,10 +56,10 @@
variable}
{(All [anchor statement]
(-> Variable (//.Operation anchor expression statement)))
- (|>> (case> (#reference.Local register)
+ (|>> (case> (#////reference.Local register)
(local register)
- (#reference.Foreign register)
+ (#////reference.Foreign register)
(foreign register))
////wrap)})
constant (:share [expression]
@@ -74,8 +74,8 @@
(def: variable variable)
(def: constant constant)
(def: reference
- (|>> (case> (#reference.Constant value)
+ (|>> (case> (#////reference.Constant value)
(constant value)
- (#reference.Variable value)
+ (#////reference.Variable value)
(variable value)))))))
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux
index aa04dc975..142e4a165 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux
@@ -11,19 +11,18 @@
["." list ("#/." functor fold)]]]
[host
["_" scheme (#+ Expression Computation Var)]]]
- [//
- ["." runtime (#+ Operation Phase)]
- ["//." primitive]
- ["." reference]
- [//
- ["common-." reference]
- ["//." // ("#/." monad)
- [//
+ ["." // #_
+ ["#." runtime (#+ Operation Phase)]
+ ["#." primitive]
+ ["#/" // #_
+ ["#." reference]
+ ["#/" // ("#/." monad)
+ ["#/" // #_
[reference (#+ Register)]
- ["." synthesis (#+ Synthesis Path)]]]]])
+ ["#." synthesis (#+ Synthesis Path)]]]]])
(def: #export register
- (common-reference.local _.var))
+ (///reference.local _.var))
(def: #export (let generate [valueS register bodyS])
(-> Phase [Synthesis Register Synthesis]
@@ -41,8 +40,8 @@
[valueO (generate valueS)]
(wrap (list/fold (function (_ [idx tail?] source)
(.let [method (.if tail?
- runtime.product//right
- runtime.product//left)]
+ //runtime.product//right
+ //runtime.product//left)]
(method source (_.int (.int idx)))))
valueO
pathP))))
@@ -105,13 +104,13 @@
(def: (pattern-matching' generate pathP)
(-> Phase Path (Operation Expression))
(.case pathP
- (^ (synthesis.path/then bodyS))
+ (^ (/////synthesis.path/then bodyS))
(generate bodyS)
- #synthesis.Pop
+ #/////synthesis.Pop
(/////wrap pop-cursor!)
- (#synthesis.Bind register)
+ (#/////synthesis.Bind register)
(/////wrap (_.define (..register register) [(list) #.None]
cursor-top))
@@ -119,25 +118,25 @@
(^ (<tag> value))
(/////wrap (_.when (|> value <format> (<=> cursor-top) _.not/1)
fail-pm!)))
- ([synthesis.path/bit //primitive.bit _.eqv?/2]
- [synthesis.path/i64 (<| //primitive.i64 .int) _.=/2]
- [synthesis.path/f64 //primitive.f64 _.=/2]
- [synthesis.path/text //primitive.text _.eqv?/2])
+ ([/////synthesis.path/bit //primitive.bit _.eqv?/2]
+ [/////synthesis.path/i64 (<| //primitive.i64 .int) _.=/2]
+ [/////synthesis.path/f64 //primitive.f64 _.=/2]
+ [/////synthesis.path/text //primitive.text _.eqv?/2])
(^template [<pm> <flag> <prep>]
(^ (<pm> idx))
- (/////wrap (_.let (list [@temp (|> idx <prep> .int _.int (runtime.sum//get cursor-top <flag>))])
+ (/////wrap (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get cursor-top <flag>))])
(_.if (_.null?/1 @temp)
fail-pm!
(push-cursor! @temp)))))
- ([synthesis.side/left _.nil (<|)]
- [synthesis.side/right (_.string "") inc])
+ ([/////synthesis.side/left _.nil (<|)]
+ [/////synthesis.side/right (_.string "") inc])
(^template [<pm> <getter> <prep>]
(^ (<pm> idx))
(/////wrap (|> idx <prep> .int _.int (<getter> cursor-top) push-cursor!)))
- ([synthesis.member/left runtime.product//left (<|)]
- [synthesis.member/right runtime.product//right inc])
+ ([/////synthesis.member/left //runtime.product//left (<|)]
+ [/////synthesis.member/right //runtime.product//right inc])
(^template [<tag> <computation>]
(^ (<tag> leftP rightP))
@@ -145,14 +144,14 @@
[leftO (pattern-matching' generate leftP)
rightO (pattern-matching' generate rightP)]
(wrap <computation>)))
- ([synthesis.path/seq (_.begin (list leftO
- rightO))]
- [synthesis.path/alt (_.with-exception-handler
- (pm-catch (_.begin (list restore-cursor!
- rightO)))
- (_.lambda [(list) #.None]
- (_.begin (list save-cursor!
- leftO))))])
+ ([/////synthesis.path/seq (_.begin (list leftO
+ rightO))]
+ [/////synthesis.path/alt (_.with-exception-handler
+ (pm-catch (_.begin (list restore-cursor!
+ rightO)))
+ (_.lambda [(list) #.None]
+ (_.begin (list save-cursor!
+ leftO))))])
_
(////.throw unrecognized-path [])))
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux
index 602eb923b..bcb98f893 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux
@@ -17,13 +17,13 @@
["s" syntax (#+ syntax:)]]
[host (#+ import:)
["_" scheme (#+ Expression Computation)]]]
- [///
- ["." runtime (#+ Operation Phase Handler Bundle)]
- ["//." ///
- ["." extension
+ ["." /// #_
+ ["#." runtime (#+ Operation Phase Handler Bundle)]
+ ["#//" ///
+ ["#." extension
["." bundle]]
- [//
- ["." synthesis (#+ Synthesis)]]]])
+ ["#/" // #_
+ ["#." synthesis (#+ Synthesis)]]]])
(syntax: (Vector {size s.nat} elemT)
(wrap (list (` [(~+ (list.repeat size elemT))]))))
@@ -52,7 +52,7 @@
((~' wrap) ((~ g!extension) [(~+ g!input+)])))
(~' _)
- (/////.throw extension.incorrect-arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
+ (/////.throw /////extension.incorrect-arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
(arity: nullary 0)
(arity: unary 1)
@@ -71,7 +71,7 @@
Bundle
(|> bundle.empty
(bundle.install "is?" (binary (product.uncurry _.eq?/2)))
- (bundle.install "try" (unary runtime.lux//try))))
+ (bundle.install "try" (unary ///runtime.lux//try))))
(do-template [<name> <op>]
[(def: (<name> [subjectO paramO])
@@ -95,7 +95,7 @@
(def: (bit::logical-right-shift [subjectO paramO])
Binary
- (runtime.bit//logical-right-shift (_.remainder/2 (_.int +64) paramO) subjectO))
+ (///runtime.bit//logical-right-shift (_.remainder/2 (_.int +64) paramO) subjectO))
(def: bundle::bit
Bundle
@@ -193,7 +193,7 @@
(bundle.install "max" (nullary frac::max))
(bundle.install "to-int" (unary _.exact/1))
(bundle.install "encode" (unary _.number->string/1))
- (bundle.install "decode" (unary runtime.frac//decode)))))
+ (bundle.install "decode" (unary ///runtime.frac//decode)))))
(def: (text::char [subjectO paramO])
Binary
@@ -221,7 +221,7 @@
(def: (void code)
(-> Expression Computation)
- (_.begin (list code (_.string synthesis.unit))))
+ (_.begin (list code (_.string //////synthesis.unit))))
(def: bundle::io
Bundle
@@ -230,7 +230,7 @@
(bundle.install "log" (unary (|>> io::log ..void)))
(bundle.install "error" (unary _.raise/1))
(bundle.install "exit" (unary _.exit/1))
- (bundle.install "current-time" (nullary (function (_ _) (runtime.io//current-time (_.string synthesis.unit))))))))
+ (bundle.install "current-time" (nullary (function (_ _) (///runtime.io//current-time (_.string //////synthesis.unit))))))))
(def: #export bundle
Bundle
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux
index 891ef736c..dea1064e1 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux
@@ -11,18 +11,17 @@
["." list ("#/." functor)]]]
[host
["_" scheme (#+ Expression Computation Var)]]]
- [//
- ["." runtime (#+ Operation Phase)]
- ["." reference]
- ["//." case]
- ["/." //
- ["common-." reference]
- ["//." // ("#/." monad)
- [//
+ ["." // #_
+ ["#." runtime (#+ Operation Phase)]
+ ["#." reference]
+ ["#." case]
+ ["#/" //
+ ["#." reference]
+ ["#/" // ("#/." monad)
+ ["#/" // #_
[reference (#+ Register Variable)]
[analysis (#+ Variant Tuple Environment Arity Abstraction Application Analysis)]
- [synthesis (#+ Synthesis)]
- ["." name]]]]])
+ [synthesis (#+ Synthesis)]]]]])
(def: #export (apply generate [functionS argsS+])
(-> Phase (Application Synthesis) (Operation Computation))
@@ -32,7 +31,7 @@
(wrap (_.apply/* functionO argsO+))))
(def: #export capture
- (common-reference.foreign _.var))
+ (///reference.foreign _.var))
(def: (with-closure function-name inits function-definition)
(-> Text (List Expression) Computation (Operation Computation))
@@ -65,7 +64,7 @@
(///.with-anchor (_.var function-name)
(generate bodyS))))
closureO+ (: (Operation (List Expression))
- (monad.map @ (:: reference.system variable) environment))
+ (monad.map @ (:: //reference.system variable) environment))
#let [arityO (|> arity .int _.int)
apply-poly (.function (_ args func)
(_.apply/2 (_.global "apply") func args))
@@ -82,10 +81,10 @@
(_.apply/2 (_.global "apply") (_.global "values") @curried)]))
bodyO))
(_.if (|> @num-args (_.>/2 arityO))
- (let [arity-args (runtime.slice (_.int +0) arityO @curried)
- output-func-args (runtime.slice arityO
- (|> @num-args (_.-/2 arityO))
- @curried)]
+ (let [arity-args (//runtime.slice (_.int +0) arityO @curried)
+ output-func-args (//runtime.slice arityO
+ (|> @num-args (_.-/2 arityO))
+ @curried)]
(|> @function
(apply-poly arity-args)
(apply-poly output-func-args))))
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux
index a177d6290..e5038dc58 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux
@@ -10,12 +10,11 @@
["." list ("#/." functor)]]]
[host
["_" scheme (#+ Computation Var)]]]
- [//
+ ["." // #_
[runtime (#+ Operation Phase)]
- ["." reference]
- ["//." case]
- ["/." //
- ["//." //
+ ["#." case]
+ ["#/" //
+ ["#/" //
[//
[synthesis (#+ Scope Synthesis)]]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux
index 063e0c55f..a3490be46 100644
--- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux
@@ -16,11 +16,11 @@
[host
["_" scheme (#+ Expression Computation Var)]]]
["." ///
- ["//." //
- [//
+ ["#/" //
+ ["#/" // #_
[analysis (#+ Variant)]
- ["." name]
- ["." synthesis]]]])
+ ["#." name]
+ ["#." synthesis]]]])
(do-template [<name> <base>]
[(type: #export <name>
@@ -34,7 +34,7 @@
(def: prefix Text "LuxRuntime")
-(def: unit (_.string synthesis.unit))
+(def: unit (_.string /////synthesis.unit))
(def: #export variant-tag "lux-variant")
@@ -79,10 +79,10 @@
(syntax: (runtime: {[name args] declaration}
definition)
(let [implementation (code.local-identifier (format "@@" name))
- runtime (format prefix "__" (name.normalize name))
+ runtime (format prefix "__" (/////name.normalize name))
@runtime (` (_.var (~ (code.text runtime))))
argsC+ (list/map code.local-identifier args)
- argsLC+ (list/map (|>> name.normalize (format "LRV__") code.text (~) (_.var) (`))
+ argsLC+ (list/map (|>> /////name.normalize (format "LRV__") code.text (~) (_.var) (`))
args)
declaration (` ((~ (code.local-identifier name))
(~+ argsC+)))
@@ -129,7 +129,7 @@
(wrap (list (` (let [(~+ (|> vars
(list/map (function (_ var)
(list (code.local-identifier var)
- (` (_.var (~ (code.text (format "LRV__" (name.normalize var)))))))))
+ (` (_.var (~ (code.text (format "LRV__" (/////name.normalize var)))))))))
list/join))]
(~ body))))))
@@ -137,16 +137,16 @@
(with-vars [error]
(_.with-exception-handler
(_.lambda [(list error) #.None]
- (..left error))
+ (..left error))
(_.lambda [(list) #.None]
- (..right (_.apply/* op (list ..unit)))))))
+ (..right (_.apply/* op (list ..unit)))))))
(runtime: (lux//program-args program-args)
(with-vars [@loop @input @output]
(_.letrec (list [@loop (_.lambda [(list @input @output) #.None]
- (_.if (_.eqv?/2 _.nil @input)
- @output
- (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))])
+ (_.if (_.eqv?/2 _.nil @input)
+ @output
+ (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))])
(_.apply/2 @loop (_.reverse/1 program-args) ..none))))
(def: runtime//lux