aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux
diff options
context:
space:
mode:
authorEduardo Julian2019-03-13 19:31:53 -0400
committerEduardo Julian2019-03-13 19:31:53 -0400
commitd5e630c8f1db51cb493ad683f06ca9e2dd521478 (patch)
tree8354effc4129701d2d3f717ca0278d9b60363d9d /stdlib/source/lux
parent64e7676f2f4e495d64bc38a501475ccbf2b5e810 (diff)
The "translation" phase has been re-named to "generation".
Diffstat (limited to 'stdlib/source/lux')
-rw-r--r--stdlib/source/lux/tool/compiler/default/evaluation.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/default/init.lux22
-rw-r--r--stdlib/source/lux/tool/compiler/default/platform.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/generation.lux (renamed from stdlib/source/lux/tool/compiler/phase/extension/translation.lux)2
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/statement.lux50
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/case.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/case.lux)36
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/expression.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/expression.lux)22
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/extension.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/extension.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/extension/common.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/extension/host.lux)22
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/function.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/function.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/loop.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/primitive.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/reference.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/reference.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/runtime.lux)2
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/js/structure.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/reference.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/reference.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/case.jvm.lux)36
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/expression.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/expression.jvm.lux)22
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/extension.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/extension.jvm.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/common.jvm.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/host.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/host.jvm.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/function.jvm.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/loop.jvm.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/primitive.jvm.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/reference.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/reference.jvm.lux)0
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/runtime.jvm.lux)2
-rw-r--r--stdlib/source/lux/tool/compiler/phase/generation/scheme/structure.jvm.lux (renamed from stdlib/source/lux/tool/compiler/phase/translation/scheme/structure.jvm.lux)10
-rw-r--r--stdlib/source/lux/tool/compiler/program.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/statement.lux12
-rw-r--r--stdlib/source/lux/tool/interpreter.lux24
32 files changed, 174 insertions, 174 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/evaluation.lux b/stdlib/source/lux/tool/compiler/default/evaluation.lux
index 42bb10ca0..5122237a8 100644
--- a/stdlib/source/lux/tool/compiler/default/evaluation.lux
+++ b/stdlib/source/lux/tool/compiler/default/evaluation.lux
@@ -12,7 +12,7 @@
[".P" analysis
["." type]]
[".P" synthesis]
- ["." translation]
+ ["." generation]
[//
[analysis (#+ Operation)]
["." synthesis]]]])
@@ -20,12 +20,12 @@
(type: #export Eval
(-> Nat Type Code (Operation Any)))
-(def: #export (evaluator expander synthesis-state translation-state translate)
+(def: #export (evaluator expander synthesis-state generation-state generate)
(All [anchor expression statement]
(-> Expander
synthesis.State+
- (translation.State+ anchor expression statement)
- (translation.Phase anchor expression statement)
+ (generation.State+ anchor expression statement)
+ (generation.Phase anchor expression statement)
Eval))
(let [analyze (analysisP.phase expander)]
(function (eval count type exprC)
@@ -34,7 +34,7 @@
(analyze exprC))]
(phase.lift (do error.monad
[exprS (|> exprA synthesisP.phase (phase.run synthesis-state))]
- (phase.run translation-state
+ (phase.run generation-state
(do phase.monad
- [exprO (translate exprS)]
- (translation.evaluate! (format "eval" (%n count)) exprO)))))))))
+ [exprO (generate exprS)]
+ (generation.evaluate! (format "eval" (%n count)) exprO)))))))))
diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux
index 850615b37..aebb74046 100644
--- a/stdlib/source/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/lux/tool/compiler/default/init.lux
@@ -26,7 +26,7 @@
[".P" analysis
["." module]]
[".P" synthesis]
- ["." translation]
+ ["." generation]
[".P" statement]
["." extension
[".E" analysis]
@@ -60,8 +60,8 @@
[[bundle state] phase.get-state
#let [eval (evaluation.evaluator expander
(get@ [#statement.synthesis #statement.state] state)
- (get@ [#statement.translation #statement.state] state)
- (get@ [#statement.translation #statement.phase] state))]]
+ (get@ [#statement.generation #statement.state] state)
+ (get@ [#statement.generation #statement.phase] state))]]
(phase.set-state [bundle
(update@ [#statement.analysis #statement.state]
(: (-> analysis.State+ analysis.State+)
@@ -69,24 +69,24 @@
[(analysisE.bundle eval)]))
state)])))
-(def: #export (state expander host translate translation-bundle)
+(def: #export (state expander host generate generation-bundle)
(All [anchor expression statement]
(-> Expander
- (translation.Host expression statement)
- (translation.Phase anchor expression statement)
- (translation.Bundle anchor expression statement)
+ (generation.Host expression statement)
+ (generation.Phase anchor expression statement)
+ (generation.Bundle anchor expression statement)
(statement.State+ anchor expression statement)))
(let [synthesis-state [synthesisE.bundle synthesis.init]
- translation-state [translation-bundle (translation.state host)]
- eval (evaluation.evaluator expander synthesis-state translation-state translate)
+ generation-state [generation-bundle (generation.state host)]
+ eval (evaluation.evaluator expander synthesis-state generation-state generate)
analysis-state [(analysisE.bundle eval) (analysis.state ..info host)]]
[statementE.bundle
{#statement.analysis {#statement.state analysis-state
#statement.phase (analysisP.phase expander)}
#statement.synthesis {#statement.state synthesis-state
#statement.phase synthesisP.phase}
- #statement.translation {#statement.state translation-state
- #statement.phase translate}}]))
+ #statement.generation {#statement.state generation-state
+ #statement.phase generate}}]))
(type: Reader
(-> Source (Error [Source Code])))
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux
index 73b5d8764..529a4ed79 100644
--- a/stdlib/source/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/lux/tool/compiler/default/platform.lux
@@ -21,7 +21,7 @@
[macro (#+ Expander)]
## TODO: Get rid of this import ASAP
[extension (#+)]
- ["." translation]
+ ["." generation]
[analysis
["." module]]]
["." cli (#+ Configuration)]
@@ -34,9 +34,9 @@
(type: #export (Platform ! anchor expression statement)
{#&monad (Monad !)
#&file-system (file.System !)
- #host (translation.Host expression statement)
- #phase (translation.Phase anchor expression statement)
- #runtime (translation.Operation anchor expression statement Any)})
+ #host (generation.Host expression statement)
+ #phase (generation.Phase anchor expression statement)
+ #runtime (generation.Operation anchor expression statement Any)})
## (def: (write-module target-dir file-name module-name module outputs)
## (-> File Text Text Module Outputs (Process Any))
@@ -49,22 +49,22 @@
(with-expansions [<Platform> (as-is (Platform ! anchor expression statement))
<State+> (as-is (statement.State+ anchor expression statement))
- <Bundle> (as-is (translation.Bundle anchor expression statement))]
+ <Bundle> (as-is (generation.Bundle anchor expression statement))]
- (def: #export (initialize expander platform translation-bundle)
+ (def: #export (initialize expander platform generation-bundle)
(All [! anchor expression statement]
(-> Expander <Platform> <Bundle> (! (Error <State+>))))
(|> platform
(get@ #runtime)
- statement.lift-translation
+ statement.lift-generation
(phase.run' (init.state expander
(get@ #host platform)
(get@ #phase platform)
- translation-bundle))
+ generation-bundle))
(:: error.functor map product.left)
(:: (get@ #&monad platform) wrap))
- ## (case (runtimeT.translate ## (initL.compiler (io.run js.init))
+ ## (case (runtimeT.generate ## (initL.compiler (io.run js.init))
## (initL.compiler (io.run hostL.init-host))
## )
## ## (#error.Success [state disk-write])
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/translation.lux b/stdlib/source/lux/tool/compiler/phase/extension/generation.lux
index 232c8c168..467adbf35 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/translation.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/generation.lux
@@ -3,7 +3,7 @@
[//
["." bundle]
[//
- [translation (#+ Bundle)]]])
+ [generation (#+ Bundle)]]])
(def: #export bundle
Bundle
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
index 4f5bdb922..83e7320d8 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
@@ -18,25 +18,25 @@
[analysis
["." module]
["." type]]
- ["." translation]
+ ["." generation]
[//
["." analysis]
["." synthesis (#+ Synthesis)]
["." statement (#+ Operation Handler Bundle)]]]])
## TODO: Inline "evaluate!'" into "evaluate!" ASAP
-(def: (evaluate!' translate code//type codeS)
+(def: (evaluate!' generate code//type codeS)
(All [anchor expression statement]
- (-> (translation.Phase anchor expression statement)
+ (-> (generation.Phase anchor expression statement)
Type
Synthesis
(Operation anchor expression statement [Type expression Any])))
- (statement.lift-translation
- (translation.with-buffer
+ (statement.lift-generation
+ (generation.with-buffer
(do ///.monad
- [codeT (translate codeS)
- count translation.next
- codeV (translation.evaluate! (format "evaluate" (%n count)) codeT)]
+ [codeT (generate codeS)
+ count generation.next
+ codeV (generation.evaluate! (format "evaluate" (%n count)) codeT)]
(wrap [code//type codeT codeV])))))
(def: (evaluate! type codeC)
@@ -46,7 +46,7 @@
[state (//.lift ///.get-state)
#let [analyse (get@ [#statement.analysis #statement.phase] state)
synthesize (get@ [#statement.synthesis #statement.phase] state)
- translate (get@ [#statement.translation #statement.phase] state)]
+ generate (get@ [#statement.generation #statement.phase] state)]
[_ code//type codeA] (statement.lift-analysis
(analysis.with-scope
(type.with-fresh-env
@@ -56,21 +56,21 @@
(wrap [type codeA]))))))
codeS (statement.lift-synthesis
(synthesize codeA))]
- (evaluate!' translate code//type codeS)))
+ (evaluate!' generate code//type codeS)))
## TODO: Inline "definition'" into "definition" ASAP
-(def: (definition' translate name code//type codeS)
+(def: (definition' generate name code//type codeS)
(All [anchor expression statement]
- (-> (translation.Phase anchor expression statement)
+ (-> (generation.Phase anchor expression statement)
Name
Type
Synthesis
(Operation anchor expression statement [Type expression Text Any])))
- (statement.lift-translation
- (translation.with-buffer
+ (statement.lift-generation
+ (generation.with-buffer
(do ///.monad
- [codeT (translate codeS)
- codeN+V (translation.define! name codeT)]
+ [codeT (generate codeS)
+ codeN+V (generation.define! name codeT)]
(wrap [code//type codeT codeN+V])))))
(def: (definition name ?type codeC)
@@ -81,7 +81,7 @@
[state (//.lift ///.get-state)
#let [analyse (get@ [#statement.analysis #statement.phase] state)
synthesize (get@ [#statement.synthesis #statement.phase] state)
- translate (get@ [#statement.translation #statement.phase] state)]
+ generate (get@ [#statement.generation #statement.phase] state)]
[_ code//type codeA] (statement.lift-analysis
(analysis.with-scope
(type.with-fresh-env
@@ -100,7 +100,7 @@
(wrap [code//type codeA]))))))
codeS (statement.lift-synthesis
(synthesize codeA))]
- (definition' translate name code//type codeS)))
+ (definition' generate name code//type codeS)))
(def: (define short-name type annotations value)
(All [anchor expression statement]
@@ -136,8 +136,8 @@
valueC)
_ (..define short-name value//type annotationsV valueV)
#let [_ (log! (format "Definition " (%name full-name)))]]
- (statement.lift-translation
- (translation.learn full-name valueN)))
+ (statement.lift-generation
+ (generation.learn full-name valueN)))
_
(///.throw //.invalid-syntax [extension-name]))))
@@ -199,10 +199,10 @@
_
(///.throw //.invalid-syntax [extension-name]))))]
- [def::analysis analysis.Handler statement.lift-analysis]
- [def::synthesis synthesis.Handler statement.lift-synthesis]
- [def::translation (translation.Handler anchor expression statement) statement.lift-translation]
- [def::statement (statement.Handler anchor expression statement) (<|)]
+ [def::analysis analysis.Handler statement.lift-analysis]
+ [def::synthesis synthesis.Handler statement.lift-synthesis]
+ [def::generation (generation.Handler anchor expression statement) statement.lift-generation]
+ [def::statement (statement.Handler anchor expression statement) (<|)]
)
(def: bundle::def
@@ -213,7 +213,7 @@
(dictionary.put "alias" def::alias)
(dictionary.put "analysis" def::analysis)
(dictionary.put "synthesis" def::synthesis)
- (dictionary.put "translation" def::translation)
+ (dictionary.put "generation" def::generation)
(dictionary.put "statement" def::statement)
)))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation.lux b/stdlib/source/lux/tool/compiler/phase/generation.lux
index 99a4c5517..99a4c5517 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux
index fc25255df..0bafcd3c0 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/case.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/case.lux
@@ -25,12 +25,12 @@
(def: #export register
(reference.local _.var))
-(def: #export (let translate [valueS register bodyS])
+(def: #export (let generate [valueS register bodyS])
(-> Phase [Synthesis Register Synthesis]
(Operation Computation))
(do ////.monad
- [valueO (translate valueS)
- bodyO (translate bodyS)]
+ [valueO (generate valueS)
+ bodyO (generate bodyS)]
## TODO: Find some way to do 'let' without paying the price of the closure.
(wrap (_.apply/* (<| (_.closure (list))
($_ _.then
@@ -38,11 +38,11 @@
(_.return bodyO)))
(list)))))
-(def: #export (record-get translate valueS pathP)
+(def: #export (record-get generate valueS pathP)
(-> Phase Synthesis (List [Nat Bit])
(Operation Expression))
(do ////.monad
- [valueO (translate valueS)]
+ [valueO (generate valueS)]
(wrap (list/fold (function (_ [idx tail?] source)
(.let [method (.if tail?
//runtime.product//right
@@ -51,13 +51,13 @@
valueO
pathP))))
-(def: #export (if translate [testS thenS elseS])
+(def: #export (if generate [testS thenS elseS])
(-> Phase [Synthesis Synthesis Synthesis]
(Operation Computation))
(do ////.monad
- [testO (translate testS)
- thenO (translate thenS)
- elseO (translate elseS)]
+ [testO (generate testS)
+ thenO (generate thenS)
+ elseO (generate elseS)]
(wrap (_.? testO thenO elseO))))
(def: @savepoint (_.var "lux_pm_cursor_savepoint"))
@@ -91,12 +91,12 @@
(exception: #export unrecognized-path)
-(def: (pattern-matching' translate pathP)
+(def: (pattern-matching' generate pathP)
(-> Phase Path (Operation Statement))
(.case pathP
(^ (synthesis.path/then bodyS))
(do ////.monad
- [body! (translate bodyS)]
+ [body! (generate bodyS)]
(wrap (_.return body!)))
#synthesis.Pop
@@ -133,8 +133,8 @@
(^template [<tag> <computation>]
(^ (<tag> leftP rightP))
(do ////.monad
- [left! (pattern-matching' translate leftP)
- right! (pattern-matching' translate rightP)]
+ [left! (pattern-matching' generate leftP)
+ right! (pattern-matching' generate rightP)]
(wrap <computation>)))
([synthesis.path/seq (_.then left! right!)]
[synthesis.path/alt ($_ _.then
@@ -149,20 +149,20 @@
_
(////.throw unrecognized-path [])))
-(def: (pattern-matching translate pathP)
+(def: (pattern-matching generate pathP)
(-> Phase Path (Operation Statement))
(do ////.monad
- [pattern-matching! (pattern-matching' translate pathP)]
+ [pattern-matching! (pattern-matching' generate pathP)]
(wrap ($_ _.then
(_.do-while _.false
pattern-matching!)
(_.throw (_.string "Invalid expression for pattern-matching."))))))
-(def: #export (case translate [valueS pathP])
+(def: #export (case generate [valueS pathP])
(-> Phase [Synthesis Path] (Operation Computation))
(do ////.monad
- [stack-init (translate valueS)
- path! (pattern-matching translate pathP)
+ [stack-init (generate valueS)
+ path! (pattern-matching generate pathP)
#let [closure (<| (_.closure (list))
($_ _.then
(_.declare @temp)
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/expression.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/expression.lux
index 822f51e35..e1d6dbbdb 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/expression.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/expression.lux
@@ -15,7 +15,7 @@
[//
["." synthesis]]]])
-(def: #export (translate synthesis)
+(def: #export (generate synthesis)
Phase
(case synthesis
(^template [<tag> <generator>]
@@ -27,34 +27,34 @@
[synthesis.text primitive.text])
(^ (synthesis.variant variantS))
- (structure.variant translate variantS)
+ (structure.variant generate variantS)
(^ (synthesis.tuple members))
- (structure.tuple translate members)
+ (structure.tuple generate members)
(#synthesis.Reference value)
(:: reference.system reference value)
(^ (synthesis.branch/case case))
- (case.case translate case)
+ (case.case generate case)
(^ (synthesis.branch/let let))
- (case.let translate let)
+ (case.let generate let)
(^ (synthesis.branch/if if))
- (case.if translate if)
+ (case.if generate if)
(^ (synthesis.loop/scope scope))
- (loop.scope translate scope)
+ (loop.scope generate scope)
(^ (synthesis.loop/recur updates))
- (loop.recur translate updates)
+ (loop.recur generate updates)
(^ (synthesis.function/abstraction abstraction))
- (function.function translate abstraction)
+ (function.function generate abstraction)
(^ (synthesis.function/apply application))
- (function.apply translate application)
+ (function.apply generate application)
(#synthesis.Extension extension)
- (extension.apply translate extension)))
+ (extension.apply generate extension)))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/extension.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension.lux
index a40b4953f..a40b4953f 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/extension.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux
index 98ef827a8..98ef827a8 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/extension/common.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/extension/host.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux
index 8091f7fee..519852967 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/extension/host.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux
@@ -26,7 +26,7 @@
[js//object (_.object (list))]
)
-(def: (js//global name translate inputs)
+(def: (js//global name generate inputs)
Handler
(case inputs
(^ (list (synthesis.text global)))
@@ -35,13 +35,13 @@
_
(/////.throw extension.incorrect-syntax name)))
-(def: (js//call name translate inputs)
+(def: (js//call name generate inputs)
Handler
(case inputs
(^ (list& functionS argsS+))
(do /////.monad
- [functionJS (translate functionS)
- argsJS+ (monad.map @ translate argsS+)]
+ [functionJS (generate functionS)
+ argsJS+ (monad.map @ generate argsS+)]
(wrap (_.apply/* functionJS argsJS+)))
_
@@ -57,26 +57,26 @@
(bundle.install "global" js//global)
(bundle.install "call" js//call)))
-(def: (object//new name translate inputs)
+(def: (object//new name generate inputs)
Handler
(case inputs
(^ (list& constructorS argsS+))
(do /////.monad
- [constructorJS (translate constructorS)
- argsJS+ (monad.map @ translate argsS+)]
+ [constructorJS (generate constructorS)
+ argsJS+ (monad.map @ generate argsS+)]
(wrap (_.new constructorJS argsJS+)))
_
(/////.throw extension.incorrect-syntax name)))
-(def: (object//call name translate inputs)
+(def: (object//call name generate inputs)
Handler
(case inputs
(^ (list& objectS methodS argsS+))
(do /////.monad
- [objectJS (translate objectS)
- methodJS (translate methodS)
- argsJS+ (monad.map @ translate argsS+)]
+ [objectJS (generate objectS)
+ methodJS (generate methodS)
+ argsJS+ (monad.map @ generate argsS+)]
(wrap (|> objectJS
(_.at methodJS)
(_.do "apply" (list& objectJS argsJS+)))))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/function.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux
index 0d0d659ab..ca647a81a 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/function.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/function.lux
@@ -24,11 +24,11 @@
[synthesis (#+ Synthesis)]
["." name]]]]])
-(def: #export (apply translate [functionS argsS+])
+(def: #export (apply generate [functionS argsS+])
(-> Phase (Application Synthesis) (Operation Computation))
(do ////.monad
- [functionO (translate functionS)
- argsO+ (monad.map @ translate argsS+)]
+ [functionO (generate functionS)
+ argsO+ (monad.map @ generate argsS+)]
(wrap (_.apply/* functionO argsO+))))
(def: #export capture
@@ -54,14 +54,14 @@
(def: @@arguments (_.var "arguments"))
-(def: #export (function translate [environment arity bodyS])
+(def: #export (function generate [environment arity bodyS])
(-> Phase (Abstraction Synthesis) (Operation Computation))
(do ////.monad
[[function-name bodyO] (///.with-context
(do @
[function-name ///.context]
(///.with-anchor (_.var function-name)
- (translate bodyS))))
+ (generate bodyS))))
closureO+ (: (Operation (List Expression))
(monad.map @ (:: reference.system variable) environment))
#let [arityO (|> arity .int _.i32)
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/loop.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux
index cbb032153..4e3c7d8a9 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/loop.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/loop.lux
@@ -21,12 +21,12 @@
(def: @scope (_.var "scope"))
-(def: #export (scope translate [start initsS+ bodyS])
+(def: #export (scope generate [start initsS+ bodyS])
(-> Phase (Scope Synthesis) (Operation Computation))
(do ////.monad
- [initsO+ (monad.map @ translate initsS+)
+ [initsO+ (monad.map @ generate initsS+)
bodyO (///.with-anchor @scope
- (translate bodyS))
+ (generate bodyS))
#let [closure (_.function @scope
(|> initsS+
list.enumerate
@@ -34,9 +34,9 @@
(_.return bodyO))]]
(wrap (_.apply/* closure initsO+))))
-(def: #export (recur translate argsS+)
+(def: #export (recur generate argsS+)
(-> Phase (List Synthesis) (Operation Computation))
(do ////.monad
[@scope ///.anchor
- argsO+ (monad.map @ translate argsS+)]
+ argsO+ (monad.map @ generate argsS+)]
(wrap (_.apply/* @scope argsO+))))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/primitive.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux
index 139fcb191..139fcb191 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/primitive.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/primitive.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/reference.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/reference.lux
index 9f8555788..9f8555788 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/reference.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/reference.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux
index 4e95e06b3..fe400e403 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux
@@ -748,7 +748,7 @@
(def: #export artifact Text (format prefix ".js"))
-(def: #export translate
+(def: #export generate
(Operation Any)
(///.with-buffer
(do ////.monad
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/js/structure.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux
index 732f48bb9..623516cdb 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/js/structure.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/js/structure.lux
@@ -12,25 +12,25 @@
[analysis (#+ Variant Tuple)]
["." synthesis (#+ Synthesis)]]]])
-(def: #export (tuple translate elemsS+)
+(def: #export (tuple generate elemsS+)
(-> Phase (Tuple Synthesis) (Operation Expression))
(case elemsS+
#.Nil
(:: ////.monad wrap (//primitive.text synthesis.unit))
(#.Cons singletonS #.Nil)
- (translate singletonS)
+ (generate singletonS)
_
(do ////.monad
- [elemsT+ (monad.map @ translate elemsS+)]
+ [elemsT+ (monad.map @ generate elemsS+)]
(wrap (_.array elemsT+)))))
-(def: #export (variant translate [lefts right? valueS])
+(def: #export (variant generate [lefts right? valueS])
(-> Phase (Variant Synthesis) (Operation Expression))
(:: ////.monad map
(//runtime.variant (_.i32 (.int (if right?
(inc lefts)
lefts)))
(//runtime.flag right?))
- (translate valueS)))
+ (generate valueS)))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/reference.lux b/stdlib/source/lux/tool/compiler/phase/generation/reference.lux
index 878d96e83..878d96e83 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/reference.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/reference.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/case.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux
index 6d5cf911b..d0f047c9f 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/case.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/case.jvm.lux
@@ -25,20 +25,20 @@
(def: #export register
(common-reference.local _.var))
-(def: #export (let translate [valueS register bodyS])
+(def: #export (let generate [valueS register bodyS])
(-> Phase [Synthesis Register Synthesis]
(Operation Computation))
(do ////.monad
- [valueO (translate valueS)
- bodyO (translate bodyS)]
+ [valueO (generate valueS)
+ bodyO (generate bodyS)]
(wrap (_.let (list [(..register register) valueO])
bodyO))))
-(def: #export (record-get translate valueS pathP)
+(def: #export (record-get generate valueS pathP)
(-> Phase Synthesis (List [Nat Bit])
(Operation Expression))
(do ////.monad
- [valueO (translate valueS)]
+ [valueO (generate valueS)]
(wrap (list/fold (function (_ [idx tail?] source)
(.let [method (.if tail?
runtime.product//right
@@ -47,13 +47,13 @@
valueO
pathP))))
-(def: #export (if translate [testS thenS elseS])
+(def: #export (if generate [testS thenS elseS])
(-> Phase [Synthesis Synthesis Synthesis]
(Operation Computation))
(do ////.monad
- [testO (translate testS)
- thenO (translate thenS)
- elseO (translate elseS)]
+ [testO (generate testS)
+ thenO (generate thenS)
+ elseO (generate elseS)]
(wrap (_.if testO thenO elseO))))
(def: @savepoint (_.var "lux_pm_cursor_savepoint"))
@@ -102,11 +102,11 @@
handler
(_.raise/1 @alt-error))))
-(def: (pattern-matching' translate pathP)
+(def: (pattern-matching' generate pathP)
(-> Phase Path (Operation Expression))
(.case pathP
(^ (synthesis.path/then bodyS))
- (translate bodyS)
+ (generate bodyS)
#synthesis.Pop
(/////wrap pop-cursor!)
@@ -142,8 +142,8 @@
(^template [<tag> <computation>]
(^ (<tag> leftP rightP))
(do ////.monad
- [leftO (pattern-matching' translate leftP)
- rightO (pattern-matching' translate rightP)]
+ [leftO (pattern-matching' generate leftP)
+ rightO (pattern-matching' generate rightP)]
(wrap <computation>)))
([synthesis.path/seq (_.begin (list leftO
rightO))]
@@ -157,19 +157,19 @@
_
(////.throw unrecognized-path [])))
-(def: (pattern-matching translate pathP)
+(def: (pattern-matching generate pathP)
(-> Phase Path (Operation Computation))
(do ////.monad
- [pattern-matching! (pattern-matching' translate pathP)]
+ [pattern-matching! (pattern-matching' generate pathP)]
(wrap (_.with-exception-handler
(pm-catch (_.raise/1 (_.string "Invalid expression for pattern-matching.")))
(_.lambda [(list) #.None]
pattern-matching!)))))
-(def: #export (case translate [valueS pathP])
+(def: #export (case generate [valueS pathP])
(-> Phase [Synthesis Path] (Operation Computation))
(do ////.monad
- [valueO (translate valueS)]
+ [valueO (generate valueS)]
(<| (:: @ map (_.let (list [@cursor (_.list/* (list valueO))]
[@savepoint (_.list/* (list))])))
- (pattern-matching translate pathP))))
+ (pattern-matching generate pathP))))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/expression.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/expression.jvm.lux
index 76b206124..9b26ba7ab 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/expression.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/expression.jvm.lux
@@ -14,7 +14,7 @@
["." synthesis]
["." extension]]])
-(def: #export (translate synthesis)
+(def: #export (generate synthesis)
Phase
(case synthesis
(^template [<tag> <generator>]
@@ -26,34 +26,34 @@
[synthesis.text primitive.text])
(^ (synthesis.variant variantS))
- (structure.variant translate variantS)
+ (structure.variant generate variantS)
(^ (synthesis.tuple members))
- (structure.tuple translate members)
+ (structure.tuple generate members)
(#synthesis.Reference value)
(:: reference.system reference value)
(^ (synthesis.branch/case case))
- (case.case translate case)
+ (case.case generate case)
(^ (synthesis.branch/let let))
- (case.let translate let)
+ (case.let generate let)
(^ (synthesis.branch/if if))
- (case.if translate if)
+ (case.if generate if)
(^ (synthesis.loop/scope scope))
- (loop.scope translate scope)
+ (loop.scope generate scope)
(^ (synthesis.loop/recur updates))
- (loop.recur translate updates)
+ (loop.recur generate updates)
(^ (synthesis.function/abstraction abstraction))
- (function.function translate abstraction)
+ (function.function generate abstraction)
(^ (synthesis.function/apply application))
- (function.apply translate application)
+ (function.apply generate application)
(#synthesis.Extension extension)
- (extension.apply translate extension)))
+ (extension.apply generate extension)))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension.jvm.lux
index a40b4953f..a40b4953f 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension.jvm.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/common.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux
index d430aba24..d430aba24 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/common.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/host.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/host.jvm.lux
index b8b2b7612..b8b2b7612 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/extension/host.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/host.jvm.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/function.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux
index bef6af902..e6069660b 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/function.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/function.jvm.lux
@@ -24,11 +24,11 @@
[reference (#+ Register Variable)]
["." name]]]]])
-(def: #export (apply translate [functionS argsS+])
+(def: #export (apply generate [functionS argsS+])
(-> Phase (Application Synthesis) (Operation Computation))
(do ////.monad
- [functionO (translate functionS)
- argsO+ (monad.map @ translate argsS+)]
+ [functionO (generate functionS)
+ argsO+ (monad.map @ generate argsS+)]
(wrap (_.apply/* functionO argsO+))))
(def: #export capture
@@ -56,14 +56,14 @@
(def: input
(|>> inc //case.register))
-(def: #export (function translate [environment arity bodyS])
+(def: #export (function generate [environment arity bodyS])
(-> Phase (Abstraction Synthesis) (Operation Computation))
(do ////.monad
[[function-name bodyO] (///.with-context
(do @
[function-name ///.context]
(///.with-anchor (_.var function-name)
- (translate bodyS))))
+ (generate bodyS))))
closureO+ (: (Operation (List Expression))
(monad.map @ (:: reference.system variable) environment))
#let [arityO (|> arity .int _.int)
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/loop.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux
index e1db0477c..0e4adcf03 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/loop.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/loop.jvm.lux
@@ -20,12 +20,12 @@
(def: @scope (_.var "scope"))
-(def: #export (scope translate [start initsS+ bodyS])
+(def: #export (scope generate [start initsS+ bodyS])
(-> Phase (Scope Synthesis) (Operation Computation))
(do ////.monad
- [initsO+ (monad.map @ translate initsS+)
+ [initsO+ (monad.map @ generate initsS+)
bodyO (///.with-anchor @scope
- (translate bodyS))]
+ (generate bodyS))]
(wrap (_.letrec (list [@scope (_.lambda [(|> initsS+
list.enumerate
(list/map (|>> product.left (n/+ start) //case.register)))
@@ -33,9 +33,9 @@
bodyO)])
(_.apply/* @scope initsO+)))))
-(def: #export (recur translate argsS+)
+(def: #export (recur generate argsS+)
(-> Phase (List Synthesis) (Operation Computation))
(do ////.monad
[@scope ///.anchor
- argsO+ (monad.map @ translate argsS+)]
+ argsO+ (monad.map @ generate argsS+)]
(wrap (_.apply/* @scope argsO+))))
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/primitive.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux
index d53a0691e..d53a0691e 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/primitive.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/reference.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/reference.jvm.lux
index b28cb1898..b28cb1898 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/reference.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/reference.jvm.lux
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/runtime.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux
index 904f40726..136e2ff2e 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/runtime.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux
@@ -313,7 +313,7 @@
runtime//io
)))
-(def: #export translate
+(def: #export generate
(Operation Any)
(///.with-buffer
(do ////.monad
diff --git a/stdlib/source/lux/tool/compiler/phase/translation/scheme/structure.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/structure.jvm.lux
index d90569d9c..c586f0706 100644
--- a/stdlib/source/lux/tool/compiler/phase/translation/scheme/structure.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/structure.jvm.lux
@@ -11,22 +11,22 @@
[analysis (#+ Variant Tuple)]
["." synthesis (#+ Synthesis)]]])
-(def: #export (tuple translate elemsS+)
+(def: #export (tuple generate elemsS+)
(-> Phase (Tuple Synthesis) (Operation Expression))
(case elemsS+
#.Nil
(:: ///.monad wrap (primitive.text synthesis.unit))
(#.Cons singletonS #.Nil)
- (translate singletonS)
+ (generate singletonS)
_
(do ///.monad
- [elemsT+ (monad.map @ translate elemsS+)]
+ [elemsT+ (monad.map @ generate elemsS+)]
(wrap (_.vector/* elemsT+)))))
-(def: #export (variant translate [lefts right? valueS])
+(def: #export (variant generate [lefts right? valueS])
(-> Phase (Variant Synthesis) (Operation Expression))
(do ///.monad
- [valueT (translate valueS)]
+ [valueT (generate valueS)]
(wrap (runtime.variant [lefts right? valueT]))))
diff --git a/stdlib/source/lux/tool/compiler/program.lux b/stdlib/source/lux/tool/compiler/program.lux
index 9de17b5df..4a079cc0f 100644
--- a/stdlib/source/lux/tool/compiler/program.lux
+++ b/stdlib/source/lux/tool/compiler/program.lux
@@ -18,7 +18,7 @@
["." statement]
[phase
[macro (#+ Expander)]
- ["." translation]]
+ ["." generation]]
[default
["." platform (#+ Platform)]
["." syntax]]
@@ -62,7 +62,7 @@
(All [anchor expression statement]
(-> Expander
(IO (Platform IO anchor expression statement))
- (translation.Bundle anchor expression statement)
+ (generation.Bundle anchor expression statement)
Service
(IO Any)))
(do io.monad
diff --git a/stdlib/source/lux/tool/compiler/statement.lux b/stdlib/source/lux/tool/compiler/statement.lux
index c4a8b56b1..7f251c42d 100644
--- a/stdlib/source/lux/tool/compiler/statement.lux
+++ b/stdlib/source/lux/tool/compiler/statement.lux
@@ -4,7 +4,7 @@
["." analysis]
["." synthesis]
["." phase
- ["." translation]
+ ["." generation]
["." extension]]])
(type: #export (Component state phase)
@@ -16,8 +16,8 @@
analysis.Phase)
#synthesis (Component synthesis.State+
synthesis.Phase)
- #translation (Component (translation.State+ anchor expression statement)
- (translation.Phase anchor expression statement))})
+ #generation (Component (generation.State+ anchor expression statement)
+ (generation.Phase anchor expression statement))})
(do-template [<special> <general>]
[(type: #export (<special> anchor expression statement)
@@ -40,7 +40,7 @@
(set@ [<component> #..state])]
operation)))]
- [lift-analysis #..analysis analysis.Operation]
- [lift-synthesis #..synthesis synthesis.Operation]
- [lift-translation #..translation (translation.Operation anchor expression statement)]
+ [lift-analysis #..analysis analysis.Operation]
+ [lift-synthesis #..synthesis synthesis.Operation]
+ [lift-generation #..generation (generation.Operation anchor expression statement)]
)
diff --git a/stdlib/source/lux/tool/interpreter.lux b/stdlib/source/lux/tool/interpreter.lux
index d2fbccfdc..4edc6067a 100644
--- a/stdlib/source/lux/tool/interpreter.lux
+++ b/stdlib/source/lux/tool/interpreter.lux
@@ -14,7 +14,7 @@
["." analysis
["." module]
["." type]]
- ["." translation]
+ ["." generation]
["." statement (#+ State+ Operation)
["." total]]
["." extension]]
@@ -60,15 +60,15 @@
[_ (module.create 0 ..module)]
(analysis.set-current-module ..module))))
-(def: (initialize Monad<!> Console<!> platform configuration translation-bundle)
+(def: (initialize Monad<!> Console<!> platform configuration generation-bundle)
(All [! anchor expression statement]
(-> (Monad !)
(Console !) (Platform ! anchor expression statement)
Configuration
- (translation.Bundle anchor expression statement)
+ (generation.Bundle anchor expression statement)
(! (State+ anchor expression statement))))
(do Monad<!>
- [state (platform.initialize platform translation-bundle)
+ [state (platform.initialize platform generation-bundle)
state (platform.compile platform
(set@ #cli.module syntax.prelude configuration)
(set@ [#extension.state
@@ -99,7 +99,7 @@
[state (extension.lift phase.get-state)
#let [analyse (get@ [#statement.analysis #statement.phase] state)
synthesize (get@ [#statement.synthesis #statement.phase] state)
- translate (get@ [#statement.translation #statement.phase] state)]
+ generate (get@ [#statement.generation #statement.phase] state)]
[_ codeT codeA] (statement.lift-analysis
(analysis.with-scope
(type.with-fresh-env
@@ -111,12 +111,12 @@
(wrap [codeT codeA])))))
codeS (statement.lift-synthesis
(synthesize codeA))]
- (statement.lift-translation
- (translation.with-buffer
+ (statement.lift-generation
+ (generation.with-buffer
(do @
- [codeH (translate codeS)
- count translation.next
- codeV (translation.evaluate! (format "interpretation_" (%n count)) codeH)]
+ [codeH (generate codeS)
+ count generation.next
+ codeV (generation.evaluate! (format "interpretation_" (%n count)) codeH)]
(wrap [codeT codeV]))))))
(def: (interpret configuration code)
@@ -186,12 +186,12 @@
(set@ #source source'))
representation]))))
-(def: #export (run Monad<!> Console<!> platform configuration translation-bundle)
+(def: #export (run Monad<!> Console<!> platform configuration generation-bundle)
(All [! anchor expression statement]
(-> (Monad !)
(Console !) (Platform ! anchor expression statement)
Configuration
- (translation.Bundle anchor expression statement)
+ (generation.Bundle anchor expression statement)
(! Any)))
(do Monad<!>
[state (initialize Monad<!> Console<!> platform configuration)]