aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool/compiler
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/default/init.lux130
-rw-r--r--stdlib/source/lux/tool/compiler/default/platform.lux27
-rw-r--r--stdlib/source/lux/tool/compiler/meta/cache.lux37
-rw-r--r--stdlib/source/lux/tool/compiler/meta/io/context.lux24
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis.lux26
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/case.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/function.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/inference.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/module.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/reference.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/scope.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/structure.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/phase/analysis/type.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux130
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux250
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/statement.lux88
-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
-rw-r--r--stdlib/source/lux/tool/compiler/phase/statement.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/phase/synthesis.lux55
-rw-r--r--stdlib/source/lux/tool/compiler/phase/synthesis/case.lux42
-rw-r--r--stdlib/source/lux/tool/compiler/phase/synthesis/function.lux34
-rw-r--r--stdlib/source/lux/tool/compiler/phase/synthesis/loop.lux44
-rw-r--r--stdlib/source/lux/tool/compiler/synthesis.lux10
36 files changed, 671 insertions, 677 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux
index 8ff684755..a00d4b5cd 100644
--- a/stdlib/source/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/lux/tool/compiler/default/init.lux
@@ -14,14 +14,14 @@
[world
["." file]]]
["." //
- ["." syntax (#+ Aliases)]
- ["." evaluation]
- ["/." // (#+ Instancer)
- ["." analysis]
- ["." synthesis]
- ["." statement]
- ["." host]
- ["." phase
+ ["#." syntax (#+ Aliases)]
+ ["#." evaluation]
+ ["#/" // (#+ Instancer)
+ ["#." analysis]
+ ["#." synthesis]
+ ["#." statement]
+ ["#." host]
+ ["#." phase
[macro (#+ Expander)]
[".P" analysis
["." module]]
@@ -41,33 +41,33 @@
(def: #export info
Info
- {#.target (`` (for {(~~ (static host.common-lisp)) host.common-lisp
- (~~ (static host.js)) host.js
- (~~ (static host.jvm)) host.jvm
- (~~ (static host.lua)) host.lua
- (~~ (static host.php)) host.php
- (~~ (static host.python)) host.python
- (~~ (static host.r)) host.r
- (~~ (static host.ruby)) host.ruby
- (~~ (static host.scheme)) host.scheme}))
+ {#.target (`` (for {(~~ (static ///host.common-lisp)) ///host.common-lisp
+ (~~ (static ///host.js)) ///host.js
+ (~~ (static ///host.jvm)) ///host.jvm
+ (~~ (static ///host.lua)) ///host.lua
+ (~~ (static ///host.php)) ///host.php
+ (~~ (static ///host.python)) ///host.python
+ (~~ (static ///host.r)) ///host.r
+ (~~ (static ///host.ruby)) ///host.ruby
+ (~~ (static ///host.scheme)) ///host.scheme}))
#.version //.version
#.mode #.Build})
(def: (refresh expander)
(All [anchor expression statement]
- (-> Expander (statement.Operation anchor expression statement Any)))
- (do phase.monad
- [[bundle state] phase.get-state
- #let [eval (evaluation.evaluator expander
- (get@ [#statement.synthesis #statement.state] 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+)
- (|>> product.right
- [(analysisE.bundle eval)]))
- state)])))
+ (-> Expander (///statement.Operation anchor expression statement Any)))
+ (do ///phase.monad
+ [[bundle state] ///phase.get-state
+ #let [eval (//evaluation.evaluator expander
+ (get@ [#///statement.synthesis #///statement.state] 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+)
+ (|>> product.right
+ [(analysisE.bundle eval)]))
+ state)])))
(def: #export (state expander host generate generation-bundle)
(All [anchor expression statement]
@@ -75,31 +75,31 @@
(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]
+ (///statement.State+ anchor expression statement)))
+ (let [synthesis-state [synthesisE.bundle ///synthesis.init]
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)]]
+ 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.generation {#statement.state generation-state
- #statement.phase generate}}]))
+ {#///statement.analysis {#///statement.state analysis-state
+ #///statement.phase (analysisP.phase expander)}
+ #///statement.synthesis {#///statement.state synthesis-state
+ #///statement.phase synthesisP.phase}
+ #///statement.generation {#///statement.state generation-state
+ #///statement.phase generate}}]))
(type: Reader
(-> Source (Error [Source Code])))
(def: (reader current-module aliases)
- (-> Module Aliases (analysis.Operation Reader))
+ (-> Module Aliases (///analysis.Operation Reader))
(function (_ [bundle state])
(let [[cursor offset source-code] (get@ #.source state)]
(#error.Success [[bundle state]
- (syntax.parse current-module aliases ("lux text size" source-code))]))))
+ (//syntax.parse current-module aliases ("lux text size" source-code))]))))
(def: (read reader)
- (-> Reader (analysis.Operation Code))
+ (-> Reader (///analysis.Operation Code))
(function (_ [bundle compiler])
(case (reader (get@ #.source compiler))
(#error.Failure error)
@@ -113,37 +113,37 @@
output])))))
(with-expansions [<Operation> (as-is (All [anchor expression statement]
- (statement.Operation anchor expression statement Any)))]
+ (///statement.Operation anchor expression statement Any)))]
(def: (begin dependencies hash input)
(-> (List Module) Nat ///.Input <Operation>)
- (statement.lift-analysis
- (do phase.monad
+ (///statement.lift-analysis
+ (do ///phase.monad
[#let [module (get@ #///.module input)]
_ (module.create hash module)
- _ (analysis.set-current-module module)
+ _ (///analysis.set-current-module module)
_ (monad.map @ module.import dependencies)]
- (analysis.set-source-code (analysis.source (get@ #///.module input) (get@ #///.code input))))))
+ (///analysis.set-source-code (///analysis.source (get@ #///.module input) (get@ #///.code input))))))
(def: end
(-> Module <Operation>)
(|>> module.set-compiled
- statement.lift-analysis))
+ ///statement.lift-analysis))
(def: (iteration expander reader)
(-> Expander Reader <Operation>)
(let [execute (statementP.phase expander)]
- (do phase.monad
- [code (statement.lift-analysis
+ (do ///phase.monad
+ [code (///statement.lift-analysis
(..read reader))
_ (execute code)]
(..refresh expander))))
(def: (loop expander module)
(-> Expander Module <Operation>)
- (do phase.monad
- [reader (statement.lift-analysis
- (..reader module syntax.no-aliases))]
+ (do ///phase.monad
+ [reader (///statement.lift-analysis
+ (..reader module //syntax.no-aliases))]
(function (_ state)
(.loop [state state]
(case (..iteration expander reader state)
@@ -151,13 +151,13 @@
(recur state')
(#error.Failure error)
- (if (ex.match? syntax.end-of-file error)
+ (if (ex.match? //syntax.end-of-file error)
(#error.Success [state []])
(ex.with-stack ///.cannot-compile module (#error.Failure error))))))))
(def: (compile expander dependencies hash input)
(-> Expander (List Module) Nat ///.Input <Operation>)
- (do phase.monad
+ (do ///phase.monad
[#let [module (get@ #///.module input)]
_ (..begin dependencies hash input)
_ (..loop expander module)]
@@ -173,21 +173,21 @@
(def: #export (compiler expander prelude module)
(-> Expander Module Module
(All [anchor expression statement]
- (Instancer (statement.State+ anchor expression statement) .Module)))
+ (Instancer (///statement.State+ anchor expression statement) .Module)))
(function (_ key parameters input)
(let [hash (text/hash (get@ #///.code input))
dependencies (default-dependencies prelude input)]
{#///.dependencies dependencies
#///.process (function (_ state archive)
(do error.monad
- [[state' analysis-module] (phase.run' state
- (: (All [anchor expression statement]
- (statement.Operation anchor expression statement .Module))
- (do phase.monad
- [_ (compile expander dependencies hash input)]
- (statement.lift-analysis
- (extension.lift
- macro.current-module)))))
+ [[state' analysis-module] (///phase.run' state
+ (: (All [anchor expression statement]
+ (///statement.Operation anchor expression statement .Module))
+ (do ///phase.monad
+ [_ (compile expander dependencies hash input)]
+ (///statement.lift-analysis
+ (extension.lift
+ macro.current-module)))))
#let [descriptor {#descriptor.hash hash
#descriptor.name (get@ #///.module input)
#descriptor.file (get@ #///.file input)
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux
index 89a02e502..e1ffb64bd 100644
--- a/stdlib/source/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/lux/tool/compiler/default/platform.lux
@@ -11,13 +11,12 @@
["." list]]]
[world
["." file (#+ File)]]]
- [//
- ["." init]
- ["." syntax]
- ["/." //
- ["." analysis]
- ["." statement]
- ["." phase
+ ["." // #_
+ ["#." init]
+ ["#." syntax]
+ ["#/" //
+ ["#." statement]
+ ["#." phase
[macro (#+ Expander)]
## TODO: Get rid of this import ASAP
[extension (#+)]
@@ -50,7 +49,7 @@
## (encoding.to-utf8 (%code (cache/description.write file-name module))))))
(with-expansions [<Platform> (as-is (Platform ! anchor expression statement))
- <State+> (as-is (statement.State+ anchor expression statement))
+ <State+> (as-is (///statement.State+ anchor expression statement))
<Bundle> (as-is (generation.Bundle anchor expression statement))]
(def: #export (initialize expander platform generation-bundle)
@@ -58,11 +57,11 @@
(-> Expander <Platform> <Bundle> (! (Error <State+>))))
(|> platform
(get@ #runtime)
- statement.lift-generation
- (phase.run' (init.state expander
- (get@ #host platform)
- (get@ #phase platform)
- generation-bundle))
+ ///statement.lift-generation
+ (///phase.run' (//init.state expander
+ (get@ #host platform)
+ (get@ #phase platform)
+ generation-bundle))
(:: error.functor map product.left)
(:: (get@ #&monad platform) wrap))
@@ -101,7 +100,7 @@
{<State+>
state}
{(///.Compiler <State+> .Module Any)
- ((init.compiler expander syntax.prelude source-module) init.key (list))})]
+ ((//init.compiler expander //syntax.prelude source-module) //init.key (list))})]
(loop [module source-module
[archive state] [archive state]]
(let [import! (:share [! anchor expression statement]
diff --git a/stdlib/source/lux/tool/compiler/meta/cache.lux b/stdlib/source/lux/tool/compiler/meta/cache.lux
index 7ba16878a..a0d5302f3 100644
--- a/stdlib/source/lux/tool/compiler/meta/cache.lux
+++ b/stdlib/source/lux/tool/compiler/meta/cache.lux
@@ -19,13 +19,14 @@
["." set (#+ Set)]]]
[world
[file (#+ File System)]]]
- [//
- [io (#+ Context Module)
- ["io/." context]
- ["io/." archive]]
- ["." archive (#+ Signature Key Descriptor Document Archive)]
- ["/." //]]
- ["." /dependency (#+ Dependency Graph)])
+ ["." //
+ ["#." io (#+ Context Module)
+ ["#/." context]
+ ["#/." archive]]
+ ["#." archive (#+ Signature Key Descriptor Document Archive)]
+ ["#/" //]]
+ ["." / #_
+ ["#." dependency (#+ Dependency Graph)]])
(exception: #export (cannot-delete-file {file File})
(ex.report ["File" file]))
@@ -37,8 +38,8 @@
(exception: #export (mismatched-signature {module ///.Module} {expected Signature} {actual Signature})
(ex.report ["Module" module]
- ["Expected" (archive.describe expected)]
- ["Actual" (archive.describe actual)]))
+ ["Expected" (//archive.describe expected)]
+ ["Actual" (//archive.describe actual)]))
(do-template [<name>]
[(exception: #export (<name> {message Text})
@@ -51,7 +52,7 @@
(def: #export (cached System<m> root)
(All [m] (-> (System m) File (m (List File))))
(|> root
- (io/archive.archive System<m>)
+ (//io/archive.archive System<m>)
(do> (:: System<m> &monad)
[(:: System<m> files)]
[(monad.map @ (function (recur file)
@@ -63,7 +64,7 @@
[(:: System<m> files)]
[(monad.map @ recur)]
[list.concat
- (list& (maybe.assume (io/archive.module System<m> root file)))
+ (list& (maybe.assume (//io/archive.module System<m> root file)))
wrap]))
(wrap (list))))))]
[list.concat wrap])))
@@ -79,7 +80,7 @@
(def: (un-install System<m> root module)
(All [m] (-> (System m) File Module (m Any)))
- (let [document (io/archive.document System<m> root module)]
+ (let [document (//io/archive.document System<m> root module)]
(|> document
(do> (:: System<m> &monad)
[(:: System<m> files)]
@@ -120,19 +121,19 @@
(All [m d] (-> (System m) (List File) File (Key d) (Format d) Module
(m (Maybe [Dependency (Document d)]))))
(do (:: System<m> &monad)
- [document' (:: System<m> read (io/archive.document System<m> root module))
- [module' source-code] (io/context.read System<m> contexts module)
+ [document' (:: System<m> read (//io/archive.document System<m> root module))
+ [module' source-code] (//io/context.read System<m> contexts module)
#let [current-hash (:: text.hash hash source-code)]]
(case (do error.monad
[[signature descriptor content] (binary.read (..document binary) document')
#let [[document-hash _file references _state] descriptor]
- _ (ex.assert mismatched-signature [module (get@ #archive.signature key) signature]
- (:: archive.equivalence =
- (get@ #archive.signature key)
+ _ (ex.assert mismatched-signature [module (get@ #//archive.signature key) signature]
+ (:: //archive.equivalence =
+ (get@ #//archive.signature key)
signature))
_ (ex.assert stale-document [module current-hash document-hash]
(n/= current-hash document-hash))
- document (archive.write key signature descriptor content)]
+ document (//archive.write key signature descriptor content)]
(wrap [[module references] document]))
(#error.Success [dependency document])
(wrap (#.Some [dependency document]))
diff --git a/stdlib/source/lux/tool/compiler/meta/io/context.lux b/stdlib/source/lux/tool/compiler/meta/io/context.lux
index 6b9ce9ba4..b009fbdc6 100644
--- a/stdlib/source/lux/tool/compiler/meta/io/context.lux
+++ b/stdlib/source/lux/tool/compiler/meta/io/context.lux
@@ -15,11 +15,11 @@
[binary (#+ Binary)]]
[type (#+ :share)]]
["." // (#+ Context Code)
- [//
+ ["#/" // #_
[archive
[descriptor (#+ Module)]]
- ["//." // (#+ Input)
- ["." host]]]])
+ ["#/" // (#+ Input)
+ ["#." host]]]])
(do-template [<name>]
[(exception: #export (<name> {module Module})
@@ -37,15 +37,15 @@
(def: partial-host-extension
Extension
- (`` (for {(~~ (static host.common-lisp)) ".cl"
- (~~ (static host.js)) ".js"
- (~~ (static host.jvm)) ".jvm"
- (~~ (static host.lua)) ".lua"
- (~~ (static host.php)) ".php"
- (~~ (static host.python)) ".py"
- (~~ (static host.r)) ".r"
- (~~ (static host.ruby)) ".rb"
- (~~ (static host.scheme)) ".scm"})))
+ (`` (for {(~~ (static ////host.common-lisp)) ".cl"
+ (~~ (static ////host.js)) ".js"
+ (~~ (static ////host.jvm)) ".jvm"
+ (~~ (static ////host.lua)) ".lua"
+ (~~ (static ////host.php)) ".php"
+ (~~ (static ////host.python)) ".py"
+ (~~ (static ////host.r)) ".r"
+ (~~ (static ////host.ruby)) ".rb"
+ (~~ (static ////host.scheme)) ".scm"})))
(def: full-host-extension
Extension
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis.lux b/stdlib/source/lux/tool/compiler/phase/analysis.lux
index 917ea1632..f12ab301e 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis.lux
@@ -8,18 +8,18 @@
[text
format]]
["." macro]]
- [/
- ["/." type]
- ["/." primitive]
- ["/." structure]
- ["/." reference]
- ["/." case]
- ["/." function]
- ["." //
- ["//." macro (#+ Expander)]
- ["//." extension]
- [//
- ["." reference]
+ ["." / #_
+ ["#." type]
+ ["#." primitive]
+ ["#." structure]
+ ["#." reference]
+ ["#." case]
+ ["#." function]
+ ["#/" //
+ ["#." macro (#+ Expander)]
+ ["#." extension]
+ ["#/" // #_
+ ["#." reference]
["/" analysis (#+ Analysis Operation Phase)]]]])
(exception: #export (unrecognized-syntax {code Code})
@@ -102,7 +102,7 @@
[[functionT functionA] (/type.with-inference
(compile functionC))]
(case functionA
- (#/.Reference (#reference.Constant def-name))
+ (#/.Reference (#///reference.Constant def-name))
(do @
[?macro (//extension.lift (macro.find-macro def-name))]
(case ?macro
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/case.lux b/stdlib/source/lux/tool/compiler/phase/analysis/case.lux
index 688d04c95..2970364a0 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/case.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/case.lux
@@ -15,16 +15,16 @@
["." check]]
["." macro
["." code]]]
- [//
- ["//." scope]
- ["//." type]
- ["//." structure]
- ["/." //
- ["///." extension]
+ ["." // #_
+ ["#." scope]
+ ["#." type]
+ ["#." structure]
+ ["#/" //
+ ["#." extension]
[//
["/" analysis (#+ Pattern Analysis Operation Phase)]]]]
- [/
- ["/." coverage (#+ Coverage)]])
+ ["." / #_
+ ["#." coverage (#+ Coverage)]])
(exception: #export (cannot-match-with-pattern {type Type} {pattern Code})
(ex.report ["Type" (%type type)]
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/function.lux b/stdlib/source/lux/tool/compiler/phase/analysis/function.lux
index bb75a313b..0438ee4c8 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/function.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/function.lux
@@ -12,12 +12,12 @@
["." type
["." check]]
["." macro]]
- [//
- ["//." scope]
- ["//." type]
- ["//." inference]
- ["/." //
- ["///." extension]
+ ["." // #_
+ ["#." scope]
+ ["#." type]
+ ["#." inference]
+ ["#/" //
+ ["#." extension]
[//
["/" analysis (#+ Analysis Operation Phase)]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux b/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux
index a99b06ac2..3b40b09d2 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux
@@ -12,10 +12,10 @@
["." type
["." check]]
["." macro]]
- [//
- ["//." type]
- ["/." // ("#/." monad)
- ["///." extension]
+ ["." // #_
+ ["#." type]
+ ["#/" // ("#/." monad)
+ ["#." extension]
[//
["/" analysis (#+ Tag Analysis Operation Phase)]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux
index ec9a3d5a0..b2af57b50 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux
@@ -14,7 +14,7 @@
["." plist]]]]
["." macro]]
["." ///
- ["///." extension]
+ ["#." extension]
[//
["/" analysis (#+ Operation)]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux b/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux
index 6e0a591d2..60e3392e6 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux
@@ -2,9 +2,9 @@
[lux (#- nat int rev)
[control
monad]]
- [//
- ["//." type]
- ["/." //
+ ["." // #_
+ ["#." type]
+ ["#/" //
[//
["/" analysis (#+ Analysis Operation)]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/reference.lux b/stdlib/source/lux/tool/compiler/phase/analysis/reference.lux
index 507441427..dad708219 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/reference.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/reference.lux
@@ -7,13 +7,13 @@
[data
["." text ("#/." equivalence)
format]]]
- [//
- ["//." scope]
- ["//." type]
- ["/." //
- ["///." extension]
- [//
- ["." reference]
+ ["." // #_
+ ["#." scope]
+ ["#." type]
+ ["#/" //
+ ["#." extension]
+ ["#/" // #_
+ ["#." reference]
["/" analysis (#+ Analysis Operation)]]]])
(exception: #export (foreign-module-has-not-been-imported {current Text} {foreign Text})
@@ -25,7 +25,7 @@
(def: (definition def-name)
(-> Name (Operation Analysis))
- (with-expansions [<return> (wrap (|> def-name reference.constant #/.Reference))]
+ (with-expansions [<return> (wrap (|> def-name ////reference.constant #/.Reference))]
(do ///.monad
[[actualT def-anns _] (///extension.lift (macro.find-def def-name))]
(case (macro.get-identifier-ann (name-of #.alias) def-anns)
@@ -55,7 +55,7 @@
(#.Some [actualT ref])
(do @
[_ (//type.infer actualT)]
- (wrap (#.Some (|> ref reference.variable #/.Reference))))
+ (wrap (#.Some (|> ref ////reference.variable #/.Reference))))
#.None
(wrap #.None))))
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux
index a1b46a761..9ad60ebf9 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux
@@ -14,9 +14,9 @@
[dictionary
["." plist]]]]]
["." ///
- ["///." extension]
- [//
- ["////." reference (#+ Register Variable)]
+ ["#." extension]
+ ["#/" // #_
+ ["#." reference (#+ Register Variable)]
["/" analysis (#+ Operation Phase)]]])
(type: Local (Bindings Text [Type Register]))
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux
index e5a936226..0a6017cdc 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux
@@ -20,12 +20,12 @@
["." check]]
["." macro
["." code]]]
- [//
- ["//." type]
- ["//." primitive]
- ["//." inference]
- ["/." //
- ["///." extension]
+ ["." // #_
+ ["#." type]
+ ["#." primitive]
+ ["#." inference]
+ ["#/" //
+ ["#." extension]
[//
["/" analysis (#+ Tag Analysis Operation Phase)]]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/type.lux b/stdlib/source/lux/tool/compiler/phase/analysis/type.lux
index ae87615e4..5a7db6516 100644
--- a/stdlib/source/lux/tool/compiler/phase/analysis/type.lux
+++ b/stdlib/source/lux/tool/compiler/phase/analysis/type.lux
@@ -9,7 +9,7 @@
["." check (#+ Check)]]
["." macro]]
["." ///
- ["///." extension]
+ ["#." extension]
[//
["/" analysis (#+ Operation)]]])
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux
index ed71847c2..dbe0b10ca 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux
@@ -13,16 +13,16 @@
["." macro]
[io (#+ IO)]]
["." ///
- ["." bundle]
- ["//." //
+ ["#." bundle]
+ ["#/" //
[analysis
[".A" type]
[".A" case]
[".A" function]]
- [//
+ ["#/" //
[default
[evaluation (#+ Eval)]]
- ["." analysis (#+ Analysis Handler Bundle)]]]])
+ ["#." analysis (#+ Analysis Handler Bundle)]]]])
## [Utils]
(def: (simple inputsT+ outputT)
@@ -38,7 +38,7 @@
(typeA.with-type argT
(analyse argC)))
(list.zip2 inputsT+ args))]
- (wrap (#analysis.Extension extension-name argsA)))
+ (wrap (#/////analysis.Extension extension-name argsA)))
(////.throw ///.incorrect-arity [extension-name num-expected num-actual]))))))
(def: #export (nullary valueT)
@@ -79,7 +79,7 @@
_ (typeA.infer (type (Either Text varT)))
opA (typeA.with-type (type (IO varT))
(analyse opC))]
- (wrap (#analysis.Extension extension-name (list opA))))
+ (wrap (#/////analysis.Extension extension-name (list opA))))
_
(////.throw ///.incorrect-arity [extension-name 1 (list.size args)]))))
@@ -89,7 +89,7 @@
(function (_ extension-name analyse argsC+)
(case argsC+
(^ (list [_ (#.Text module-name)] exprC))
- (analysis.with-current-module module-name
+ (/////analysis.with-current-module module-name
(analyse exprC))
_
@@ -132,85 +132,85 @@
(def: (bundle::lux eval)
(-> Eval Bundle)
- (|> bundle.empty
- (bundle.install "is" lux::is)
- (bundle.install "try" lux::try)
- (bundle.install "check" (lux::check eval))
- (bundle.install "coerce" (lux::coerce eval))
- (bundle.install "check type" lux::check::type)
- (bundle.install "in-module" lux::in-module)))
+ (|> ///bundle.empty
+ (///bundle.install "is" lux::is)
+ (///bundle.install "try" lux::try)
+ (///bundle.install "check" (lux::check eval))
+ (///bundle.install "coerce" (lux::coerce eval))
+ (///bundle.install "check type" lux::check::type)
+ (///bundle.install "in-module" lux::in-module)))
(def: bundle::io
Bundle
- (<| (bundle.prefix "io")
- (|> bundle.empty
- (bundle.install "log" (unary Text Any))
- (bundle.install "error" (unary Text Nothing))
- (bundle.install "exit" (unary Int Nothing))
- (bundle.install "current-time" (nullary Int)))))
+ (<| (///bundle.prefix "io")
+ (|> ///bundle.empty
+ (///bundle.install "log" (unary Text Any))
+ (///bundle.install "error" (unary Text Nothing))
+ (///bundle.install "exit" (unary Int Nothing))
+ (///bundle.install "current-time" (nullary Int)))))
(def: I64* (type (I64 Any)))
(def: bundle::i64
Bundle
- (<| (bundle.prefix "i64")
- (|> bundle.empty
- (bundle.install "and" (binary I64* I64* I64))
- (bundle.install "or" (binary I64* I64* I64))
- (bundle.install "xor" (binary I64* I64* I64))
- (bundle.install "left-shift" (binary Nat I64* I64))
- (bundle.install "logical-right-shift" (binary Nat I64* I64))
- (bundle.install "arithmetic-right-shift" (binary Nat I64* I64))
- (bundle.install "+" (binary I64* I64* I64))
- (bundle.install "-" (binary I64* I64* I64))
- (bundle.install "=" (binary I64* I64* Bit)))))
+ (<| (///bundle.prefix "i64")
+ (|> ///bundle.empty
+ (///bundle.install "and" (binary I64* I64* I64))
+ (///bundle.install "or" (binary I64* I64* I64))
+ (///bundle.install "xor" (binary I64* I64* I64))
+ (///bundle.install "left-shift" (binary Nat I64* I64))
+ (///bundle.install "logical-right-shift" (binary Nat I64* I64))
+ (///bundle.install "arithmetic-right-shift" (binary Nat I64* I64))
+ (///bundle.install "+" (binary I64* I64* I64))
+ (///bundle.install "-" (binary I64* I64* I64))
+ (///bundle.install "=" (binary I64* I64* Bit)))))
(def: bundle::int
Bundle
- (<| (bundle.prefix "int")
- (|> bundle.empty
- (bundle.install "*" (binary Int Int Int))
- (bundle.install "/" (binary Int Int Int))
- (bundle.install "%" (binary Int Int Int))
- (bundle.install "<" (binary Int Int Bit))
- (bundle.install "frac" (unary Int Frac))
- (bundle.install "char" (unary Int Text)))))
+ (<| (///bundle.prefix "int")
+ (|> ///bundle.empty
+ (///bundle.install "*" (binary Int Int Int))
+ (///bundle.install "/" (binary Int Int Int))
+ (///bundle.install "%" (binary Int Int Int))
+ (///bundle.install "<" (binary Int Int Bit))
+ (///bundle.install "frac" (unary Int Frac))
+ (///bundle.install "char" (unary Int Text)))))
(def: bundle::frac
Bundle
- (<| (bundle.prefix "frac")
- (|> bundle.empty
- (bundle.install "+" (binary Frac Frac Frac))
- (bundle.install "-" (binary Frac Frac Frac))
- (bundle.install "*" (binary Frac Frac Frac))
- (bundle.install "/" (binary Frac Frac Frac))
- (bundle.install "%" (binary Frac Frac Frac))
- (bundle.install "=" (binary Frac Frac Bit))
- (bundle.install "<" (binary Frac Frac Bit))
- (bundle.install "smallest" (nullary Frac))
- (bundle.install "min" (nullary Frac))
- (bundle.install "max" (nullary Frac))
- (bundle.install "int" (unary Frac Int))
- (bundle.install "encode" (unary Frac Text))
- (bundle.install "decode" (unary Text (type (Maybe Frac)))))))
+ (<| (///bundle.prefix "frac")
+ (|> ///bundle.empty
+ (///bundle.install "+" (binary Frac Frac Frac))
+ (///bundle.install "-" (binary Frac Frac Frac))
+ (///bundle.install "*" (binary Frac Frac Frac))
+ (///bundle.install "/" (binary Frac Frac Frac))
+ (///bundle.install "%" (binary Frac Frac Frac))
+ (///bundle.install "=" (binary Frac Frac Bit))
+ (///bundle.install "<" (binary Frac Frac Bit))
+ (///bundle.install "smallest" (nullary Frac))
+ (///bundle.install "min" (nullary Frac))
+ (///bundle.install "max" (nullary Frac))
+ (///bundle.install "int" (unary Frac Int))
+ (///bundle.install "encode" (unary Frac Text))
+ (///bundle.install "decode" (unary Text (type (Maybe Frac)))))))
(def: bundle::text
Bundle
- (<| (bundle.prefix "text")
- (|> bundle.empty
- (bundle.install "=" (binary Text Text Bit))
- (bundle.install "<" (binary Text Text Bit))
- (bundle.install "concat" (binary Text Text Text))
- (bundle.install "index" (trinary Text Text Nat (type (Maybe Nat))))
- (bundle.install "size" (unary Text Nat))
- (bundle.install "char" (binary Text Nat Nat))
- (bundle.install "clip" (trinary Text Nat Nat Text))
+ (<| (///bundle.prefix "text")
+ (|> ///bundle.empty
+ (///bundle.install "=" (binary Text Text Bit))
+ (///bundle.install "<" (binary Text Text Bit))
+ (///bundle.install "concat" (binary Text Text Text))
+ (///bundle.install "index" (trinary Text Text Nat (type (Maybe Nat))))
+ (///bundle.install "size" (unary Text Nat))
+ (///bundle.install "char" (binary Text Nat Nat))
+ (///bundle.install "clip" (trinary Text Nat Nat Text))
)))
(def: #export (bundle eval)
(-> Eval Bundle)
- (<| (bundle.prefix "lux")
- (|> bundle.empty
+ (<| (///bundle.prefix "lux")
+ (|> ///bundle.empty
(dictionary.merge (bundle::lux eval))
(dictionary.merge bundle::i64)
(dictionary.merge bundle::int)
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux
index 7edc13cbd..6b1e6ed5b 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux
@@ -20,16 +20,16 @@
["." macro
["s" syntax]]
["." host (#+ import:)]]
- [//
- ["." common]
- ["/." //
- ["." bundle]
- ["//." // ("#/." monad)
+ ["." // #_
+ ["#." common]
+ ["#/" //
+ ["#." bundle]
+ ["#/" // ("#/." monad)
[analysis
[".A" type]
[".A" inference]]
- [//
- ["." analysis (#+ Analysis Operation Handler Bundle)]]]]])
+ ["#/" // #_
+ ["#." analysis (#+ Analysis Operation Handler Bundle)]]]]])
(type: Method-Signature
{#method Type
@@ -130,51 +130,51 @@
(def: bundle::conversion
Bundle
- (<| (bundle.prefix "convert")
- (|> bundle.empty
- (bundle.install "double-to-float" (common.unary Double Float))
- (bundle.install "double-to-int" (common.unary Double Integer))
- (bundle.install "double-to-long" (common.unary Double Long))
- (bundle.install "float-to-double" (common.unary Float Double))
- (bundle.install "float-to-int" (common.unary Float Integer))
- (bundle.install "float-to-long" (common.unary Float Long))
- (bundle.install "int-to-byte" (common.unary Integer Byte))
- (bundle.install "int-to-char" (common.unary Integer Character))
- (bundle.install "int-to-double" (common.unary Integer Double))
- (bundle.install "int-to-float" (common.unary Integer Float))
- (bundle.install "int-to-long" (common.unary Integer Long))
- (bundle.install "int-to-short" (common.unary Integer Short))
- (bundle.install "long-to-double" (common.unary Long Double))
- (bundle.install "long-to-float" (common.unary Long Float))
- (bundle.install "long-to-int" (common.unary Long Integer))
- (bundle.install "long-to-short" (common.unary Long Short))
- (bundle.install "long-to-byte" (common.unary Long Byte))
- (bundle.install "char-to-byte" (common.unary Character Byte))
- (bundle.install "char-to-short" (common.unary Character Short))
- (bundle.install "char-to-int" (common.unary Character Integer))
- (bundle.install "char-to-long" (common.unary Character Long))
- (bundle.install "byte-to-long" (common.unary Byte Long))
- (bundle.install "short-to-long" (common.unary Short Long))
+ (<| (///bundle.prefix "convert")
+ (|> ///bundle.empty
+ (///bundle.install "double-to-float" (//common.unary Double Float))
+ (///bundle.install "double-to-int" (//common.unary Double Integer))
+ (///bundle.install "double-to-long" (//common.unary Double Long))
+ (///bundle.install "float-to-double" (//common.unary Float Double))
+ (///bundle.install "float-to-int" (//common.unary Float Integer))
+ (///bundle.install "float-to-long" (//common.unary Float Long))
+ (///bundle.install "int-to-byte" (//common.unary Integer Byte))
+ (///bundle.install "int-to-char" (//common.unary Integer Character))
+ (///bundle.install "int-to-double" (//common.unary Integer Double))
+ (///bundle.install "int-to-float" (//common.unary Integer Float))
+ (///bundle.install "int-to-long" (//common.unary Integer Long))
+ (///bundle.install "int-to-short" (//common.unary Integer Short))
+ (///bundle.install "long-to-double" (//common.unary Long Double))
+ (///bundle.install "long-to-float" (//common.unary Long Float))
+ (///bundle.install "long-to-int" (//common.unary Long Integer))
+ (///bundle.install "long-to-short" (//common.unary Long Short))
+ (///bundle.install "long-to-byte" (//common.unary Long Byte))
+ (///bundle.install "char-to-byte" (//common.unary Character Byte))
+ (///bundle.install "char-to-short" (//common.unary Character Short))
+ (///bundle.install "char-to-int" (//common.unary Character Integer))
+ (///bundle.install "char-to-long" (//common.unary Character Long))
+ (///bundle.install "byte-to-long" (//common.unary Byte Long))
+ (///bundle.install "short-to-long" (//common.unary Short Long))
)))
(do-template [<name> <prefix> <type>]
[(def: <name>
Bundle
- (<| (bundle.prefix <prefix>)
- (|> bundle.empty
- (bundle.install "+" (common.binary <type> <type> <type>))
- (bundle.install "-" (common.binary <type> <type> <type>))
- (bundle.install "*" (common.binary <type> <type> <type>))
- (bundle.install "/" (common.binary <type> <type> <type>))
- (bundle.install "%" (common.binary <type> <type> <type>))
- (bundle.install "=" (common.binary <type> <type> Bit))
- (bundle.install "<" (common.binary <type> <type> Bit))
- (bundle.install "and" (common.binary <type> <type> <type>))
- (bundle.install "or" (common.binary <type> <type> <type>))
- (bundle.install "xor" (common.binary <type> <type> <type>))
- (bundle.install "shl" (common.binary <type> Integer <type>))
- (bundle.install "shr" (common.binary <type> Integer <type>))
- (bundle.install "ushr" (common.binary <type> Integer <type>))
+ (<| (///bundle.prefix <prefix>)
+ (|> ///bundle.empty
+ (///bundle.install "+" (//common.binary <type> <type> <type>))
+ (///bundle.install "-" (//common.binary <type> <type> <type>))
+ (///bundle.install "*" (//common.binary <type> <type> <type>))
+ (///bundle.install "/" (//common.binary <type> <type> <type>))
+ (///bundle.install "%" (//common.binary <type> <type> <type>))
+ (///bundle.install "=" (//common.binary <type> <type> Bit))
+ (///bundle.install "<" (//common.binary <type> <type> Bit))
+ (///bundle.install "and" (//common.binary <type> <type> <type>))
+ (///bundle.install "or" (//common.binary <type> <type> <type>))
+ (///bundle.install "xor" (//common.binary <type> <type> <type>))
+ (///bundle.install "shl" (//common.binary <type> Integer <type>))
+ (///bundle.install "shr" (//common.binary <type> Integer <type>))
+ (///bundle.install "ushr" (//common.binary <type> Integer <type>))
)))]
[bundle::int "int" Integer]
@@ -184,15 +184,15 @@
(do-template [<name> <prefix> <type>]
[(def: <name>
Bundle
- (<| (bundle.prefix <prefix>)
- (|> bundle.empty
- (bundle.install "+" (common.binary <type> <type> <type>))
- (bundle.install "-" (common.binary <type> <type> <type>))
- (bundle.install "*" (common.binary <type> <type> <type>))
- (bundle.install "/" (common.binary <type> <type> <type>))
- (bundle.install "%" (common.binary <type> <type> <type>))
- (bundle.install "=" (common.binary <type> <type> Bit))
- (bundle.install "<" (common.binary <type> <type> Bit))
+ (<| (///bundle.prefix <prefix>)
+ (|> ///bundle.empty
+ (///bundle.install "+" (//common.binary <type> <type> <type>))
+ (///bundle.install "-" (//common.binary <type> <type> <type>))
+ (///bundle.install "*" (//common.binary <type> <type> <type>))
+ (///bundle.install "/" (//common.binary <type> <type> <type>))
+ (///bundle.install "%" (//common.binary <type> <type> <type>))
+ (///bundle.install "=" (//common.binary <type> <type> Bit))
+ (///bundle.install "<" (//common.binary <type> <type> Bit))
)))]
[bundle::float "float" Float]
@@ -201,10 +201,10 @@
(def: bundle::char
Bundle
- (<| (bundle.prefix "char")
- (|> bundle.empty
- (bundle.install "=" (common.binary Character Character Bit))
- (bundle.install "<" (common.binary Character Character Bit))
+ (<| (///bundle.prefix "char")
+ (|> ///bundle.empty
+ (///bundle.install "=" (//common.binary Character Character Bit))
+ (///bundle.install "<" (//common.binary Character Character Bit))
)))
(def: #export boxes
@@ -229,7 +229,7 @@
[var-id varT] (typeA.with-env check.var)
arrayA (typeA.with-type (type (Array varT))
(analyse arrayC))]
- (wrap (#analysis.Extension extension-name (list arrayA))))
+ (wrap (#/////analysis.Extension extension-name (list arrayA))))
_
(////.throw ///.incorrect-arity [extension-name 1 (list.size args)]))))
@@ -266,9 +266,9 @@
_ (if (n/> 0 level)
(wrap [])
(////.throw non-array expectedT))]
- (wrap (#analysis.Extension extension-name (list (analysis.nat (dec level))
- (analysis.text elem-class)
- lengthA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.nat (dec level))
+ (/////analysis.text elem-class)
+ lengthA))))
_
(////.throw ///.incorrect-arity [extension-name 1 (list.size args)]))))
@@ -342,7 +342,7 @@
[elemT elem-class] (box-array-element-type (maybe.default varT ?elemT))
idxA (typeA.with-type Nat
(analyse idxC))]
- (wrap (#analysis.Extension extension-name (list (analysis.text elem-class) idxA arrayA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text elem-class) idxA arrayA))))
_
(////.throw ///.incorrect-arity [extension-name 2 (list.size args)]))))
@@ -364,19 +364,19 @@
(analyse idxC))
valueA (typeA.with-type valueT
(analyse valueC))]
- (wrap (#analysis.Extension extension-name (list (analysis.text elem-class) idxA valueA arrayA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text elem-class) idxA valueA arrayA))))
_
(////.throw ///.incorrect-arity [extension-name 3 (list.size args)]))))
(def: bundle::array
Bundle
- (<| (bundle.prefix "array")
- (|> bundle.empty
- (bundle.install "length" array::length)
- (bundle.install "new" array::new)
- (bundle.install "read" array::read)
- (bundle.install "write" array::write)
+ (<| (///bundle.prefix "array")
+ (|> ///bundle.empty
+ (///bundle.install "length" array::length)
+ (///bundle.install "new" array::new)
+ (///bundle.install "read" array::read)
+ (///bundle.install "write" array::write)
)))
(def: object::null
@@ -387,7 +387,7 @@
(do ////.monad
[expectedT (///.lift macro.expected-type)
_ (check-object expectedT)]
- (wrap (#analysis.Extension extension-name (list))))
+ (wrap (#/////analysis.Extension extension-name (list))))
_
(////.throw ///.incorrect-arity [extension-name 0 (list.size args)]))))
@@ -402,7 +402,7 @@
[objectT objectA] (typeA.with-inference
(analyse objectC))
_ (check-object objectT)]
- (wrap (#analysis.Extension extension-name (list objectA))))
+ (wrap (#/////analysis.Extension extension-name (list objectA))))
_
(////.throw ///.incorrect-arity [extension-name 1 (list.size args)]))))
@@ -417,7 +417,7 @@
(analyse monitorC))
_ (check-object monitorT)
exprA (analyse exprC)]
- (wrap (#analysis.Extension extension-name (list monitorA exprA))))
+ (wrap (#/////analysis.Extension extension-name (list monitorA exprA))))
_
(////.throw ///.incorrect-arity [extension-name 2 (list.size args)]))))
@@ -514,7 +514,7 @@
(if ?
(wrap [])
(////.throw non-throwable exception-class)))]
- (wrap (#analysis.Extension extension-name (list exceptionA))))
+ (wrap (#/////analysis.Extension extension-name (list exceptionA))))
_
(////.throw ///.incorrect-arity [extension-name 1 (list.size args)]))))
@@ -529,7 +529,7 @@
(do ////.monad
[_ (typeA.infer (#.Primitive "java.lang.Class" (list (#.Primitive class (list)))))
_ (load-class class)]
- (wrap (#analysis.Extension extension-name (list (analysis.text class)))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class)))))
_
(////.throw ///.invalid-syntax extension-name))
@@ -551,7 +551,7 @@
object-class (check-object objectT)
? (sub-class? class object-class)]
(if ?
- (wrap (#analysis.Extension extension-name (list (analysis.text class))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class))))
(////.throw cannot-possibly-be-an-instance (format object-class " !<= " class))))
_
@@ -747,9 +747,9 @@
" For value: " (%code valueC) text.new-line)))
))))))]
(if can-cast?
- (wrap (#analysis.Extension extension-name (list (analysis.text from-name)
- (analysis.text to-name)
- valueA)))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text from-name)
+ (/////analysis.text to-name)
+ valueA)))
(////.throw cannot-cast (format "From class/primitive: " from-name text.new-line
" To class/primitive: " to-name text.new-line
" For value: " (%code valueC) text.new-line))))
@@ -759,15 +759,15 @@
(def: bundle::object
Bundle
- (<| (bundle.prefix "object")
- (|> bundle.empty
- (bundle.install "null" object::null)
- (bundle.install "null?" object::null?)
- (bundle.install "synchronized" object::synchronized)
- (bundle.install "throw" object::throw)
- (bundle.install "class" object::class)
- (bundle.install "instance?" object::instance?)
- (bundle.install "cast" object::cast)
+ (<| (///bundle.prefix "object")
+ (|> ///bundle.empty
+ (///bundle.install "null" object::null)
+ (///bundle.install "null?" object::null?)
+ (///bundle.install "synchronized" object::synchronized)
+ (///bundle.install "throw" object::throw)
+ (///bundle.install "class" object::class)
+ (///bundle.install "instance?" object::instance?)
+ (///bundle.install "cast" object::cast)
)))
(def: (find-field class-name field-name)
@@ -841,7 +841,7 @@
[[_ (#.Text class)] [_ (#.Text field)]]
(do ////.monad
[[fieldT final?] (static-field class field)]
- (wrap (#analysis.Extension extension-name (list (analysis.text class) (analysis.text field)))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class) (/////analysis.text field)))))
_
(////.throw ///.invalid-syntax extension-name))
@@ -863,7 +863,7 @@
(not final?))
valueA (typeA.with-type fieldT
(analyse valueC))]
- (wrap (#analysis.Extension extension-name (list (analysis.text class) (analysis.text field) valueA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class) (/////analysis.text field) valueA))))
_
(////.throw ///.invalid-syntax extension-name))
@@ -882,7 +882,7 @@
[[objectT objectA] (typeA.with-inference
(analyse objectC))
[fieldT final?] (virtual-field class field objectT)]
- (wrap (#analysis.Extension extension-name (list (analysis.text class) (analysis.text field) objectA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class) (/////analysis.text field) objectA))))
_
(////.throw ///.invalid-syntax extension-name))
@@ -906,7 +906,7 @@
(not final?))
valueA (typeA.with-type fieldT
(analyse valueC))]
- (wrap (#analysis.Extension extension-name (list (analysis.text class) (analysis.text field) valueA objectA))))
+ (wrap (#/////analysis.Extension extension-name (list (/////analysis.text class) (/////analysis.text field) valueA objectA))))
_
(////.throw ///.invalid-syntax extension-name))
@@ -1165,9 +1165,9 @@
(def: (decorate-inputs typesT inputsA)
(-> (List Text) (List Analysis) (List Analysis))
(|> inputsA
- (list.zip2 (list/map analysis.text typesT))
+ (list.zip2 (list/map /////analysis.text typesT))
(list/map (function (_ [type value])
- (analysis.tuple (list type value))))))
+ (/////analysis.tuple (list type value))))))
(def: invoke::static
Handler
@@ -1180,8 +1180,8 @@
[methodT exceptionsT] (method-candidate class method #Static argsT)
[outputT argsA] (inferenceA.general analyse methodT (list/map product.right argsTC))
outputJC (check-jvm outputT)]
- (wrap (#analysis.Extension extension-name (list& (analysis.text class) (analysis.text method)
- (analysis.text outputJC) (decorate-inputs argsT argsA)))))
+ (wrap (#/////analysis.Extension extension-name (list& (/////analysis.text class) (/////analysis.text method)
+ (/////analysis.text outputJC) (decorate-inputs argsT argsA)))))
_
(////.throw ///.invalid-syntax extension-name))))
@@ -1203,8 +1203,8 @@
_
(undefined))]
outputJC (check-jvm outputT)]
- (wrap (#analysis.Extension extension-name (list& (analysis.text class) (analysis.text method)
- (analysis.text outputJC) objectA (decorate-inputs argsT argsA)))))
+ (wrap (#/////analysis.Extension extension-name (list& (/////analysis.text class) (/////analysis.text method)
+ (/////analysis.text outputJC) objectA (decorate-inputs argsT argsA)))))
_
(////.throw ///.invalid-syntax extension-name))))
@@ -1220,8 +1220,8 @@
[methodT exceptionsT] (method-candidate class method #Special argsT)
[outputT argsA] (inferenceA.general analyse methodT (list& objectC (list/map product.right argsTC)))
outputJC (check-jvm outputT)]
- (wrap (#analysis.Extension extension-name (list& (analysis.text class) (analysis.text method)
- (analysis.text outputJC) (decorate-inputs argsT argsA)))))
+ (wrap (#/////analysis.Extension extension-name (list& (/////analysis.text class) (/////analysis.text method)
+ (/////analysis.text outputJC) (decorate-inputs argsT argsA)))))
_
(////.throw ///.invalid-syntax extension-name))))
@@ -1240,9 +1240,9 @@
[methodT exceptionsT] (method-candidate class-name method #Interface argsT)
[outputT argsA] (inferenceA.general analyse methodT (list& objectC (list/map product.right argsTC)))
outputJC (check-jvm outputT)]
- (wrap (#analysis.Extension extension-name
- (list& (analysis.text class-name) (analysis.text method) (analysis.text outputJC)
- (decorate-inputs argsT argsA)))))
+ (wrap (#/////analysis.Extension extension-name
+ (list& (/////analysis.text class-name) (/////analysis.text method) (/////analysis.text outputJC)
+ (decorate-inputs argsT argsA)))))
_
(////.throw ///.invalid-syntax extension-name))))
@@ -1257,37 +1257,37 @@
[#let [argsT (list/map product.left argsTC)]
[methodT exceptionsT] (constructor-candidate class argsT)
[outputT argsA] (inferenceA.general analyse methodT (list/map product.right argsTC))]
- (wrap (#analysis.Extension extension-name (list& (analysis.text class) (decorate-inputs argsT argsA)))))
+ (wrap (#/////analysis.Extension extension-name (list& (/////analysis.text class) (decorate-inputs argsT argsA)))))
_
(////.throw ///.invalid-syntax extension-name))))
(def: bundle::member
Bundle
- (<| (bundle.prefix "member")
- (|> bundle.empty
- (dictionary.merge (<| (bundle.prefix "static")
- (|> bundle.empty
- (bundle.install "get" static::get)
- (bundle.install "put" static::put))))
- (dictionary.merge (<| (bundle.prefix "virtual")
- (|> bundle.empty
- (bundle.install "get" virtual::get)
- (bundle.install "put" virtual::put))))
- (dictionary.merge (<| (bundle.prefix "invoke")
- (|> bundle.empty
- (bundle.install "static" invoke::static)
- (bundle.install "virtual" invoke::virtual)
- (bundle.install "special" invoke::special)
- (bundle.install "interface" invoke::interface)
- (bundle.install "constructor" invoke::constructor)
+ (<| (///bundle.prefix "member")
+ (|> ///bundle.empty
+ (dictionary.merge (<| (///bundle.prefix "static")
+ (|> ///bundle.empty
+ (///bundle.install "get" static::get)
+ (///bundle.install "put" static::put))))
+ (dictionary.merge (<| (///bundle.prefix "virtual")
+ (|> ///bundle.empty
+ (///bundle.install "get" virtual::get)
+ (///bundle.install "put" virtual::put))))
+ (dictionary.merge (<| (///bundle.prefix "invoke")
+ (|> ///bundle.empty
+ (///bundle.install "static" invoke::static)
+ (///bundle.install "virtual" invoke::virtual)
+ (///bundle.install "special" invoke::special)
+ (///bundle.install "interface" invoke::interface)
+ (///bundle.install "constructor" invoke::constructor)
)))
)))
(def: #export bundle
Bundle
- (<| (bundle.prefix "jvm")
- (|> bundle.empty
+ (<| (///bundle.prefix "jvm")
+ (|> ///bundle.empty
(dictionary.merge bundle::conversion)
(dictionary.merge bundle::int)
(dictionary.merge bundle::long)
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
index 83e7320d8..5c957aab1 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
@@ -13,30 +13,30 @@
[type (#+ :share :by-example)
["." check]]]
["." //
- ["." bundle]
- ["/." //
+ ["#." bundle]
+ ["#/" //
[analysis
["." module]
["." type]]
- ["." generation]
- [//
- ["." analysis]
- ["." synthesis (#+ Synthesis)]
- ["." statement (#+ Operation Handler Bundle)]]]])
+ ["#." generation]
+ ["#/" // #_
+ ["#." analysis]
+ ["#." synthesis (#+ Synthesis)]
+ ["#." statement (#+ Operation Handler Bundle)]]]])
## TODO: Inline "evaluate!'" into "evaluate!" ASAP
(def: (evaluate!' generate code//type codeS)
(All [anchor expression statement]
- (-> (generation.Phase anchor expression statement)
+ (-> (///generation.Phase anchor expression statement)
Type
Synthesis
(Operation anchor expression statement [Type expression Any])))
- (statement.lift-generation
- (generation.with-buffer
+ (////statement.lift-generation
+ (///generation.with-buffer
(do ///.monad
[codeT (generate codeS)
- count generation.next
- codeV (generation.evaluate! (format "evaluate" (%n count)) codeT)]
+ count ///generation.next
+ codeV (///generation.evaluate! (format "evaluate" (%n count)) codeT)]
(wrap [code//type codeT codeV])))))
(def: (evaluate! type codeC)
@@ -44,33 +44,33 @@
(-> Type Code (Operation anchor expression statement [Type expression Any])))
(do ///.monad
[state (//.lift ///.get-state)
- #let [analyse (get@ [#statement.analysis #statement.phase] state)
- synthesize (get@ [#statement.synthesis #statement.phase] state)
- generate (get@ [#statement.generation #statement.phase] state)]
- [_ code//type codeA] (statement.lift-analysis
- (analysis.with-scope
+ #let [analyse (get@ [#////statement.analysis #////statement.phase] state)
+ synthesize (get@ [#////statement.synthesis #////statement.phase] state)
+ generate (get@ [#////statement.generation #////statement.phase] state)]
+ [_ code//type codeA] (////statement.lift-analysis
+ (////analysis.with-scope
(type.with-fresh-env
(type.with-type type
(do @
[codeA (analyse codeC)]
(wrap [type codeA]))))))
- codeS (statement.lift-synthesis
+ codeS (////statement.lift-synthesis
(synthesize codeA))]
(evaluate!' generate code//type codeS)))
## TODO: Inline "definition'" into "definition" ASAP
(def: (definition' generate name code//type codeS)
(All [anchor expression statement]
- (-> (generation.Phase anchor expression statement)
+ (-> (///generation.Phase anchor expression statement)
Name
Type
Synthesis
(Operation anchor expression statement [Type expression Text Any])))
- (statement.lift-generation
- (generation.with-buffer
+ (////statement.lift-generation
+ (///generation.with-buffer
(do ///.monad
[codeT (generate codeS)
- codeN+V (generation.define! name codeT)]
+ codeN+V (///generation.define! name codeT)]
(wrap [code//type codeT codeN+V])))))
(def: (definition name ?type codeC)
@@ -79,11 +79,11 @@
(Operation anchor expression statement [Type expression Text Any])))
(do ///.monad
[state (//.lift ///.get-state)
- #let [analyse (get@ [#statement.analysis #statement.phase] state)
- synthesize (get@ [#statement.synthesis #statement.phase] state)
- generate (get@ [#statement.generation #statement.phase] state)]
- [_ code//type codeA] (statement.lift-analysis
- (analysis.with-scope
+ #let [analyse (get@ [#////statement.analysis #////statement.phase] state)
+ synthesize (get@ [#////statement.synthesis #////statement.phase] state)
+ generate (get@ [#////statement.generation #////statement.phase] state)]
+ [_ code//type codeA] (////statement.lift-analysis
+ (////analysis.with-scope
(type.with-fresh-env
(case ?type
(#.Some type)
@@ -98,7 +98,7 @@
code//type (type.with-env
(check.clean code//type))]
(wrap [code//type codeA]))))))
- codeS (statement.lift-synthesis
+ codeS (////statement.lift-synthesis
(synthesize codeA))]
(definition' generate name code//type codeS)))
@@ -106,7 +106,7 @@
(All [anchor expression statement]
(-> Text Type Code Any
(Operation anchor expression statement Any)))
- (statement.lift-analysis
+ (////statement.lift-analysis
(do ///.monad
[_ (module.define short-name [type annotations value])]
(if (macro.type? annotations)
@@ -124,7 +124,7 @@
(case inputsC+
(^ (list [_ (#.Identifier ["" short-name])] valueC annotationsC))
(do ///.monad
- [current-module (statement.lift-analysis
+ [current-module (////statement.lift-analysis
(//.lift macro.current-module-name))
#let [full-name [current-module short-name]]
[_ annotationsT annotationsV] (evaluate! Code annotationsC)
@@ -136,14 +136,14 @@
valueC)
_ (..define short-name value//type annotationsV valueV)
#let [_ (log! (format "Definition " (%name full-name)))]]
- (statement.lift-generation
- (generation.learn full-name valueN)))
+ (////statement.lift-generation
+ (///generation.learn full-name valueN)))
_
(///.throw //.invalid-syntax [extension-name]))))
(def: (alias! alias def-name)
- (-> Text Name (analysis.Operation Any))
+ (-> Text Name (////analysis.Operation Any))
(do ///.monad
[definition (//.lift (macro.find-def def-name))]
(module.define alias definition)))
@@ -155,7 +155,7 @@
(^ (list annotationsC))
(do ///.monad
[[_ annotationsT annotationsV] (evaluate! Code annotationsC)
- _ (statement.lift-analysis
+ _ (////statement.lift-analysis
(module.set-annotations (:coerce Code annotationsV)))]
(wrap []))
@@ -168,8 +168,8 @@
(case inputsC+
(^ (list [_ (#.Identifier ["" alias])] [_ (#.Identifier def-name)]))
(//.lift
- (///.sub [(get@ [#statement.analysis #statement.state])
- (set@ [#statement.analysis #statement.state])]
+ (///.sub [(get@ [#////statement.analysis #////statement.state])
+ (set@ [#////statement.analysis #////statement.state])]
(alias! alias def-name)))
_
@@ -199,16 +199,16 @@
_
(///.throw //.invalid-syntax [extension-name]))))]
- [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::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
Bundle
- (<| (bundle.prefix "def")
- (|> bundle.empty
+ (<| (//bundle.prefix "def")
+ (|> //bundle.empty
(dictionary.put "module" def::module)
(dictionary.put "alias" def::alias)
(dictionary.put "analysis" def::analysis)
@@ -219,7 +219,7 @@
(def: #export bundle
Bundle
- (<| (bundle.prefix "lux")
- (|> bundle.empty
+ (<| (//bundle.prefix "lux")
+ (|> //bundle.empty
(dictionary.put "def" lux::def)
(dictionary.merge ..bundle::def))))
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
diff --git a/stdlib/source/lux/tool/compiler/phase/statement.lux b/stdlib/source/lux/tool/compiler/phase/statement.lux
index 87736643c..7e55e2dc6 100644
--- a/stdlib/source/lux/tool/compiler/phase/statement.lux
+++ b/stdlib/source/lux/tool/compiler/phase/statement.lux
@@ -8,13 +8,13 @@
format]]
["." macro]]
["." //
- ["//." macro (#+ Expander)]
- ["//." extension]
+ ["#." macro (#+ Expander)]
+ ["#." extension]
[".P" analysis
["." type]]
- [//
- ["/" statement (#+ Phase)]
- ["." analysis]]])
+ ["#/" // #_
+ ["#." analysis]
+ ["/" statement (#+ Phase)]]])
(exception: #export (not-a-statement {code Code})
(exception.report
@@ -43,7 +43,7 @@
[macroA (type.with-type Macro
(analyze macro))]
(case macroA
- (^ (analysis.constant macro-name))
+ (^ (///analysis.constant macro-name))
(do @
[?macro (//extension.lift (macro.find-macro macro-name))
macro (case ?macro
diff --git a/stdlib/source/lux/tool/compiler/phase/synthesis.lux b/stdlib/source/lux/tool/compiler/phase/synthesis.lux
index 17af9a6fa..c5152ff6a 100644
--- a/stdlib/source/lux/tool/compiler/phase/synthesis.lux
+++ b/stdlib/source/lux/tool/compiler/phase/synthesis.lux
@@ -9,70 +9,69 @@
[collection
["." list ("#/." functor)]
["." dictionary (#+ Dictionary)]]]]
- [/
- ["/." function]
- ["/." case]
- ["." // ("#/." monad)
- ["//." extension]
- [//
- ["." reference]
- ["." analysis (#+ Analysis)]
+ ["." / #_
+ ["#." function]
+ ["#." case]
+ ["#/" // ("#/." monad)
+ ["#." extension]
+ ["#/" // #_
+ ["#." analysis (#+ Analysis)]
["/" synthesis (#+ Synthesis Phase)]]]])
(def: (primitive analysis)
- (-> analysis.Primitive /.Primitive)
+ (-> ///analysis.Primitive /.Primitive)
(case analysis
- #analysis.Unit
+ #///analysis.Unit
(#/.Text /.unit)
(^template [<analysis> <synthesis>]
(<analysis> value)
(<synthesis> value))
- ([#analysis.Bit #/.Bit]
- [#analysis.Frac #/.F64]
- [#analysis.Text #/.Text])
+ ([#///analysis.Bit #/.Bit]
+ [#///analysis.Frac #/.F64]
+ [#///analysis.Text #/.Text])
(^template [<analysis> <synthesis>]
(<analysis> value)
(<synthesis> (.i64 value)))
- ([#analysis.Nat #/.I64]
- [#analysis.Int #/.I64]
- [#analysis.Rev #/.I64])))
+ ([#///analysis.Nat #/.I64]
+ [#///analysis.Int #/.I64]
+ [#///analysis.Rev #/.I64])))
(def: #export (phase analysis)
Phase
(case analysis
- (#analysis.Primitive analysis')
+ (#///analysis.Primitive analysis')
(///wrap (#/.Primitive (..primitive analysis')))
- (#analysis.Structure structure)
+ (#///analysis.Structure structure)
(case structure
- (#analysis.Variant variant)
+ (#///analysis.Variant variant)
(do //.monad
- [valueS (phase (get@ #analysis.value variant))]
- (wrap (/.variant (set@ #analysis.value valueS variant))))
+ [valueS (phase (get@ #///analysis.value variant))]
+ (wrap (/.variant (set@ #///analysis.value valueS variant))))
- (#analysis.Tuple tuple)
+ (#///analysis.Tuple tuple)
(|> tuple
(monad.map //.monad phase)
(///map (|>> /.tuple))))
- (#analysis.Reference reference)
+ (#///analysis.Reference reference)
(///wrap (#/.Reference reference))
- (#analysis.Case inputA branchesAB+)
+ (#///analysis.Case inputA branchesAB+)
(/case.synthesize phase inputA branchesAB+)
- (^ (analysis.no-op value))
+ (^ (///analysis.no-op value))
(phase value)
- (#analysis.Apply _)
+ (#///analysis.Apply _)
(/function.apply phase analysis)
- (#analysis.Function environmentA bodyA)
+ (#///analysis.Function environmentA bodyA)
(/function.abstraction phase environmentA bodyA)
- (#analysis.Extension name args)
+ (#///analysis.Extension name args)
(function (_ state)
(|> (//extension.apply phase [name args])
(//.run' state)
diff --git a/stdlib/source/lux/tool/compiler/phase/synthesis/case.lux b/stdlib/source/lux/tool/compiler/phase/synthesis/case.lux
index 94a2637fe..52d7b09a7 100644
--- a/stdlib/source/lux/tool/compiler/phase/synthesis/case.lux
+++ b/stdlib/source/lux/tool/compiler/phase/synthesis/case.lux
@@ -14,9 +14,9 @@
[collection
["." list ("#/." fold monoid)]]]]
["." /// ("#/." monad)
- [//
- ["." reference]
- ["." analysis (#+ Pattern Match Analysis)]
+ ["#/" //
+ ["#." reference]
+ ["#." analysis (#+ Pattern Match Analysis)]
["/" synthesis (#+ Path Synthesis Operation Phase)]]])
(def: clean-up
@@ -26,28 +26,28 @@
(def: (path' pattern end? thenC)
(-> Pattern Bit (Operation Path) (Operation Path))
(case pattern
- (#analysis.Simple simple)
+ (#////analysis.Simple simple)
(case simple
- #analysis.Unit
+ #////analysis.Unit
thenC
(^template [<from> <to>]
(<from> value)
(////map (|>> (#/.Seq (#/.Test (|> value <to>))))
thenC))
- ([#analysis.Bit #/.Bit]
- [#analysis.Nat (<| #/.I64 .i64)]
- [#analysis.Int (<| #/.I64 .i64)]
- [#analysis.Rev (<| #/.I64 .i64)]
- [#analysis.Frac #/.F64]
- [#analysis.Text #/.Text]))
-
- (#analysis.Bind register)
+ ([#////analysis.Bit #/.Bit]
+ [#////analysis.Nat (<| #/.I64 .i64)]
+ [#////analysis.Int (<| #/.I64 .i64)]
+ [#////analysis.Rev (<| #/.I64 .i64)]
+ [#////analysis.Frac #/.F64]
+ [#////analysis.Text #/.Text]))
+
+ (#////analysis.Bind register)
(<| (:: ///.monad map (|>> (#/.Seq (#/.Bind register))))
/.with-new-local
thenC)
- (#analysis.Complex (#analysis.Variant [lefts right? value-pattern]))
+ (#////analysis.Complex (#////analysis.Variant [lefts right? value-pattern]))
(<| (////map (|>> (#/.Seq (#/.Access (#/.Side (if right?
(#.Right lefts)
(#.Left lefts)))))))
@@ -55,7 +55,7 @@
(when> [(new> (not end?) [])] [(////map ..clean-up)])
thenC)
- (#analysis.Complex (#analysis.Tuple tuple))
+ (#////analysis.Complex (#////analysis.Tuple tuple))
(let [tuple::last (dec (list.size tuple))]
(list/fold (function (_ [tuple::lefts tuple::member] nextC)
(let [right? (n/= tuple::last tuple::lefts)
@@ -125,12 +125,12 @@
(do ///.monad
[inputS (synthesize^ inputA)]
(with-expansions [<unnecesary-let>
- (as-is (^multi (^ (#analysis.Reference (reference.local outputR)))
+ (as-is (^multi (^ (#////analysis.Reference (////reference.local outputR)))
(n/= inputR outputR))
(wrap inputS))
<let>
- (as-is [[(#analysis.Bind inputR) headB/bodyA]
+ (as-is [[(#////analysis.Bind inputR) headB/bodyA]
#.Nil]
(case headB/bodyA
<unnecesary-let>
@@ -142,10 +142,10 @@
(wrap (/.branch/let [inputS inputR headB/bodyS])))))
<if>
- (as-is (^or (^ [[(analysis.pattern/bit #1) thenA]
- (list [(analysis.pattern/bit #0) elseA])])
- (^ [[(analysis.pattern/bit #0) elseA]
- (list [(analysis.pattern/bit #1) thenA])]))
+ (as-is (^or (^ [[(////analysis.pattern/bit #1) thenA]
+ (list [(////analysis.pattern/bit #0) elseA])])
+ (^ [[(////analysis.pattern/bit #0) elseA]
+ (list [(////analysis.pattern/bit #1) thenA])]))
(do @
[thenS (synthesize^ thenA)
elseS (synthesize^ elseA)]
diff --git a/stdlib/source/lux/tool/compiler/phase/synthesis/function.lux b/stdlib/source/lux/tool/compiler/phase/synthesis/function.lux
index b5c97e825..547e684c2 100644
--- a/stdlib/source/lux/tool/compiler/phase/synthesis/function.lux
+++ b/stdlib/source/lux/tool/compiler/phase/synthesis/function.lux
@@ -10,18 +10,18 @@
[collection
["." list ("#/." functor monoid fold)]
["dict" dictionary (#+ Dictionary)]]]]
- [//
- ["//." loop (#+ Transform)]
- ["/." // ("#/." monad)
- [//
- ["." reference (#+ Register Variable)]
- ["." analysis (#+ Environment Arity Analysis)]
+ ["." // #_
+ ["#." loop (#+ Transform)]
+ ["#/" // ("#/." monad)
+ ["#/" // #_
+ ["#." reference (#+ Register Variable)]
+ ["#." analysis (#+ Environment Arity Analysis)]
["/" synthesis (#+ Path Synthesis Operation Phase)]]]])
(exception: #export (cannot-find-foreign-variable-in-environment {foreign Register} {environment Environment})
(ex.report ["Foreign" (%n foreign)]
["Environment" (|> environment
- (list/map reference.%variable)
+ (list/map ////reference.%variable)
(text.join-with " "))]))
(def: arity-arguments
@@ -40,7 +40,7 @@
(def: #export (apply phase)
(-> Phase Phase)
(function (_ exprA)
- (let [[funcA argsA] (analysis.application exprA)]
+ (let [[funcA argsA] (////analysis.application exprA)]
(do ///.monad
[funcS (phase funcA)
argsS (monad.map @ phase argsA)
@@ -95,10 +95,10 @@
(monad.map ///.monad
(function (_ variable)
(case variable
- (#reference.Local register)
- (////wrap (#reference.Local (inc register)))
+ (#////reference.Local register)
+ (////wrap (#////reference.Local (inc register)))
- (#reference.Foreign register)
+ (#////reference.Foreign register)
(find-foreign super register)))
sub))
@@ -107,12 +107,12 @@
(case expression
(#/.Structure structure)
(case structure
- (#analysis.Variant [lefts right? subS])
+ (#////analysis.Variant [lefts right? subS])
(|> subS
(grow environment)
(////map (|>> [lefts right?] /.variant)))
- (#analysis.Tuple membersS+)
+ (#////analysis.Tuple membersS+)
(|> membersS+
(monad.map ///.monad (grow environment))
(////map (|>> /.tuple))))
@@ -122,17 +122,17 @@
(#/.Reference reference)
(case reference
- (#reference.Variable variable)
+ (#////reference.Variable variable)
(case variable
- (#reference.Local register)
+ (#////reference.Local register)
(////wrap (/.variable/local (inc register)))
- (#reference.Foreign register)
+ (#////reference.Foreign register)
(|> register
(find-foreign environment)
(////map (|>> /.variable))))
- (#reference.Constant constant)
+ (#////reference.Constant constant)
(////wrap expression))
(#/.Control control)
diff --git a/stdlib/source/lux/tool/compiler/phase/synthesis/loop.lux b/stdlib/source/lux/tool/compiler/phase/synthesis/loop.lux
index ecf13440b..ce5b5e3be 100644
--- a/stdlib/source/lux/tool/compiler/phase/synthesis/loop.lux
+++ b/stdlib/source/lux/tool/compiler/phase/synthesis/loop.lux
@@ -10,12 +10,12 @@
[macro
["." code]
["." syntax]]]
- [///
+ ["." /// #_
## TODO: Remove the 'extension' import ASAP.
- ["///." extension]
- [//
- ["." reference (#+ Register Variable)]
- ["." analysis (#+ Environment)]
+ ["#." extension]
+ ["#/" //
+ ["#." reference (#+ Register Variable)]
+ ["#." analysis (#+ Environment)]
["/" synthesis (#+ Path Abstraction Synthesis)]]])
(type: #export (Transform a)
@@ -28,7 +28,7 @@
#.None #0))
(template: #export (self)
- (#/.Reference (reference.local 0)))
+ (#/.Reference (////reference.local 0)))
(template: (recursive-apply args)
(#/.Apply (self) args))
@@ -44,10 +44,10 @@
(#/.Structure structure)
(case structure
- (#analysis.Variant variantS)
- (proper? (get@ #analysis.value variantS))
+ (#////analysis.Variant variantS)
+ (proper? (get@ #////analysis.value variantS))
- (#analysis.Tuple membersS+)
+ (#////analysis.Tuple membersS+)
(list.every? proper? membersS+))
(#/.Control controlS)
@@ -88,7 +88,7 @@
(#/.Function functionS)
(case functionS
(#/.Abstraction environment arity bodyS)
- (list.every? reference.self? environment)
+ (list.every? ////reference.self? environment)
(#/.Apply funcS argsS)
(and (proper? funcS)
@@ -165,7 +165,7 @@
(-> Environment (Transform Variable))
(function (_ variable)
(case variable
- (#reference.Foreign register)
+ (#////reference.Foreign register)
(list.nth register environment)
_
@@ -198,31 +198,31 @@
(case exprS
(#/.Structure structureS)
(case structureS
- (#analysis.Variant variantS)
+ (#////analysis.Variant variantS)
(do maybe.monad
- [valueS' (|> variantS (get@ #analysis.value) recur)]
+ [valueS' (|> variantS (get@ #////analysis.value) recur)]
(wrap (|> variantS
- (set@ #analysis.value valueS')
- #analysis.Variant
+ (set@ #////analysis.value valueS')
+ #////analysis.Variant
#/.Structure)))
- (#analysis.Tuple membersS+)
+ (#////analysis.Tuple membersS+)
(|> membersS+
(monad.map maybe.monad recur)
- (maybe/map (|>> #analysis.Tuple #/.Structure))))
+ (maybe/map (|>> #////analysis.Tuple #/.Structure))))
(#/.Reference reference)
(case reference
- (^ (reference.constant constant))
+ (^ (////reference.constant constant))
(#.Some exprS)
- (^ (reference.local register))
- (#.Some (#/.Reference (reference.local (n/+ offset register))))
+ (^ (////reference.local register))
+ (#.Some (#/.Reference (////reference.local (n/+ offset register))))
- (^ (reference.foreign register))
+ (^ (////reference.foreign register))
(|> scope-environment
(list.nth register)
- (maybe/map (|>> #reference.Variable #/.Reference))))
+ (maybe/map (|>> #////reference.Variable #/.Reference))))
(^ (/.branch/case [inputS pathS]))
(do maybe.monad
diff --git a/stdlib/source/lux/tool/compiler/synthesis.lux b/stdlib/source/lux/tool/compiler/synthesis.lux
index a287caf5e..1e56a90a3 100644
--- a/stdlib/source/lux/tool/compiler/synthesis.lux
+++ b/stdlib/source/lux/tool/compiler/synthesis.lux
@@ -11,10 +11,10 @@
[collection
["." list ("#/." functor)]
["." dictionary (#+ Dictionary)]]]]
- [//
- ["//." reference (#+ Register Variable Reference)]
- ["//." analysis (#+ Environment Arity Composite Analysis)]
- ["." phase
+ ["." // #_
+ ["#." reference (#+ Register Variable Reference)]
+ ["#." analysis (#+ Environment Arity Composite Analysis)]
+ ["#." phase
["." extension (#+ Extension)]]])
(type: #export Resolver (Dictionary Variable Variable))
@@ -192,7 +192,7 @@
(def: #export with-new-local
(All [a] (-> (Operation a) (Operation a)))
- (<<| (do phase.monad
+ (<<| (do //phase.monad
[locals ..locals])
(..with-locals (inc locals))))