aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2022-03-16 08:37:23 -0400
committerEduardo Julian2022-03-16 08:37:23 -0400
commitbf53ee92fc3c33a4885aa227e55d24f7ba3cb2c4 (patch)
tree49683a62ae8e110c62b42a9a6386bb2ddb3c47c6 /stdlib/source/library/lux/tool/compiler
parentd710d9f4fc098e7c243c8a5f23cd42683f13e07f (diff)
De-sigil-ification: prefix :
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux362
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux.lux88
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux40
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux30
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux36
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux154
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux42
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux42
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux78
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux38
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux70
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux102
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux34
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux78
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux34
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux68
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux90
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux56
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux30
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux56
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux20
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux52
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux38
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux56
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux94
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux92
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux56
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux48
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux50
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/key.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux30
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux142
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/module.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cli.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/export.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/import.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux232
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/context.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux24
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux44
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/script.lux14
79 files changed, 1457 insertions, 1457 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 48a1fb475..9f615c86e 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -146,7 +146,7 @@
(do ///phase.monad
[_ (///directive.lifted_analysis
(moduleA.set_compiled module))
- analysis_module (<| (: (Operation .Module))
+ analysis_module (<| (is (Operation .Module))
///directive.lifted_analysis
extension.lifted
meta.current_module)
@@ -276,7 +276,7 @@
///.#process (function (_ state archive)
(again (<| (///phase.result' state)
(do [! ///phase.monad]
- [analysis_module (<| (: (Operation .Module))
+ [analysis_module (<| (is (Operation .Module))
///directive.lifted_analysis
extension.lifted
meta.current_module)
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index b4c2a8be8..0a69b7995 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -29,7 +29,7 @@
["_" binary {"+" Writer}]]]
["[0]" meta
["[0]" configuration {"+" Configuration}]]
- [type {"+" :sharing}
+ [type {"+" sharing}
["[0]" check]]
[world
["[0]" file {"+" Path}]
@@ -89,8 +89,8 @@
... TODO: Get rid of this
(def: monad
- (:as (Monad Action)
- (try.with async.monad)))
+ (as (Monad Action)
+ (try.with async.monad)))
(with_expansions [<Platform> (as_is (Platform <type_vars>))
<State+> (as_is (///directive.State+ <type_vars>))
@@ -113,23 +113,23 @@
(-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document)
(Async (Try Any))))
(let [system (the #&file_system platform)
- write_artifact! (: (-> [artifact.ID (Maybe Text) Binary] (Action Any))
- (function (_ [artifact_id custom content])
- (cache/artifact.cache! system context @module artifact_id content)))]
+ write_artifact! (is (-> [artifact.ID (Maybe Text) Binary] (Action Any))
+ (function (_ [artifact_id custom content])
+ (cache/artifact.cache! system context @module artifact_id content)))]
(do [! ..monad]
- [_ (: (Async (Try Any))
- (cache/module.enable! async.monad system context @module))
+ [_ (is (Async (Try Any))
+ (cache/module.enable! async.monad system context @module))
_ (for @.python (|> entry
(the archive.#output)
sequence.list
(list.sub 128)
(monad.each ! (monad.each ! write_artifact!))
- (: (Action (List (List Any)))))
+ (is (Action (List (List Any)))))
(|> entry
(the archive.#output)
sequence.list
(monad.each ..monad write_artifact!)
- (: (Action (List Any)))))
+ (is (Action (List Any)))))
document (# async.monad in
(document.marked? key (the [archive.#module module.#document] entry)))]
(|> [(|> entry
@@ -203,22 +203,22 @@
.Lux
<State+>
(Try <State+>)))
- (|> (:sharing [<type_vars>]
- <State+>
- state
-
- (///directive.Operation <type_vars> Any)
- (do [! ///phase.monad]
- [_ (///directive.lifted_analysis
- (do !
- [_ (///analysis.set_state analysis_state)]
- (extension.with extender analysers)))
- _ (///directive.lifted_synthesis
- (extension.with extender synthesizers))
- _ (///directive.lifted_generation
- (extension.with extender (:expected generators)))
- _ (extension.with extender (:expected directives))]
- (in [])))
+ (|> (sharing [<type_vars>]
+ <State+>
+ state
+
+ (///directive.Operation <type_vars> Any)
+ (do [! ///phase.monad]
+ [_ (///directive.lifted_analysis
+ (do !
+ [_ (///analysis.set_state analysis_state)]
+ (extension.with extender analysers)))
+ _ (///directive.lifted_synthesis
+ (extension.with extender synthesizers))
+ _ (///directive.lifted_generation
+ (extension.with extender (as_expected generators)))
+ _ (extension.with extender (as_expected directives))]
+ (in [])))
(///phase.result' state)
(# try.monad each product.left)))
@@ -270,23 +270,23 @@
(the #host platform)
(the #phase platform)
generation_bundle)]
- _ (: (Async (Try Any))
- (cache.enable! async.monad (the #&file_system platform) context))
+ _ (is (Async (Try Any))
+ (cache.enable! async.monad (the #&file_system platform) context))
[archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (the #host platform) (the #&file_system platform) context import compilation_sources)
.let [with_missing_extensions
- (: (All (_ <type_vars>)
- (-> <Platform> (Program expression directive) <State+>
- (Async (Try [///phase.Wrapper <State+>]))))
- (function (_ platform program state)
- (async#in
- (do try.monad
- [[state phase_wrapper] (..phase_wrapper archive platform state)]
- (|> state
- (initialize_state (extender phase_wrapper)
- (:expected (..complete_extensions host_directive_bundle phase_wrapper (:expected bundles)))
- analysis_state)
- (try#each (|>> (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper))
- [phase_wrapper])))))))]]
+ (is (All (_ <type_vars>)
+ (-> <Platform> (Program expression directive) <State+>
+ (Async (Try [///phase.Wrapper <State+>]))))
+ (function (_ platform program state)
+ (async#in
+ (do try.monad
+ [[state phase_wrapper] (..phase_wrapper archive platform state)]
+ (|> state
+ (initialize_state (extender phase_wrapper)
+ (as_expected (..complete_extensions host_directive_bundle phase_wrapper (as_expected bundles)))
+ analysis_state)
+ (try#each (|>> (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper))
+ [phase_wrapper])))))))]]
(if (archive.archived? archive descriptor.runtime)
(do !
[[phase_wrapper state] (with_missing_extensions platform program state)]
@@ -345,26 +345,26 @@
(def: (depend module import dependence)
(-> descriptor.Module descriptor.Module Dependence Dependence)
- (let [transitive_dependency (: (-> (-> Dependence Mapping) descriptor.Module (Set descriptor.Module))
- (function (_ lens module)
- (|> dependence
- lens
- (dictionary.value module)
- (maybe.else ..empty))))
+ (let [transitive_dependency (is (-> (-> Dependence Mapping) descriptor.Module (Set descriptor.Module))
+ (function (_ lens module)
+ (|> dependence
+ lens
+ (dictionary.value module)
+ (maybe.else ..empty))))
transitive_depends_on (transitive_dependency (the #depends_on) import)
transitive_depended_by (transitive_dependency (the #depended_by) module)
- update_dependence (: (-> [descriptor.Module (Set descriptor.Module)] [descriptor.Module (Set descriptor.Module)]
- (-> Mapping Mapping))
- (function (_ [source forward] [target backward])
- (function (_ mapping)
- (let [with_dependence+transitives
- (|> mapping
- (dictionary.revised' source ..empty (set.has target))
- (dictionary.revised source (set.union forward)))]
- (list#mix (function (_ previous)
- (dictionary.revised' previous ..empty (set.has target)))
- with_dependence+transitives
- (set.list backward))))))]
+ update_dependence (is (-> [descriptor.Module (Set descriptor.Module)] [descriptor.Module (Set descriptor.Module)]
+ (-> Mapping Mapping))
+ (function (_ [source forward] [target backward])
+ (function (_ mapping)
+ (let [with_dependence+transitives
+ (|> mapping
+ (dictionary.revised' source ..empty (set.has target))
+ (dictionary.revised source (set.union forward)))]
+ (list#mix (function (_ previous)
+ (dictionary.revised' previous ..empty (set.has target)))
+ with_dependence+transitives
+ (set.list backward))))))]
(|> dependence
(revised #depends_on
(update_dependence
@@ -377,13 +377,13 @@
(def: (circular_dependency? module import dependence)
(-> descriptor.Module descriptor.Module Dependence Bit)
- (let [dependence? (: (-> descriptor.Module (-> Dependence Mapping) descriptor.Module Bit)
- (function (_ from relationship to)
- (let [targets (|> dependence
- relationship
- (dictionary.value from)
- (maybe.else ..empty))]
- (set.member? targets to))))]
+ (let [dependence? (is (-> descriptor.Module (-> Dependence Mapping) descriptor.Module Bit)
+ (function (_ from relationship to)
+ (let [targets (|> dependence
+ relationship
+ (dictionary.value from)
+ (maybe.else ..empty))]
+ (set.member? targets to))))]
(or (dependence? import (the #depends_on) module)
(dependence? module (the #depended_by) import))))
@@ -495,74 +495,74 @@
(-> Lux_Context
(-> Lux_Compiler Lux_Importer)))
(let [current (stm.var initial)
- pending (:sharing [<type_vars>]
- Lux_Context
- initial
-
- (Var (Dictionary descriptor.Module Lux_Pending))
- (:expected (stm.var (dictionary.empty text.hash))))
- dependence (: (Var Dependence)
- (stm.var ..independence))]
+ pending (sharing [<type_vars>]
+ Lux_Context
+ initial
+
+ (Var (Dictionary descriptor.Module Lux_Pending))
+ (as_expected (stm.var (dictionary.empty text.hash))))
+ dependence (is (Var Dependence)
+ (stm.var ..independence))]
(function (_ compile)
(function (import! customs importer module)
(do [! async.monad]
- [[return signal] (:sharing [<type_vars>]
- Lux_Context
- initial
-
- (Async [Lux_Return (Maybe [Lux_Context
- module.ID
- Lux_Signal])])
- (:expected
- (stm.commit!
- (do [! stm.monad]
- [dependence (if (text#= descriptor.runtime importer)
- (stm.read dependence)
- (do !
- [[_ dependence] (stm.update (..depend importer module) dependence)]
- (in dependence)))]
- (case (..verify_dependencies importer module dependence)
- {try.#Failure error}
- (in [(async.resolved {try.#Failure error})
- {.#None}])
-
- {try.#Success _}
- (do !
- [[archive state] (stm.read current)]
- (if (archive.archived? archive module)
- (in [(async#in {try.#Success [archive state]})
- {.#None}])
- (do !
- [@pending (stm.read pending)]
- (case (dictionary.value module @pending)
- {.#Some [return signal]}
- (in [return
- {.#None}])
-
- {.#None}
- (case (if (archive.reserved? archive module)
- (do try.monad
- [@module (archive.id module archive)]
- (in [@module archive]))
- (archive.reserve module archive))
- {try.#Success [@module archive]}
- (do !
- [_ (stm.write [archive state] current)
- .let [[return signal] (:sharing [<type_vars>]
- Lux_Context
- initial
-
- Lux_Pending
- (async.async []))]
- _ (stm.update (dictionary.has module [return signal]) pending)]
- (in [return
- {.#Some [[archive state]
- @module
- signal]}]))
-
- {try.#Failure error}
- (in [(async#in {try.#Failure error})
- {.#None}])))))))))))
+ [[return signal] (sharing [<type_vars>]
+ Lux_Context
+ initial
+
+ (Async [Lux_Return (Maybe [Lux_Context
+ module.ID
+ Lux_Signal])])
+ (as_expected
+ (stm.commit!
+ (do [! stm.monad]
+ [dependence (if (text#= descriptor.runtime importer)
+ (stm.read dependence)
+ (do !
+ [[_ dependence] (stm.update (..depend importer module) dependence)]
+ (in dependence)))]
+ (case (..verify_dependencies importer module dependence)
+ {try.#Failure error}
+ (in [(async.resolved {try.#Failure error})
+ {.#None}])
+
+ {try.#Success _}
+ (do !
+ [[archive state] (stm.read current)]
+ (if (archive.archived? archive module)
+ (in [(async#in {try.#Success [archive state]})
+ {.#None}])
+ (do !
+ [@pending (stm.read pending)]
+ (case (dictionary.value module @pending)
+ {.#Some [return signal]}
+ (in [return
+ {.#None}])
+
+ {.#None}
+ (case (if (archive.reserved? archive module)
+ (do try.monad
+ [@module (archive.id module archive)]
+ (in [@module archive]))
+ (archive.reserve module archive))
+ {try.#Success [@module archive]}
+ (do !
+ [_ (stm.write [archive state] current)
+ .let [[return signal] (sharing [<type_vars>]
+ Lux_Context
+ initial
+
+ Lux_Pending
+ (async.async []))]
+ _ (stm.update (dictionary.has module [return signal]) pending)]
+ (in [return
+ {.#Some [[archive state]
+ @module
+ signal]}]))
+
+ {try.#Failure error}
+ (in [(async#in {try.#Failure error})
+ {.#None}])))))))))))
_ (case signal
{.#None}
(in [])
@@ -600,23 +600,23 @@
.let [additions (|> modules
(list#each product.left)
(set.of_list text.hash))
- with_modules (: (All (_ <type_vars>)
- (-> <State+> <State+>))
- (revised [extension.#state
- ///directive.#analysis
- ///directive.#state
- extension.#state]
- (: (All (_ a) (-> a a))
- (function (_ analysis_state)
- (|> analysis_state
- (:as .Lux)
- (revised .#modules (function (_ current)
- (list#composite (list.only (|>> product.left
- (set.member? additions)
- not)
- current)
- modules)))
- :expected)))))]
+ with_modules (is (All (_ <type_vars>)
+ (-> <State+> <State+>))
+ (revised [extension.#state
+ ///directive.#analysis
+ ///directive.#state
+ extension.#state]
+ (is (All (_ a) (-> a a))
+ (function (_ analysis_state)
+ (|> analysis_state
+ (as .Lux)
+ (revised .#modules (function (_ current)
+ (list#composite (list.only (|>> product.left
+ (set.member? additions)
+ not)
+ current)
+ modules)))
+ as_expected)))))]
state (monad.mix ! with_all_extensions state extended_states)]
(in (with_modules state))))
@@ -633,18 +633,18 @@
... This might not be the case in the future.
(def: (with_new_dependencies new_dependencies all_dependencies)
(-> (List descriptor.Module) (Set descriptor.Module) [(Set descriptor.Module) (Set descriptor.Module)])
- (let [[all_dependencies duplicates _] (: [(Set descriptor.Module) (Set descriptor.Module) Bit]
- (list#mix (function (_ new [all duplicates seen_prelude?])
- (if (set.member? all new)
- (if (text#= .prelude_module new)
- (if seen_prelude?
- [all (set.has new duplicates) seen_prelude?]
- [all duplicates true])
- [all (set.has new duplicates) seen_prelude?])
- [(set.has new all) duplicates seen_prelude?]))
- (: [(Set descriptor.Module) (Set descriptor.Module) Bit]
- [all_dependencies ..empty (set.empty? all_dependencies)])
- new_dependencies))]
+ (let [[all_dependencies duplicates _] (is [(Set descriptor.Module) (Set descriptor.Module) Bit]
+ (list#mix (function (_ new [all duplicates seen_prelude?])
+ (if (set.member? all new)
+ (if (text#= .prelude_module new)
+ (if seen_prelude?
+ [all (set.has new duplicates) seen_prelude?]
+ [all duplicates true])
+ [all (set.has new duplicates) seen_prelude?])
+ [(set.has new all) duplicates seen_prelude?]))
+ (is [(Set descriptor.Module) (Set descriptor.Module) Bit]
+ [all_dependencies ..empty (set.empty? all_dependencies)])
+ new_dependencies))]
[all_dependencies duplicates]))
(def: (any|after_imports customs import! module duplicates new_dependencies archive)
@@ -713,8 +713,8 @@
(function (_ customs importer import! @module [archive state] module)
(loop [[archive state] [archive state]
compilation custom_compilation
- all_dependencies (: (Set descriptor.Module)
- (set.of_list text.hash (list)))]
+ all_dependencies (is (Set descriptor.Module)
+ (set.of_list text.hash (list)))]
(do [! (try.with async.monad)]
[.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
@@ -723,13 +723,13 @@
{try.#Success [state more|done]}
(case more|done
{.#Left more}
- (let [continue! (:sharing [state document object]
- (///.Compilation state document object)
- custom_compilation
-
- (-> (..Context state) (///.Compilation state document object) (Set descriptor.Module)
- (..Return state))
- (:expected again))]
+ (let [continue! (sharing [state document object]
+ (///.Compilation state document object)
+ custom_compilation
+
+ (-> (..Context state) (///.Compilation state document object) (Set descriptor.Module)
+ (..Return state))
+ (as_expected again))]
(continue! [archive state] more all_dependencies))
{.#Right entry}
@@ -753,8 +753,8 @@
(function (_ customs importer import! @module [archive state] module)
(loop [[archive state] [archive (..set_current_module module state)]
compilation compilation
- all_dependencies (: (Set descriptor.Module)
- (set.of_list text.hash (list)))]
+ all_dependencies (is (Set descriptor.Module)
+ (set.of_list text.hash (list)))]
(do [! (try.with async.monad)]
[.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
@@ -763,13 +763,13 @@
{try.#Success [state more|done]}
(case more|done
{.#Left more}
- (let [continue! (:sharing [<type_vars>]
- <Platform>
- platform
-
- (-> Lux_Context (///.Compilation <State+> .Module Any) (Set descriptor.Module)
- (Action [Archive <State+>]))
- (:expected again))]
+ (let [continue! (sharing [<type_vars>]
+ <Platform>
+ platform
+
+ (-> Lux_Context (///.Compilation <State+> .Module Any) (Set descriptor.Module)
+ (Action [Archive <State+>]))
+ (as_expected again))]
(continue! [archive state] more all_dependencies))
{.#Right entry}
@@ -784,7 +784,7 @@
(console.write_line report console))
<else>)))
.let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
- _ (..cache_module context platform @module $.key $.writer (:as (archive.Entry .Module) entry))]
+ _ (..cache_module context platform @module $.key $.writer (as (archive.Entry .Module) entry))]
(async#in (do try.monad
[archive (archive.has module entry archive)]
(in [archive
@@ -820,8 +820,8 @@
compilation_sources
(the context.#host_module_extension context)
module)]
- (loop [customs (for @.old (:as (List (///.Custom Fake_State Fake_Document Fake_Object))
- all_customs)
+ (loop [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object))
+ all_customs)
all_customs)]
(case customs
{.#End}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux
index d5b883eed..f237ebeae 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux
@@ -22,24 +22,24 @@
... TODO: Not just from this parser, but from the lux.Module type.
(def: .public writer
(Writer .Module)
- (let [definition (: (Writer Definition)
- ($_ _.and _.bit _.type _.any))
- labels (: (Writer [Text (List Text)])
- (_.and _.text (_.list _.text)))
- global_type (: (Writer [Bit Type (Either [Text (List Text)]
- [Text (List Text)])])
- ($_ _.and _.bit _.type (_.or labels labels)))
- global_label (: (Writer .Label)
- ($_ _.and _.bit _.type (_.list _.text) _.nat))
- alias (: (Writer Alias)
- (_.and _.text _.text))
- global (: (Writer Global)
- ($_ _.or
- definition
- global_type
- global_label
- global_label
- alias))]
+ (let [definition (is (Writer Definition)
+ ($_ _.and _.bit _.type _.any))
+ labels (is (Writer [Text (List Text)])
+ (_.and _.text (_.list _.text)))
+ global_type (is (Writer [Bit Type (Either [Text (List Text)]
+ [Text (List Text)])])
+ ($_ _.and _.bit _.type (_.or labels labels)))
+ global_label (is (Writer .Label)
+ ($_ _.and _.bit _.type (_.list _.text) _.nat))
+ alias (is (Writer Alias)
+ (_.and _.text _.text))
+ global (is (Writer Global)
+ ($_ _.or
+ definition
+ global_type
+ global_label
+ global_label
+ alias))]
($_ _.and
... #module_hash
_.nat
@@ -54,38 +54,38 @@
(def: .public parser
(Parser .Module)
- (let [definition (: (Parser Definition)
- ($_ <>.and
- <binary>.bit
- <binary>.type
- <binary>.any))
- labels (: (Parser [Text (List Text)])
- ($_ <>.and
- <binary>.text
- (<binary>.list <binary>.text)))
- global_type (: (Parser [Bit Type (Either [Text (List Text)]
- [Text (List Text)])])
+ (let [definition (is (Parser Definition)
($_ <>.and
<binary>.bit
<binary>.type
- (<binary>.or labels labels)))
- global_label (: (Parser .Label)
+ <binary>.any))
+ labels (is (Parser [Text (List Text)])
+ ($_ <>.and
+ <binary>.text
+ (<binary>.list <binary>.text)))
+ global_type (is (Parser [Bit Type (Either [Text (List Text)]
+ [Text (List Text)])])
($_ <>.and
<binary>.bit
<binary>.type
- (<binary>.list <binary>.text)
- <binary>.nat))
- alias (: (Parser Alias)
- ($_ <>.and
- <binary>.text
- <binary>.text))
- global (: (Parser Global)
- ($_ <binary>.or
- definition
- global_type
- global_label
- global_label
- alias))]
+ (<binary>.or labels labels)))
+ global_label (is (Parser .Label)
+ ($_ <>.and
+ <binary>.bit
+ <binary>.type
+ (<binary>.list <binary>.text)
+ <binary>.nat))
+ alias (is (Parser Alias)
+ ($_ <>.and
+ <binary>.text
+ <binary>.text))
+ global (is (Parser Global)
+ ($_ <binary>.or
+ definition
+ global_type
+ global_label
+ global_label
+ alias))]
($_ <>.and
... #module_hash
<binary>.nat
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
index 1828747ab..24c60d5fa 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -160,8 +160,8 @@
(def: .public (reification analysis)
(-> Analysis (Reification Analysis))
(loop [abstraction analysis
- inputs (: (List Analysis)
- (list))]
+ inputs (is (List Analysis)
+ (list))]
(.case abstraction
{#Apply input next}
(again next {.#Item input inputs})
@@ -377,5 +377,5 @@
.#seed 0
.#scope_type_vars (list)
.#extensions []
- .#eval (:as (-> Type Code (Meta Any)) [])
+ .#eval (as (-> Type Code (Meta Any)) [])
.#host []])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
index 9c2aa022e..0484b5941 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
@@ -367,26 +367,26 @@
... merges can be done.
[_ {#Alt leftS rightS}]
(do [! try.monad]
- [.let [fuse_once (: (-> Coverage (List Coverage)
- (Try [(Maybe Coverage)
- (List Coverage)]))
- (function (_ coverageA possibilitiesSF)
- (loop [altsSF possibilitiesSF]
- (case altsSF
- {.#End}
- (in [{.#None} (list coverageA)])
-
- {.#Item altSF altsSF'}
- (do !
- [altMSF (composite coverageA altSF)]
- (case altMSF
- {#Alt _}
- (do !
- [[success altsSF+] (again altsSF')]
- (in [success {.#Item altSF altsSF+}]))
-
- _
- (in [{.#Some altMSF} altsSF'])))))))]]
+ [.let [fuse_once (is (-> Coverage (List Coverage)
+ (Try [(Maybe Coverage)
+ (List Coverage)]))
+ (function (_ coverageA possibilitiesSF)
+ (loop [altsSF possibilitiesSF]
+ (case altsSF
+ {.#End}
+ (in [{.#None} (list coverageA)])
+
+ {.#Item altSF altsSF'}
+ (do !
+ [altMSF (composite coverageA altSF)]
+ (case altMSF
+ {#Alt _}
+ (do !
+ [[success altsSF+] (again altsSF')]
+ (in [success {.#Item altSF altsSF+}]))
+
+ _
+ (in [{.#Some altMSF} altsSF'])))))))]]
(loop [addition addition
possibilitiesSF (alternatives so_far)]
(do !
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
index 3ca408bea..de22db2db 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
@@ -1,7 +1,7 @@
(.using
[library
[lux "*"
- [type {"+" :sharing}]
+ [type {"+" sharing}]
["[0]" meta]
[abstract
[monad {"+" do}]]
@@ -62,12 +62,12 @@
[exprS (|> exprA (synthesisP.phase archive) (phase.result synthesis_state))])
(phase.result generation_state)
(do phase.monad
- [@module (:sharing [anchor expression artifact]
- (generation.Phase anchor expression artifact)
- generate
+ [@module (sharing [anchor expression artifact]
+ (generation.Phase anchor expression artifact)
+ generate
- (generation.Operation anchor expression artifact module.ID)
- (generation.module_id module archive))
+ (generation.Operation anchor expression artifact module.ID)
+ (generation.module_id module archive))
.let [[evals _] (io.run! (atom.update! (dictionary.revised' @module 0 ++) ..evals))
@eval (maybe.else 0 (dictionary.value @module evals))]
exprO (<| (generation.with_registry_shift (|> @module
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
index 0d22a6790..1a95a5a2c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
@@ -99,8 +99,8 @@
[self_name meta.current_module_name]
(function (_ state)
{try.#Success [(revised .#modules
- (plist.revised self_name (revised .#module_aliases (: (-> (List [Text Text]) (List [Text Text]))
- (|>> {.#Item [alias module]}))))
+ (plist.revised self_name (revised .#module_aliases (is (-> (List [Text Text]) (List [Text Text]))
+ (|>> {.#Item [alias module]}))))
state)
[]]}))))
@@ -127,8 +127,8 @@
{try.#Success [(revised .#modules
(plist.has self_name
(revised .#definitions
- (: (-> (List [Text Global]) (List [Text Global]))
- (|>> {.#Item [name definition]}))
+ (is (-> (List [Text Global]) (List [Text Global]))
+ (|>> {.#Item [name definition]}))
self))
state)
[]]}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
index 42ccf412d..6902cd718 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
@@ -90,15 +90,15 @@
{.#Item top_outer _}
(let [[ref_type init_ref] (maybe.else (undefined)
(..reference name top_outer))
- [ref inner'] (list#mix (: (-> Scope [Variable (List Scope)] [Variable (List Scope)])
- (function (_ scope ref+inner)
- [{variable.#Foreign (the [.#captured .#counter] scope)}
- {.#Item (revised .#captured
- (: (-> Foreign Foreign)
- (|>> (revised .#counter ++)
- (revised .#mappings (plist.has name [ref_type (product.left ref+inner)]))))
- scope)
- (product.right ref+inner)}]))
+ [ref inner'] (list#mix (is (-> Scope [Variable (List Scope)] [Variable (List Scope)])
+ (function (_ scope ref+inner)
+ [{variable.#Foreign (the [.#captured .#counter] scope)}
+ {.#Item (revised .#captured
+ (is (-> Foreign Foreign)
+ (|>> (revised .#counter ++)
+ (revised .#mappings (plist.has name [ref_type (product.left ref+inner)]))))
+ scope)
+ (product.right ref+inner)}]))
[init_ref {.#End}]
(list.reversed inner))
scopes (list#composite inner' outer)]
@@ -117,9 +117,9 @@
(let [old_mappings (the [.#locals .#mappings] head)
new_var_id (the [.#locals .#counter] head)
new_head (revised .#locals
- (: (-> Local Local)
- (|>> (revised .#counter ++)
- (revised .#mappings (plist.has name [type new_var_id]))))
+ (is (-> Local Local)
+ (|>> (revised .#counter ++)
+ (revised .#mappings (plist.has name [type new_var_id]))))
head)]
(case (phase.result' [bundle (has .#scopes {.#Item new_head tail} state)]
action)
@@ -142,9 +142,9 @@
(def: empty
Scope
- (let [bindings (: Bindings
- [.#counter 0
- .#mappings (list)])]
+ (let [bindings (is Bindings
+ [.#counter 0
+ .#mappings (list)])]
[.#name (list)
.#inner 0
.#locals bindings
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
index 724d85a24..b215fa8b0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
@@ -84,7 +84,7 @@
... (if (n.< (the .#var_counter post)
... pre#var_counter)
... (do !
- ... [.let [new! (: (-> [Nat (Maybe Type)] (Maybe Nat))
+ ... [.let [new! (is (-> [Nat (Maybe Type)] (Maybe Nat))
... (function (_ [id _])
... (if (n.< id pre#var_counter)
... {.#Some id}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
index 706603273..2b9f8b598 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -57,19 +57,19 @@
(type: .public (Host expression directive)
(Interface
- (: (-> unit.ID [(Maybe unit.ID) expression] (Try Any))
- evaluate)
- (: (-> directive (Try Any))
- execute)
- (: (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive]))
- define)
-
- (: (-> unit.ID Binary directive)
- ingest)
- (: (-> unit.ID (Maybe Text) directive (Try Any))
- re_learn)
- (: (-> unit.ID (Maybe Text) directive (Try Any))
- re_load)))
+ (is (-> unit.ID [(Maybe unit.ID) expression] (Try Any))
+ evaluate)
+ (is (-> directive (Try Any))
+ execute)
+ (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive]))
+ define)
+
+ (is (-> unit.ID Binary directive)
+ ingest)
+ (is (-> unit.ID (Maybe Text) directive (Try Any))
+ re_learn)
+ (is (-> unit.ID (Maybe Text) directive (Try Any))
+ re_load)))
(type: .public (State anchor expression directive)
(Record
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index c999697dd..a35c61eb3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -89,8 +89,8 @@
... type-check the input with respect to the patterns.
(def: .public (tuple :it:)
(-> Type (Check [(List check.Var) Type]))
- (loop [envs (: (List (List Type))
- (list))
+ (loop [envs (is (List (List Type))
+ (list))
:it: :it:]
(.case :it:
{.#Var id}
@@ -167,8 +167,8 @@
{.#Product _}
(let [matches (loop [types (type.flat_tuple :input:')
patterns sub_patterns
- output (: (List [Type Code])
- {.#End})]
+ output (is (List [Type Code])
+ {.#End})]
(.case [types patterns]
[{.#End} {.#End}]
output
@@ -188,15 +188,15 @@
_
(undefined)))]
(do !
- [[memberP+ thenA] (list#mix (: (All (_ a)
- (-> [Type Code] (Operation [(List Pattern) a])
- (Operation [(List Pattern) a])))
- (function (_ [memberT memberC] then)
- (do !
- [[memberP [memberP+ thenA]] ((:as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])))
+ [[memberP+ thenA] (list#mix (is (All (_ a)
+ (-> [Type Code] (Operation [(List Pattern) a])
+ (Operation [(List Pattern) a])))
+ (function (_ [memberT memberC] then)
+ (do !
+ [[memberP [memberP+ thenA]] ((as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])))
pattern_analysis)
- {.#None} memberT memberC then)]
- (in [(list& memberP memberP+) thenA]))))
+ {.#None} memberT memberC then)]
+ (in [(list& memberP memberP+) thenA]))))
(do !
[nextA next]
(in [(list) nextA]))
@@ -253,13 +253,13 @@
(/.with_location location
(do [! ///.monad]
[record (//complex.normal true sub_patterns)
- record_size,members,recordT (: (Operation (Maybe [Nat (List Code) Type]))
- (.case record
- {.#Some record}
- (//complex.order true record)
+ record_size,members,recordT (is (Operation (Maybe [Nat (List Code) Type]))
+ (.case record
+ {.#Some record}
+ (//complex.order true record)
- {.#None}
- (in {.#None})))]
+ {.#None}
+ (in {.#None})))]
(.case record_size,members,recordT
{.#Some [record_size members recordT]}
(do !
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
index eb34d19c2..2a8279ae8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
@@ -192,7 +192,7 @@
(-> Phase Type Archive (List Code) (Operation Analysis))
(<| (let [! ///.monad])
(# ! each (|>> /.tuple))
- (: (Operation (List Analysis)))
+ (is (Operation (List Analysis)))
(loop [membersT+ (type.flat_tuple expectedT)
membersC+ members]
(case [membersT+ membersC+]
@@ -293,8 +293,8 @@
(def: .public (normal pattern_matching? record)
(-> Bit (List Code) (Operation (Maybe (List [Symbol Code]))))
(loop [input record
- output (: (List [Symbol Code])
- {.#End})]
+ output (is (List [Symbol Code])
+ {.#End})]
(case input
(pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail))
(if pattern_matching?
@@ -352,8 +352,8 @@
{.#None}
(/.except ..slot_does_not_belong_to_record [key recordT]))))
- (: (Dictionary Nat Code)
- (dictionary.empty n.hash))
+ (is (Dictionary Nat Code)
+ (dictionary.empty n.hash))
record)
.let [ordered_tuple (list#each (function (_ idx)
(maybe.trusted (dictionary.value idx idx->val)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
index bfd85814a..eb3cfa9ba 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
@@ -87,7 +87,7 @@
(the [//extension.#state /.#synthesis /.#state] state)
(the [//extension.#state /.#generation /.#state] state)
(the [//extension.#state /.#generation /.#phase] state)))
- extension_eval (:as Eval (wrapper (:expected compiler_eval)))]
+ extension_eval (as Eval (wrapper (as_expected compiler_eval)))]
_ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))]
(case code
(pattern [_ {.#Form (list& [_ {.#Text name}] inputs)}])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 6a8793379..ea51560df 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -416,18 +416,18 @@
{.#None}
(do [! phase.monad]
- [parametersJT (: (Operation (List (Type Parameter)))
- (monad.each !
- (function (_ parameterT)
- (do phase.monad
- [parameterJT (jvm_type parameterT)]
- (case (parser.parameter? parameterJT)
- {.#Some parameterJT}
- (in parameterJT)
-
- {.#None}
- (/////analysis.except ..non_parameter parameterT))))
- parametersT))]
+ [parametersJT (is (Operation (List (Type Parameter)))
+ (monad.each !
+ (function (_ parameterT)
+ (do phase.monad
+ [parameterJT (jvm_type parameterT)]
+ (case (parser.parameter? parameterJT)
+ {.#Some parameterJT}
+ (in parameterJT)
+
+ {.#None}
+ (/////analysis.except ..non_parameter parameterT))))
+ parametersT))]
(in (jvm.class class parametersJT))))
{.#Ex _}
@@ -869,10 +869,10 @@
(analyse archive exceptionC))
[exception_class _] (check_object exceptionT)
? (phase.lifted (reflection!.sub? class_loader "java.lang.Throwable" exception_class))
- _ (: (Operation Any)
- (if ?
- (in [])
- (/////analysis.except non_throwable exception_class)))]
+ _ (is (Operation Any)
+ (if ?
+ (in [])
+ (/////analysis.except non_throwable exception_class)))]
(in {/////analysis.#Extension extension_name (list exceptionA)}))
_
@@ -932,7 +932,7 @@
{.#None}
(if (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers source_class))
- {.#Item (:as java/lang/reflect/Type (ffi.class_for java/lang/Object))
+ {.#Item (as java/lang/reflect/Type (ffi.class_for java/lang/Object))
(array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))}
(array.list {.#None} (java/lang/Class::getGenericInterfaces source_class)))))))
@@ -963,50 +963,50 @@
[fromT fromA] (typeA.inferring
(analyse archive fromC))
source_name (# ! each ..reflection (check_jvm fromT))
- can_cast? (: (Operation Bit)
- (`` (cond (~~ (template [<primitive> <object>]
- [(let [=primitive (reflection.reflection <primitive>)]
- (or (and (text#= =primitive source_name)
- (or (text#= <object> target_name)
- (text#= =primitive target_name)))
- (and (text#= <object> source_name)
- (text#= =primitive target_name))))
- (in true)]
-
- [reflection.boolean box.boolean]
- [reflection.byte box.byte]
- [reflection.short box.short]
- [reflection.int box.int]
- [reflection.long box.long]
- [reflection.float box.float]
- [reflection.double box.double]
- [reflection.char box.char]))
-
- ... else
- (do !
- [_ (phase.assertion ..primitives_are_not_objects [source_name]
- (not (dictionary.key? ..boxes source_name)))
- _ (phase.assertion ..primitives_are_not_objects [target_name]
- (not (dictionary.key? ..boxes target_name)))
- target_class (phase.lifted (reflection!.load class_loader target_name))
- _ (do !
- [source_class (phase.lifted (reflection!.load class_loader source_name))]
- (phase.assertion ..cannot_cast [fromT toT fromC]
- (java/lang/Class::isAssignableFrom source_class target_class)))]
- (loop [[current_name currentT] [source_name fromT]]
- (if (text#= target_name current_name)
- (in true)
- (do !
- [candidate_parents (: (Operation (List [[Text .Type] Bit]))
- (class_candidate_parents class_loader current_name currentT target_name target_class))]
- (case (|> candidate_parents
- (list.only product.right)
- (list#each product.left))
- {.#Item [next_name nextT] _}
- (again [next_name nextT])
-
- {.#End}
- (in false)))))))))]
+ can_cast? (is (Operation Bit)
+ (`` (cond (~~ (template [<primitive> <object>]
+ [(let [=primitive (reflection.reflection <primitive>)]
+ (or (and (text#= =primitive source_name)
+ (or (text#= <object> target_name)
+ (text#= =primitive target_name)))
+ (and (text#= <object> source_name)
+ (text#= =primitive target_name))))
+ (in true)]
+
+ [reflection.boolean box.boolean]
+ [reflection.byte box.byte]
+ [reflection.short box.short]
+ [reflection.int box.int]
+ [reflection.long box.long]
+ [reflection.float box.float]
+ [reflection.double box.double]
+ [reflection.char box.char]))
+
+ ... else
+ (do !
+ [_ (phase.assertion ..primitives_are_not_objects [source_name]
+ (not (dictionary.key? ..boxes source_name)))
+ _ (phase.assertion ..primitives_are_not_objects [target_name]
+ (not (dictionary.key? ..boxes target_name)))
+ target_class (phase.lifted (reflection!.load class_loader target_name))
+ _ (do !
+ [source_class (phase.lifted (reflection!.load class_loader source_name))]
+ (phase.assertion ..cannot_cast [fromT toT fromC]
+ (java/lang/Class::isAssignableFrom source_class target_class)))]
+ (loop [[current_name currentT] [source_name fromT]]
+ (if (text#= target_name current_name)
+ (in true)
+ (do !
+ [candidate_parents (is (Operation (List [[Text .Type] Bit]))
+ (class_candidate_parents class_loader current_name currentT target_name target_class))]
+ (case (|> candidate_parents
+ (list.only product.right)
+ (list#each product.left))
+ {.#Item [next_name nextT] _}
+ (again [next_name nextT])
+
+ {.#End}
+ (in false)))))))))]
(if can_cast?
(in {/////analysis.#Extension extension_name (list (/////analysis.text source_name)
(/////analysis.text target_name)
@@ -1150,13 +1150,13 @@
(case (parser.class? it)
{.#Some [name parameters]}
(|> parameters
- (list#each (|>> again (:as (Type Parameter))))
+ (list#each (|>> again (as (Type Parameter))))
(jvm.class name))
{.#None})
(~~ (template [<read> <as> <write>]
[(case (<read> it)
{.#Some :sub:}
- (<write> (:as (Type <as>) (again :sub:)))
+ (<write> (as (Type <as>) (again :sub:)))
{.#None})]
[parser.array? Value jvm.array]
@@ -1381,17 +1381,17 @@
java/lang/Class::getDeclaredMethods
(array.list {.#None})
(list.only (|>> java/lang/reflect/Method::getName (text#= method_name)))
- (monad.each ! (: (-> java/lang/reflect/Method (Operation Evaluation))
- (function (_ method)
- (do !
- [.let [expected_method_tvars (method_type_variables method)
- aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars)
- (..aliasing expected_method_tvars actual_method_tvars))]
- passes? (check_method aliasing class method_name method_style inputsJT method)]
- (# ! each (if passes?
- (|>> {#Pass})
- (|>> {#Hint}))
- (method_signature method_style method)))))))]
+ (monad.each ! (is (-> java/lang/reflect/Method (Operation Evaluation))
+ (function (_ method)
+ (do !
+ [.let [expected_method_tvars (method_type_variables method)
+ aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars)
+ (..aliasing expected_method_tvars actual_method_tvars))]
+ passes? (check_method aliasing class method_name method_style inputsJT method)]
+ (# ! each (if passes?
+ (|>> {#Pass})
+ (|>> {#Hint}))
+ (method_signature method_style method)))))))]
(case (list.all pass! candidates)
{.#Item method {.#End}}
(in method)
@@ -1732,9 +1732,9 @@
(template [<name>]
[(exception: .public (<name> [expected (List [(Type Class) Text (Type Method)])
actual (List [(Type Class) Text (Type Method)])])
- (let [%method (: (%.Format [(Type Class) Text (Type Method)])
- (function (_ [super name type])
- (format (..signature super) " :: " (%.text name) " " (..signature type))))]
+ (let [%method (is (%.Format [(Type Class) Text (Type Method)])
+ (function (_ [super name type])
+ (format (..signature super) " :: " (%.text name) " " (..signature type))))]
(exception.report
"Expected Methods" (exception.listing %method expected)
"Actual Methods" (exception.listing %method actual))))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
index 6c3e7c9fc..a85e87d85 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -167,7 +167,7 @@
(case args
(pattern (list typeC valueC))
(do [! ////.monad]
- [actualT (# ! each (|>> (:as Type))
+ [actualT (# ! each (|>> (as Type))
(eval archive Type typeC))
_ (typeA.inference actualT)]
(<| (typeA.expecting actualT)
@@ -182,7 +182,7 @@
(case args
(pattern (list typeC valueC))
(do [! ////.monad]
- [actualT (# ! each (|>> (:as Type))
+ [actualT (# ! each (|>> (as Type))
(eval archive Type typeC))
_ (typeA.inference actualT)
[valueT valueA] (typeA.inferring
@@ -219,7 +219,7 @@
(case input_type
(^.or {.#Definition [exported? def_type def_value]}
{.#Type [exported? def_value labels]})
- (in (:as Type def_value))
+ (in (as Type def_value))
(^.or {.#Tag _}
{.#Slot _})
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
index a35443c11..0ec22f549 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
@@ -452,7 +452,7 @@
(list#mix (function (_ [lux_register type] [jvm_register before])
(let [[jvm_register' after] (method_argument (n.+ offset lux_register) type jvm_register)]
[jvm_register' ($_ _.composite before after)]))
- (: [Register (Bytecode Any)] [offset (_#in [])]))
+ (is [Register (Bytecode Any)] [offset (_#in [])]))
product.right))
(def: (constructor_method_generation archive super_class method)
@@ -645,26 +645,26 @@
(-> (Method_Definition Code) (Operation [(Set unit.ID) (Resource Method)])))
(function (_ methodC)
(do phase.monad
- [methodA (: (Operation Analysis)
- (directive.lifted_analysis
- (case methodC
- {#Constructor method}
- (jvm.analyse_constructor_method analyse archive selfT mapping method)
-
- {#Virtual_Method method}
- (jvm.analyse_virtual_method analyse archive selfT mapping method)
-
- {#Static_Method method}
- (jvm.analyse_static_method analyse archive mapping method)
-
- {#Overriden_Method method}
- (jvm.analyse_overriden_method analyse archive selfT mapping (list& super interfaces) method)
-
- {#Abstract_Method method}
- (jvm.analyse_abstract_method analyse archive method))))
- methodS (: (Operation Synthesis)
- (directive.lifted_synthesis
- (synthesize archive methodA)))
+ [methodA (is (Operation Analysis)
+ (directive.lifted_analysis
+ (case methodC
+ {#Constructor method}
+ (jvm.analyse_constructor_method analyse archive selfT mapping method)
+
+ {#Virtual_Method method}
+ (jvm.analyse_virtual_method analyse archive selfT mapping method)
+
+ {#Static_Method method}
+ (jvm.analyse_static_method analyse archive mapping method)
+
+ {#Overriden_Method method}
+ (jvm.analyse_overriden_method analyse archive selfT mapping (list& super interfaces) method)
+
+ {#Abstract_Method method}
+ (jvm.analyse_abstract_method analyse archive method))))
+ methodS (is (Operation Synthesis)
+ (directive.lifted_synthesis
+ (synthesize archive methodA)))
dependencies (directive.lifted_generation
(cache.dependencies archive methodS))
methodS' (|> methodS
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index a76c39427..16bd430fa 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -28,7 +28,7 @@
[math
[number
["n" nat]]]
- ["[0]" type {"+" :sharing} ("[1]#[0]" equivalence)
+ ["[0]" type {"+" sharing} ("[1]#[0]" equivalence)
["[0]" check]]]]
["[0]" /// {"+" Extender}
["[1][0]" bundle]
@@ -230,10 +230,10 @@
previous_analysis_extensions (the [/////directive.#analysis /////directive.#state ///.#bundle] state)]]
(phase.with [bundle
(revised [/////directive.#analysis /////directive.#state]
- (: (-> /////analysis.State+ /////analysis.State+)
- (|>> product.right
- [(|> previous_analysis_extensions
- (dictionary.merged (///analysis.bundle eval host_analysis)))]))
+ (is (-> /////analysis.State+ /////analysis.State+)
+ (|>> product.right
+ [(|> previous_analysis_extensions
+ (dictionary.merged (///analysis.bundle eval host_analysis)))]))
state)])))
(def: (announce_definition! short type)
@@ -254,7 +254,7 @@
[type valueT value] (..definition archive full_name {.#None} valueC)
[_ _ exported?] (evaluate! archive Bit exported?C)
_ (/////directive.lifted_analysis
- (moduleA.define short_name {.#Definition [(:as Bit exported?) type value]}))
+ (moduleA.define short_name {.#Definition [(as Bit exported?) type value]}))
_ (..refresh expander host_analysis)
_ (..announce_definition! short_name type)]
(in /////directive.no_requirements))
@@ -284,7 +284,7 @@
(///.lifted meta.current_module_name))
.let [full_name [current_module short_name]]
[_ _ exported?] (evaluate! archive Bit exported?C)
- .let [exported? (:as Bit exported?)]
+ .let [exported? (as Bit exported?)]
[type valueT value] (..definition archive full_name {.#Some .Type} valueC)
labels (/////directive.lifted_analysis
(do phase.monad
@@ -299,14 +299,14 @@
(moduleA.define short_name {.#Definition [exported? type value]})
{.#Item labels}
- (moduleA.define short_name {.#Type [exported? (:as .Type value) (if record?
- {.#Right labels}
- {.#Left labels})]}))
- _ (moduleA.declare_labels record? labels exported? (:as .Type value))]
+ (moduleA.define short_name {.#Type [exported? (as .Type value) (if record?
+ {.#Right labels}
+ {.#Left labels})]}))
+ _ (moduleA.declare_labels record? labels exported? (as .Type value))]
(in labels)))
_ (..refresh expander host_analysis)
_ (..announce_definition! short_name type)
- _ (..announce_labels! labels (:as Type value))]
+ _ (..announce_labels! labels (as Type value))]
(in /////directive.no_requirements)))]))
(def: imports
@@ -431,7 +431,7 @@
[target_platform (/////directive.lifted_analysis
(///.lifted meta.target))
[_ _ name] (evaluate! archive Text nameC)
- [_ handlerV] (<definer> archive (:as Text name)
+ [_ handlerV] (<definer> archive (as Text name)
(let [raw_type (type <def_type>)]
(case target_platform
(^.or (pattern (static @.jvm))
@@ -445,15 +445,15 @@
(swapped binary.Binary Binary|DEFAULT raw_type)))
valueC)
_ (<| <scope>
- (///.install extender (:as Text name))
- (:sharing [anchor expression directive]
- (Handler anchor expression directive)
- handler
-
- <type>
- (:expected handlerV)))
+ (///.install extender (as Text name))
+ (sharing [anchor expression directive]
+ (Handler anchor expression directive)
+ handler
+
+ <type>
+ (as_expected handlerV)))
_ (/////directive.lifted_generation
- (/////generation.log! (format <description> " " (%.text (:as Text name)))))]
+ (/////generation.log! (format <description> " " (%.text (as Text name)))))]
(in /////directive.no_requirements))
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
index 61f03e588..987ae0104 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
@@ -1,42 +1,42 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["[0]" try]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" dictionary]
- ["[0]" set]
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["f" frac]]]
- ["@" target
- ["_" common_lisp {"+" Expression}]]]]
- ["[0]" //// "_"
- ["/" bundle]
- ["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" common_lisp "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
- ["[1][0]" case]]]
- [//
- ["[0]" synthesis {"+" %synthesis}]
- ["[0]" generation]
- [///
- ["[1]" phase]]]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["[0]" try]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" dictionary]
+ ["[0]" set]
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["f" frac]]]
+ ["@" target
+ ["_" common_lisp {"+" Expression}]]]]
+ ["[0]" //// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" common_lisp "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
+ ["[1][0]" case]]]
+ [//
+ ["[0]" synthesis {"+" %synthesis}]
+ ["[0]" generation]
+ [///
+ ["[1]" phase]]]]])
(def: .public (custom [parser handler])
(All (_ s)
@@ -67,7 +67,7 @@
... [@input (# ! each _.var (generation.symbol "input"))
... inputG (phase archive input)
... elseG (phase archive else)
-... conditionalsG (: (Operation (List [Expression Expression]))
+... conditionalsG (is (Operation (List [Expression Expression]))
... (monad.each ! (function (_ [chars branch])
... (do !
... [branchG (phase archive branch)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
index 8f4bec35c..121fd29fa 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
@@ -105,7 +105,7 @@
{synthesis.#Extension "lux syntax char case!" parameters}
(do /////.monad
[body (expression archive synthesis)]
- (in (:as Statement body)))
+ (in (as Statement body)))
(^.template [<tag>]
[(pattern (<tag> value))
@@ -159,21 +159,21 @@
(do [! /////.monad]
[inputG (phase archive input)
else! (..statement phase archive else)
- conditionals! (: (Operation (List [(List Literal)
- Statement]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branch! (..statement phase archive branch)]
- (in [(list#each (|>> .int _.int) chars)
- branch!])))
- conditionals))]
+ conditionals! (is (Operation (List [(List Literal)
+ Statement]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branch! (..statement phase archive branch)]
+ (in [(list#each (|>> .int _.int) chars)
+ branch!])))
+ conditionals))]
... (in (_.apply/* (_.closure (list)
... (_.switch (_.the //runtime.i64_low_field inputG)
... conditionals!
... {.#Some (_.return else!)}))
... (list)))
- (in (<| (:as Expression)
- (: Statement)
+ (in (<| (as Expression)
+ (is Statement)
(_.switch (_.the //runtime.i64_low_field inputG)
conditionals!
{.#Some else!})))))]))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
index 9f6f59ab9..77908df35 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
@@ -132,9 +132,9 @@
(function (_ extension phase archive [arity abstractionS])
(do [! ////////phase.monad]
[abstractionG (phase archive abstractionS)
- .let [variable (: (-> Text (Operation Var))
- (|>> generation.symbol
- (# ! each _.var)))]
+ .let [variable (is (-> Text (Operation Var))
+ (|>> generation.symbol
+ (# ! each _.var)))]
g!inputs (monad.each ! (function (_ _) (variable "input"))
(list.repeated (.nat arity) []))
g!abstraction (variable "abstraction")]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
index aa59d8b01..becc799b6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
@@ -106,20 +106,20 @@
[@end ///runtime.forge_label
inputG (phase archive inputS)
elseG (phase archive elseS)
- conditionalsG+ (: (Operation (List [(List [S4 Label])
- (Bytecode Any)]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branchG (phase archive branch)
- @branch ///runtime.forge_label]
- (in [(list#each (function (_ char)
- [(try.trusted (signed.s4 (.int char))) @branch])
- chars)
- ($_ _.composite
- (_.set_label @branch)
- branchG
- (_.when_continuous (_.goto @end)))])))
- conditionalsS))
+ conditionalsG+ (is (Operation (List [(List [S4 Label])
+ (Bytecode Any)]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branchG (phase archive branch)
+ @branch ///runtime.forge_label]
+ (in [(list#each (function (_ char)
+ [(try.trusted (signed.s4 (.int char))) @branch])
+ chars)
+ ($_ _.composite
+ (_.set_label @branch)
+ branchG
+ (_.when_continuous (_.goto @end)))])))
+ conditionalsS))
.let [table (|> conditionalsG+
(list#each product.left)
list#conjoint)
@@ -154,7 +154,7 @@
(def: bundle::lux
Bundle
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "syntax char case!" ..lux::syntax_char_case!)
(/////bundle.install "is" (binary ..lux::is))
(/////bundle.install "try" (unary ..lux::try))))
@@ -266,7 +266,7 @@
(def: bundle::i64
Bundle
(<| (/////bundle.prefix "i64")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "and" (binary ..i64::and))
(/////bundle.install "or" (binary ..i64::or))
(/////bundle.install "xor" (binary ..i64::xor))
@@ -285,7 +285,7 @@
(def: bundle::f64
Bundle
(<| (/////bundle.prefix "f64")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "+" (binary ..f64::+))
(/////bundle.install "-" (binary ..f64::-))
(/////bundle.install "*" (binary ..f64::*))
@@ -368,7 +368,7 @@
(def: bundle::text
Bundle
(<| (/////bundle.prefix "text")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "=" (binary ..text::=))
(/////bundle.install "<" (binary ..text::<))
(/////bundle.install "concat" (binary ..text::concat))
@@ -400,7 +400,7 @@
(def: bundle::io
Bundle
(<| (/////bundle.prefix "io")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "log" (unary ..io::log))
(/////bundle.install "error" (unary ..io::error)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
index a89e094ea..081984baf 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
@@ -135,7 +135,7 @@
(def: bundle::conversion
Bundle
(<| (/////bundle.prefix "conversion")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "double-to-float" (unary conversion::double_to_float))
(/////bundle.install "double-to-int" (unary conversion::double_to_int))
(/////bundle.install "double-to-long" (unary conversion::double_to_long))
@@ -271,7 +271,7 @@
(def: bundle::int
Bundle
(<| (/////bundle.prefix (reflection.reflection reflection.int))
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "+" (binary int::+))
(/////bundle.install "-" (binary int::-))
(/////bundle.install "*" (binary int::*))
@@ -290,7 +290,7 @@
(def: bundle::long
Bundle
(<| (/////bundle.prefix (reflection.reflection reflection.long))
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "+" (binary long::+))
(/////bundle.install "-" (binary long::-))
(/////bundle.install "*" (binary long::*))
@@ -309,7 +309,7 @@
(def: bundle::float
Bundle
(<| (/////bundle.prefix (reflection.reflection reflection.float))
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "+" (binary float::+))
(/////bundle.install "-" (binary float::-))
(/////bundle.install "*" (binary float::*))
@@ -322,7 +322,7 @@
(def: bundle::double
Bundle
(<| (/////bundle.prefix (reflection.reflection reflection.double))
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "+" (binary double::+))
(/////bundle.install "-" (binary double::-))
(/////bundle.install "*" (binary double::*))
@@ -335,7 +335,7 @@
(def: bundle::char
Bundle
(<| (/////bundle.prefix (reflection.reflection reflection.char))
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "=" (binary char::=))
(/////bundle.install "<" (binary char::<))
)))
@@ -634,7 +634,7 @@
(def: bundle::object
Bundle
(<| (/////bundle.prefix "object")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "null" (nullary object::null))
(/////bundle.install "null?" (unary object::null?))
(/////bundle.install "synchronized" (binary object::synchronized))
@@ -790,17 +790,17 @@
(def: bundle::member
Bundle
(<| (/////bundle.prefix "member")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(dictionary.merged (<| (/////bundle.prefix "get")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "static" get::static)
(/////bundle.install "virtual" get::virtual))))
(dictionary.merged (<| (/////bundle.prefix "put")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "static" put::static)
(/////bundle.install "virtual" put::virtual))))
(dictionary.merged (<| (/////bundle.prefix "invoke")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "static" invoke::static)
(/////bundle.install "virtual" invoke::virtual)
(/////bundle.install "special" invoke::special)
@@ -832,7 +832,7 @@
hidden
[_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}]
- (loop [path (: Path path)]
+ (loop [path (is Path path)]
(case path
{//////synthesis.#Seq _ next}
(again next)
@@ -1133,9 +1133,9 @@
($_ _.composite
before
after)]))
- (: [Register (Bytecode Any)]
- [offset
- (_#in [])]))
+ (is [Register (Bytecode Any)]
+ [offset
+ (_#in [])]))
product.right))
(def: (normalized_method global_mapping [environment method])
@@ -1241,7 +1241,7 @@
(def: bundle::class
Bundle
(<| (/////bundle.prefix "class")
- (|> (: Bundle /////bundle.empty)
+ (|> (is Bundle /////bundle.empty)
(/////bundle.install "anonymous" class::anonymous)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index e8be23f6c..bb9c71927 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -66,7 +66,7 @@
{synthesis.#Extension "lux syntax char case!" parameters}
(do /////.monad
[body (expression archive synthesis)]
- (in (:as Statement body)))
+ (in (as Statement body)))
(^.template [<tag>]
[(pattern (<tag> value))
@@ -138,7 +138,7 @@
{synthesis.#Then else})
[input]
(//case.case! statement phase archive)
- (# /////.monad each (|>> (:as Expression)))))]))
+ (# /////.monad each (|>> (as Expression)))))]))
(def: lux_procs
Bundle
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
index 23469d067..74540b895 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
@@ -1,37 +1,37 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- [collection
- ["[0]" dictionary]
- ["[0]" list]]
- [text
- ["%" format {"+" format}]]]
- [target
- ["_" lua {"+" Var Expression}]]]]
- ["[0]" // "_"
- ["[1][0]" common {"+" custom}]
- ["//[1]" /// "_"
- ["/" bundle]
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ [collection
+ ["[0]" dictionary]
+ ["[0]" list]]
+ [text
+ ["%" format {"+" format}]]]
+ [target
+ ["_" lua {"+" Var Expression}]]]]
+ ["[0]" // "_"
+ ["[1][0]" common {"+" custom}]
+ ["//[1]" /// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" lua "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle
+ with_vars}]]]
["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" lua "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle
- with_vars}]]]
- ["/[1]" // "_"
- ["[0]" generation]
- ["//[1]" /// "_"
- ["[1][0]" phase]]]]]])
+ ["[0]" generation]
+ ["//[1]" /// "_"
+ ["[1][0]" phase]]]]]])
(def: array::new
(Unary Expression)
@@ -170,9 +170,9 @@
(function (_ extension phase archive [arity abstractionS])
(do [! ////////phase.monad]
[abstractionG (phase archive abstractionS)
- .let [variable (: (-> Text (Operation Var))
- (|>> generation.symbol
- (# ! each _.var)))]
+ .let [variable (is (-> Text (Operation Var))
+ (|>> generation.symbol
+ (# ! each _.var)))]
g!inputs (monad.each ! (function (_ _)
(variable "input"))
(list.repeated (.nat arity) []))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
index 503b85252..2e6338e37 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
@@ -1,42 +1,42 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["[0]" try]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" dictionary]
- ["[0]" set]
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["f" frac]]]
- ["@" target
- ["_" php {"+" Expression}]]]]
- ["[0]" //// "_"
- ["/" bundle]
- ["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" php "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
- ["[1][0]" case]]]
- [//
- ["[0]" synthesis {"+" %synthesis}]
- ["[0]" generation]
- [///
- ["[1]" phase]]]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["[0]" try]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" dictionary]
+ ["[0]" set]
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["f" frac]]]
+ ["@" target
+ ["_" php {"+" Expression}]]]]
+ ["[0]" //// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" php "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
+ ["[1][0]" case]]]
+ [//
+ ["[0]" synthesis {"+" %synthesis}]
+ ["[0]" generation]
+ [///
+ ["[1]" phase]]]]])
(def: .public (custom [parser handler])
(All (_ s)
@@ -68,19 +68,19 @@
[[context_module context_artifact] elseG] (generation.with_new_context archive
(phase archive else))
@input (# ! each _.var (generation.symbol "input"))
- conditionalsG (: (Operation (List [Expression Expression]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branchG (phase archive branch)]
- (in [(|> chars
- (list#each (|>> .int _.int (_.=== @input)))
- (list#mix (function (_ clause total)
- (if (same? _.null total)
- clause
- (_.or clause total)))
- _.null))
- branchG])))
- conditionals))
+ conditionalsG (is (Operation (List [Expression Expression]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branchG (phase archive branch)]
+ (in [(|> chars
+ (list#each (|>> .int _.int (_.=== @input)))
+ (list#mix (function (_ clause total)
+ (if (same? _.null total)
+ clause
+ (_.or clause total)))
+ _.null))
+ branchG])))
+ conditionals))
.let [foreigns (|> conditionals
(list#each (|>> product.right synthesis.path/then //case.dependencies))
(list& (//case.dependencies (synthesis.path/then else)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
index 481eefce0..dc6845bc8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
@@ -52,7 +52,7 @@
{synthesis.#Extension "lux syntax char case!" parameters}
(do /////.monad
[body (expression archive synthesis)]
- (in (:as (Statement Any) body)))
+ (in (as (Statement Any) body)))
(^.template [<tag>]
[(pattern (<tag> value))
@@ -114,20 +114,20 @@
[inputG (phase archive input)
else! (..statement phase archive else)
@input (# ! each _.var (generation.symbol "input"))
- conditionals! (: (Operation (List [(Expression Any)
- (Statement Any)]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branch! (..statement phase archive branch)]
- (in [(|> chars
- (list#each (|>> .int _.int (_.= @input)))
- (list#mix (function (_ clause total)
- (if (same? _.none total)
- clause
- (_.or clause total)))
- _.none))
- branch!])))
- conditionals))
+ conditionals! (is (Operation (List [(Expression Any)
+ (Statement Any)]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branch! (..statement phase archive branch)]
+ (in [(|> chars
+ (list#each (|>> .int _.int (_.= @input)))
+ (list#mix (function (_ clause total)
+ (if (same? _.none total)
+ clause
+ (_.or clause total)))
+ _.none))
+ branch!])))
+ conditionals))
... .let [dependencies (//case.dependencies (list#mix (function (_ right left)
... (synthesis.path/seq left right))
... (synthesis.path/then input)
@@ -147,8 +147,8 @@
... _ (generation.save! (product.right artifact_id) {.#None} closure)
]
... (in (_.apply/* @closure dependencies))
- (in (<| (:as (Expression Any))
- (: (Statement Any))
+ (in (<| (as (Expression Any))
+ (is (Statement Any))
($_ _.then
(_.set (list @input) inputG)
(list#mix (function (_ [test then!] else!)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
index fa18710f9..72ade0f7d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
@@ -132,9 +132,9 @@
(function (_ extension phase archive [arity abstractionS])
(do [! ////////phase.monad]
[abstractionG (phase archive abstractionS)
- .let [variable (: (-> Text (Operation SVar))
- (|>> generation.symbol
- (# ! each _.var)))]
+ .let [variable (is (-> Text (Operation SVar))
+ (|>> generation.symbol
+ (# ! each _.var)))]
g!inputs (monad.each ! (function (_ _) (variable "input"))
(list.repeated (.nat arity) []))]
(in (_.lambda g!inputs
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
index 492d9954f..e3beeba75 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
@@ -1,42 +1,42 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["[0]" try]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" dictionary]
- ["[0]" set]
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["f" frac]]]
- ["@" target
- ["_" r {"+" Expression}]]]]
- ["[0]" //// "_"
- ["/" bundle]
- ["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" r "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
- ["[1][0]" case]]]
- [//
- ["[0]" synthesis {"+" %synthesis}]
- ["[0]" generation]
- [///
- ["[1]" phase]]]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["[0]" try]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" dictionary]
+ ["[0]" set]
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["f" frac]]]
+ ["@" target
+ ["_" r {"+" Expression}]]]]
+ ["[0]" //// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" r "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
+ ["[1][0]" case]]]
+ [//
+ ["[0]" synthesis {"+" %synthesis}]
+ ["[0]" generation]
+ [///
+ ["[1]" phase]]]]])
(def: .public (custom [parser handler])
(All (_ s)
@@ -67,7 +67,7 @@
... ... [@input (# ! each _.var (generation.symbol "input"))
... ... inputG (phase archive input)
... ... elseG (phase archive else)
-... ... conditionalsG (: (Operation (List [Expression Expression]))
+... ... conditionalsG (is (Operation (List [Expression Expression]))
... ... (monad.each ! (function (_ [chars branch])
... ... (do !
... ... [branchG (phase archive branch)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
index 7f71e4292..37a202c9f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
@@ -63,8 +63,8 @@
{synthesis.#Extension "lux syntax char case!" parameters}
(do /////.monad
[body (expression archive synthesis)]
- (in (:as Statement
- body)))
+ (in (as Statement
+ body)))
(^.template [<tag>]
[(pattern (<tag> value))
@@ -113,19 +113,19 @@
[inputG (phase archive input)
else! (statement phase archive else)
@input (# ! each _.local (generation.symbol "input"))
- conditionals! (: (Operation (List [Expression Statement]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branch! (statement phase archive branch)]
- (in [(|> chars
- (list#each (|>> .int _.int (_.= @input)))
- (list#mix (function (_ clause total)
- (if (same? _.nil total)
- clause
- (_.or clause total)))
- _.nil))
- branch!])))
- conditionals))
+ conditionals! (is (Operation (List [Expression Statement]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branch! (statement phase archive branch)]
+ (in [(|> chars
+ (list#each (|>> .int _.int (_.= @input)))
+ (list#mix (function (_ clause total)
+ (if (same? _.nil total)
+ clause
+ (_.or clause total)))
+ _.nil))
+ branch!])))
+ conditionals))
... .let [closure (_.lambda {.#None} (list @input)
... (list#mix (function (_ [test then] else)
... (_.if test (_.return then) else))
@@ -133,8 +133,8 @@
... conditionals!))]
]
... (in (_.apply_lambda/* (list inputG) closure))
- (in (<| (:as Expression)
- (: Statement)
+ (in (<| (as Expression)
+ (is Statement)
($_ _.then
(_.set (list @input) inputG)
(list#mix (function (_ [test then!] else!)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
index e11fc7aa6..53b71239f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
@@ -1,41 +1,41 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- [collection
- ["[0]" dictionary]
- ["[0]" list]]
- [text
- ["%" format {"+" format}]]]
- [target
- ["_" ruby {"+" Var Expression}]]]]
- ["[0]" // "_"
- ["[1][0]" common {"+" custom}]
- ["//[1]" /// "_"
- ["/" bundle]
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ [collection
+ ["[0]" dictionary]
+ ["[0]" list]]
+ [text
+ ["%" format {"+" format}]]]
+ [target
+ ["_" ruby {"+" Var Expression}]]]]
+ ["[0]" // "_"
+ ["[1][0]" common {"+" custom}]
+ ["//[1]" /// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" ruby "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle
+ with_vars}]]]
["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" ruby "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle
- with_vars}]]]
- ["/[1]" // "_"
- ["[0]" generation]
- ["//[1]" /// "_"
- ["[1][0]" phase]]]]]])
+ ["[0]" generation]
+ ["//[1]" /// "_"
+ ["[1][0]" phase]]]]]])
(def: (array::new [size])
(Unary Expression)
- (_.do "new" (list size) {.#None} (: _.CVar (_.manual "Array"))))
+ (_.do "new" (list size) {.#None} (is _.CVar (_.manual "Array"))))
(def: array::length
(Unary Expression)
@@ -104,7 +104,7 @@
(custom
[<s>.text
(function (_ extension phase archive name)
- (# ////////phase.monad in (: _.CVar (_.manual name))))]))
+ (# ////////phase.monad in (is _.CVar (_.manual name))))]))
(def: ruby::apply
(custom
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
index d55e5056a..6aa4e52b1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
@@ -1,42 +1,42 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["[0]" try]
- ["<>" parser
- ["<s>" synthesis {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" dictionary]
- ["[0]" set]
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["f" frac]]]
- ["@" target
- ["_" scheme {"+" Expression}]]]]
- ["[0]" //// "_"
- ["/" bundle]
- ["/[1]" // "_"
- ["[0]" extension]
- [generation
- [extension {"+" Nullary Unary Binary Trinary
- nullary unary binary trinary}]
- ["[0]" reference]
- ["//" scheme "_"
- ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
- ["[1][0]" case]]]
- [//
- ["[0]" synthesis {"+" %synthesis}]
- ["[0]" generation]
- [///
- ["[1]" phase]]]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["[0]" try]
+ ["<>" parser
+ ["<s>" synthesis {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" dictionary]
+ ["[0]" set]
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["f" frac]]]
+ ["@" target
+ ["_" scheme {"+" Expression}]]]]
+ ["[0]" //// "_"
+ ["/" bundle]
+ ["/[1]" // "_"
+ ["[0]" extension]
+ [generation
+ [extension {"+" Nullary Unary Binary Trinary
+ nullary unary binary trinary}]
+ ["[0]" reference]
+ ["//" scheme "_"
+ ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}]
+ ["[1][0]" case]]]
+ [//
+ ["[0]" synthesis {"+" %synthesis}]
+ ["[0]" generation]
+ [///
+ ["[1]" phase]]]]])
(def: .public (custom [parser handler])
(All (_ s)
@@ -67,13 +67,13 @@
[@input (# ! each _.var (generation.symbol "input"))
inputG (phase archive input)
elseG (phase archive else)
- conditionalsG (: (Operation (List [Expression Expression]))
- (monad.each ! (function (_ [chars branch])
- (do !
- [branchG (phase archive branch)]
- (in [(|> chars (list#each (|>> .int _.int (_.=/2 @input))) _.or)
- branchG])))
- conditionals))]
+ conditionalsG (is (Operation (List [Expression Expression]))
+ (monad.each ! (function (_ [chars branch])
+ (do !
+ [branchG (phase archive branch)]
+ (in [(|> chars (list#each (|>> .int _.int (_.=/2 @input))) _.or)
+ branchG])))
+ conditionals))]
(in (_.let (list [@input inputG])
(list#mix (function (_ [test then] else)
(_.if test then else))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
index 60b9cd96e..fbad56663 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
@@ -39,11 +39,11 @@
(def: .public register
(-> Register Var/1)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register Var/1)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
index 2d18193e7..d91f824ad 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
@@ -1,33 +1,33 @@
(.using
- [library
- [lux {"-" function}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- pipe]
- [data
- ["[0]" product]
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [target
- ["_" common_lisp {"+" Expression Var/1}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Generator}]
+ [library
+ [lux {"-" function}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ pipe]
+ [data
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [target
+ ["_" common_lisp {"+" Expression Var/1}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Generator}]
+ ["[1][0]" reference]
+ ["[1][0]" case]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" case]
- ["/[1]" // "_"
- ["[1][0]" reference]
+ ["//[1]" /// "_"
+ [analysis {"+" Variant Tuple Abstraction Application Analysis}]
+ [synthesis {"+" Synthesis}]
+ ["[1][0]" generation {"+" Context}]
["//[1]" /// "_"
- [analysis {"+" Variant Tuple Abstraction Application Analysis}]
- [synthesis {"+" Synthesis}]
- ["[1][0]" generation {"+" Context}]
- ["//[1]" /// "_"
- [arity {"+" Arity}]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [reference
- [variable {"+" Register Variable}]]]]]])
+ [arity {"+" Arity}]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [reference
+ [variable {"+" Register Variable}]]]]]])
(def: .public (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
@@ -38,7 +38,7 @@
(def: capture
(-> Register Var/1)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure inits function_definition)
(-> (List (Expression Any)) (Expression Any) (Operation (Expression Any)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index cca5cda23..4c3e03ca3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -38,7 +38,7 @@
(def: .public register
(-> Register Var)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public (exec expression archive [this that])
(Generator [Synthesis Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
index a3fa9317d..26ac01808 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
@@ -42,7 +42,7 @@
(def: capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure @self inits body!)
(-> Var (List Expression) Statement [Statement Expression])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux
index 85e221b18..5caa9c817 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux
@@ -1,17 +1,17 @@
(.using
- [library
- [lux "*"
- [abstract
- [monad {"+" do}]]
- [control
- ["[0]" io {"+" IO}]
- ["[0]" try {"+" Try}]]
- [data
- [binary {"+" Binary}]
- [text
- ["%" format {"+" format}]]]
- [world
- ["[0]" file {"+" File}]]]])
+ [library
+ [lux "*"
+ [abstract
+ [monad {"+" do}]]
+ [control
+ ["[0]" io {"+" IO}]
+ ["[0]" try {"+" Try}]]
+ [data
+ [binary {"+" Binary}]
+ [text
+ ["%" format {"+" format}]]]
+ [world
+ ["[0]" file {"+" File}]]]])
(def: extension ".class")
@@ -20,8 +20,8 @@
(let [file_path (format name ..extension)]
(do io.monad
[outcome (do (try.with @)
- [file (: (IO (Try (File IO)))
- (file.get_file io.monad file.default file_path))]
+ [file (is (IO (Try (File IO)))
+ (file.get_file io.monad file.default file_path))]
(# file over_write bytecode))]
(in (case outcome
{try.#Success definition}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
index 1a0569fbc..7fd639b8f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
@@ -73,19 +73,19 @@
(List (Resource Method))
(Bytecode Any)]))
(let [classT (type.class class (list))
- fields (: (List (Resource Field))
- (list#composite (/foreign.variables environment)
- (/partial.variables arity)))
- methods (: (List (Resource Method))
- (list& (/init.method classT environment arity)
- (/reset.method classT environment arity)
- (if (arity.multiary? arity)
- (|> (n.min arity /arity.maximum)
- list.indices
- (list#each (|>> ++ (/apply.method classT environment arity @begin body)))
- (list& (/implementation.method classT arity @begin body)))
- (list (/implementation.method classT arity @begin body)
- (/apply.method classT environment arity @begin body 1)))))]
+ fields (is (List (Resource Field))
+ (list#composite (/foreign.variables environment)
+ (/partial.variables arity)))
+ methods (is (List (Resource Method))
+ (list& (/init.method classT environment arity)
+ (/reset.method classT environment arity)
+ (if (arity.multiary? arity)
+ (|> (n.min arity /arity.maximum)
+ list.indices
+ (list#each (|>> ++ (/apply.method classT environment arity @begin body)))
+ (list& (/implementation.method classT arity @begin body)))
+ (list (/implementation.method classT arity @begin body)
+ (/apply.method classT environment arity @begin body 1)))))]
(do phase.monad
[instance (/new.instance generate archive classT environment arity)]
(in [fields methods instance]))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
index 14d2fdc03..e6734dfcb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
@@ -87,12 +87,12 @@
(def: .public (method class environment arity)
(-> (Type Class) (Environment Synthesis) Arity (Resource Method))
(let [environment_size (list.size environment)
- offset_foreign (: (-> Register Register)
- (n.+ 1))
- offset_arity (: (-> Register Register)
- (|>> offset_foreign (n.+ environment_size)))
- offset_partial (: (-> Register Register)
- (|>> offset_arity (n.+ 1)))]
+ offset_foreign (is (-> Register Register)
+ (n.+ 1))
+ offset_arity (is (-> Register Register)
+ (|>> offset_foreign (n.+ environment_size)))
+ offset_partial (is (-> Register Register)
+ (|>> offset_arity (n.+ 1)))]
(method.method //.modifier ..name
#0 (..type environment arity)
(list)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
index 3edbe1e05..5087f0357 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
@@ -60,13 +60,13 @@
(def: .public (method class environment arity)
(-> (Type Class) (Environment Synthesis) Arity (Resource Method))
- (let [after_this (: (-> Nat Nat)
- (n.+ 1))
+ (let [after_this (is (-> Nat Nat)
+ (n.+ 1))
environment_size (list.size environment)
- after_environment (: (-> Nat Nat)
- (|>> after_this (n.+ environment_size)))
- after_arity (: (-> Nat Nat)
- (|>> after_environment (n.+ 1)))]
+ after_environment (is (-> Nat Nat)
+ (|>> after_this (n.+ environment_size)))
+ after_arity (is (-> Nat Nat)
+ (|>> after_environment (n.+ 1)))]
(method.method //.modifier //init.name
#0 (//init.type environment arity)
(list)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
index ced3ea64a..d512d7050 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
@@ -147,7 +147,7 @@
(# io.monad each (function (_ library)
(dictionary.key? library class_name)))
(try.lifted io.monad)
- (: (IO (Try Bit))))
+ (is (IO (Try Bit))))
_ (if existing_class?
(in [])
(loader.store class_name class_bytecode library))]
@@ -166,30 +166,30 @@
(io (let [library (loader.new_library [])
loader (loader.memory library)]
[loader
- (: //runtime.Host
- (implementation
- (def: (evaluate context @it,valueG)
- (# try.monad each product.left
- (..evaluate! library loader (format "E" (//runtime.class_name context)) @it,valueG)))
-
- (def: execute
- (..execute! library loader))
-
- (def: define
- (..define! library loader))
-
- (def: (ingest context bytecode)
- [(//runtime.class_name context) bytecode])
-
- (def: (re_learn context custom [_ bytecode])
- (io.run! (loader.store (maybe.else (//runtime.class_name context) custom) bytecode library)))
-
- (def: (re_load context custom [directive_name bytecode])
- (io.run!
- (do (try.with io.monad)
- [.let [class_name (maybe.else (//runtime.class_name context)
- custom)]
- _ (loader.store class_name bytecode library)
- class (loader.load class_name loader)]
- (# io.monad in (..class_value class_name class)))))
- ))])))
+ (is //runtime.Host
+ (implementation
+ (def: (evaluate context @it,valueG)
+ (# try.monad each product.left
+ (..evaluate! library loader (format "E" (//runtime.class_name context)) @it,valueG)))
+
+ (def: execute
+ (..execute! library loader))
+
+ (def: define
+ (..define! library loader))
+
+ (def: (ingest context bytecode)
+ [(//runtime.class_name context) bytecode])
+
+ (def: (re_learn context custom [_ bytecode])
+ (io.run! (loader.store (maybe.else (//runtime.class_name context) custom) bytecode library)))
+
+ (def: (re_load context custom [directive_name bytecode])
+ (io.run!
+ (do (try.with io.monad)
+ [.let [class_name (maybe.else (//runtime.class_name context)
+ custom)]
+ _ (loader.store class_name bytecode library)
+ class (loader.load class_name loader)]
+ (# io.monad in (..class_value class_name class)))))
+ ))])))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
index 10f11edd9..21a10ad06 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
@@ -122,7 +122,7 @@
_
(let [constantI (if (i.= ..d0_bits
- (java/lang/Double::doubleToRawLongBits (:as java/lang/Double value)))
+ (java/lang/Double::doubleToRawLongBits (as java/lang/Double value)))
_.dconst_0
(_.double value))]
(do _.monad
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
index 23ec9402e..2b761e907 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
@@ -92,16 +92,16 @@
_.iconst_2
(_.anewarray ^Object)
)
- set_side! (: (-> (Bytecode Any) (Bytecode Any))
- (function (_ index)
- ($_ _.composite
- ... ?P
- _.dup_x1 ... P?P
- _.swap ... PP?
- index ... PP?I
- _.swap ... PPI?
- _.aastore ... P
- )))]
+ set_side! (is (-> (Bytecode Any) (Bytecode Any))
+ (function (_ index)
+ ($_ _.composite
+ ... ?P
+ _.dup_x1 ... P?P
+ _.swap ... PP?
+ index ... PP?I
+ _.swap ... PPI?
+ _.aastore ... P
+ )))]
($_ _.composite
... RL
empty_pair ... RLP
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
index 6031ed1db..789884c63 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
@@ -337,13 +337,13 @@
_.isub
(_.int (i32.i32 (.i64 +1)))
_.isub)
- again (: (-> Label (Bytecode Any))
- (function (_ @)
- ($_ _.composite
- ... lefts, sumT
- update_$variant ... lefts, sumT
- update_$lefts ... sub_lefts
- (_.goto @))))]]
+ again (is (-> Label (Bytecode Any))
+ (function (_ @)
+ ($_ _.composite
+ ... lefts, sumT
+ update_$variant ... lefts, sumT
+ update_$lefts ... sub_lefts
+ (_.goto @))))]]
($_ _.composite
$lefts
(_.set_label @loop)
@@ -399,12 +399,12 @@
update_$tuple ($_ _.composite
$tuple $last_right _.aaload (_.checkcast //type.tuple)
_.astore_0)
- recur (: (-> Label (Bytecode Any))
- (function (_ @loop)
- ($_ _.composite
- update_$lefts
- update_$tuple
- (_.goto @loop))))
+ recur (is (-> Label (Bytecode Any))
+ (function (_ @loop)
+ ($_ _.composite
+ update_$lefts
+ update_$tuple
+ (_.goto @loop))))
left_projection::method
(method.method ..modifier ..left_projection::name
@@ -542,10 +542,10 @@
(def: generate_runtime
(Operation [artifact.ID (Maybe Text) Binary])
(let [class (..reflection ..class)
- modifier (: (Modifier Class)
- ($_ modifier#composite
- class.public
- class.final))
+ modifier (is (Modifier Class)
+ ($_ modifier#composite
+ class.public
+ class.final))
bytecode (<| (format.result class.writer)
try.trusted
(class.class jvm/version.v6_0
@@ -609,16 +609,16 @@
$partials
(_.putfield //function.class //function/count.field //function/count.type)
_.return))})
- modifier (: (Modifier Class)
- ($_ modifier#composite
- class.public
- class.abstract))
+ modifier (is (Modifier Class)
+ ($_ modifier#composite
+ class.public
+ class.abstract))
class (..reflection //function.class)
- partial_count (: (Resource Field)
- (field.field (modifier#composite field.public field.final)
- //function/count.field
- #0 //function/count.type
- sequence.empty))
+ partial_count (is (Resource Field)
+ (field.field (modifier#composite field.public field.final)
+ //function/count.field
+ #0 //function/count.type
+ sequence.empty))
bytecode (<| (format.result class.writer)
try.trusted
(class.class jvm/version.v6_0
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 6d79e0750..2c35a85bd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -36,11 +36,11 @@
(def: .public register
(-> Register Var)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (exec expression archive [this that])
(Generator [Synthesis Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index ef4118721..bc3e2210d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -44,7 +44,7 @@
(def: capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure inits @self @args body!)
(-> (List Expression) Var (List Var) Statement [Statement Expression])
@@ -93,9 +93,9 @@
initialize_self!
(list.indices arity))
pack (|>> (list) _.array)
- unpack (: (-> Expression Expression)
- (.function (_ it)
- (_.apply (list it) (_.var "table.unpack"))))
+ unpack (is (-> Expression Expression)
+ (.function (_ it)
+ (_.apply (list it) (_.var "table.unpack"))))
@var_args (_.var "...")]
.let [[definition instantiation] (with_closure closureO+ @self (list @var_args)
($_ _.then
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
index 9409ab00f..57e35ab75 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
@@ -91,26 +91,26 @@
locals (|> initsO+
list.enumeration
(list#each (|>> product.left (n.+ start) //case.register)))
- [directive instantiation] (: [Statement Expression]
- (case (|> (synthesis.path/then bodyS)
- //case.dependencies
- (set.of_list _.hash)
- (set.difference (set.of_list _.hash locals))
- set.list)
- {.#End}
- [(_.function @loop locals
- scope!)
- @loop]
+ [directive instantiation] (is [Statement Expression]
+ (case (|> (synthesis.path/then bodyS)
+ //case.dependencies
+ (set.of_list _.hash)
+ (set.difference (set.of_list _.hash locals))
+ set.list)
+ {.#End}
+ [(_.function @loop locals
+ scope!)
+ @loop]
- foreigns
- (let [@context (_.var (format (_.code @loop) "_context"))]
- [(_.function @context foreigns
- ($_ _.then
- (<| (_.local_function @loop locals)
- scope!)
- (_.return @loop)
- ))
- (_.apply foreigns @context)])))]
+ foreigns
+ (let [@context (_.var (format (_.code @loop) "_context"))]
+ [(_.function @context foreigns
+ ($_ _.then
+ (<| (_.local_function @loop locals)
+ scope!)
+ (_.return @loop)
+ ))
+ (_.apply foreigns @context)])))]
_ (/////generation.execute! directive)
_ (/////generation.save! artifact_id {.#None} directive)]
(in (_.apply initsO+ instantiation)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
index 595c313cf..761b34fab 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
@@ -38,11 +38,11 @@
(def: .public register
(-> Register Var)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
index add7ae3e5..bd95510e2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
@@ -1,33 +1,33 @@
(.using
- [library
- [lux {"-" Global function}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- pipe]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [target
- ["_" php {"+" Var Global Expression Argument Label Statement}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Phase! Generator}]
+ [library
+ [lux {"-" Global function}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ pipe]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [target
+ ["_" php {"+" Var Global Expression Argument Label Statement}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Phase! Generator}]
+ ["[1][0]" reference]
+ ["[1][0]" case]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" case]
- ["/[1]" // "_"
- ["[1][0]" reference]
+ ["//[1]" /// "_"
+ [analysis {"+" Variant Tuple Abstraction Application Analysis}]
+ [synthesis {"+" Synthesis}]
+ ["[1][0]" generation {"+" Context}]
["//[1]" /// "_"
- [analysis {"+" Variant Tuple Abstraction Application Analysis}]
- [synthesis {"+" Synthesis}]
- ["[1][0]" generation {"+" Context}]
- ["//[1]" /// "_"
- [arity {"+" Arity}]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [reference
- [variable {"+" Register Variable}]]]]]])
+ [arity {"+" Arity}]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [reference
+ [variable {"+" Register Variable}]]]]]])
(def: .public (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
@@ -38,7 +38,7 @@
(def: capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: input
(|>> ++ //case.register))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
index 7fc0e8c4d..1f2d6253c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
@@ -1,37 +1,37 @@
(.using
- [library
- [lux {"-" Scope}
- [abstract
- ["[0]" monad {"+" do}]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]
- ["[0]" set {"+" Set}]]]
- [math
- [number
- ["n" nat]]]
- [target
- ["_" php {"+" Var Expression Label Statement}]]]]
- ["[0]" // "_"
- [runtime {"+" Operation Phase Phase! Generator Generator!}]
- ["[1][0]" case]
+ [library
+ [lux {"-" Scope}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]
+ ["[0]" set {"+" Set}]]]
+ [math
+ [number
+ ["n" nat]]]
+ [target
+ ["_" php {"+" Var Expression Label Statement}]]]]
+ ["[0]" // "_"
+ [runtime {"+" Operation Phase Phase! Generator Generator!}]
+ ["[1][0]" case]
+ ["/[1]" // "_"
+ ["[1][0]" reference]
["/[1]" // "_"
- ["[1][0]" reference]
+ [synthesis
+ ["[0]" case]]
["/[1]" // "_"
- [synthesis
- ["[0]" case]]
- ["/[1]" // "_"
- ["[0]"synthesis {"+" Scope Synthesis}]
- ["[1][0]" generation]
- ["//[1]" /// "_"
- ["[1][0]" phase]
- [meta
- [archive {"+" Archive}]]
- [reference
- [variable {"+" Register}]]]]]]])
+ ["[0]"synthesis {"+" Scope Synthesis}]
+ ["[1][0]" generation]
+ ["//[1]" /// "_"
+ ["[1][0]" phase]
+ [meta
+ [archive {"+" Archive}]]
+ [reference
+ [variable {"+" Register}]]]]]]])
(def: @scope
(-> Nat Label)
@@ -84,23 +84,23 @@
(list#each (|>> product.left (n.+ start) //case.register _.parameter)))
@loop (_.constant (///reference.artifact [loop_module loop_artifact]))
loop_variables (set.of_list _.hash (list#each product.right locals))
- referenced_variables (: (-> Synthesis (Set Var))
- (|>> synthesis.path/then
- //case.dependencies
- (set.of_list _.hash)))
- [directive instantiation] (: [Statement Expression]
- (case (|> (list#each referenced_variables initsS+)
- (list#mix set.union (referenced_variables bodyS))
- (set.difference loop_variables)
- set.list)
- {.#End}
- [(_.define_function @loop (list) scope!)
- @loop]
+ referenced_variables (is (-> Synthesis (Set Var))
+ (|>> synthesis.path/then
+ //case.dependencies
+ (set.of_list _.hash)))
+ [directive instantiation] (is [Statement Expression]
+ (case (|> (list#each referenced_variables initsS+)
+ (list#mix set.union (referenced_variables bodyS))
+ (set.difference loop_variables)
+ set.list)
+ {.#End}
+ [(_.define_function @loop (list) scope!)
+ @loop]
- foreigns
- [(<| (_.define_function @loop (list#each _.parameter foreigns))
- (_.return (_.closure (list#each _.parameter foreigns) (list) scope!)))
- (_.apply/* foreigns @loop)]))]
+ foreigns
+ [(<| (_.define_function @loop (list#each _.parameter foreigns))
+ (_.return (_.closure (list#each _.parameter foreigns) (list) scope!)))
+ (_.apply/* foreigns @loop)]))]
_ (/////generation.execute! directive)
_ (/////generation.save! loop_artifact directive)]
(in (_.apply/* (list) instantiation)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
index 3e4699361..aed266e9f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
@@ -48,11 +48,11 @@
(def: .public register
(-> Register SVar)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register SVar)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
index 9692d6ee7..efbefac6b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
@@ -43,7 +43,7 @@
(def: .public capture
(-> Register SVar)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure function_id @function inits function_definition)
(-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
index 36762f8cc..5c6d545f1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
@@ -89,23 +89,23 @@
actual_loop (<| (_.def @loop locals)
..set_scope
body!)
- [directive instantiation] (: [(Statement Any) (Expression Any)]
- (case (|> (synthesis.path/then bodyS)
- //case.dependencies
- (set.of_list _.hash)
- (set.difference (set.of_list _.hash locals))
- set.list)
- {.#End}
- [actual_loop
- @loop]
+ [directive instantiation] (is [(Statement Any) (Expression Any)]
+ (case (|> (synthesis.path/then bodyS)
+ //case.dependencies
+ (set.of_list _.hash)
+ (set.difference (set.of_list _.hash locals))
+ set.list)
+ {.#End}
+ [actual_loop
+ @loop]
- foreigns
- [(_.def @loop foreigns
- ($_ _.then
- actual_loop
- (_.return @loop)
- ))
- (_.apply/* foreigns @loop)]))]
+ foreigns
+ [(_.def @loop foreigns
+ ($_ _.then
+ actual_loop
+ (_.return @loop)
+ ))
+ (_.apply/* foreigns @loop)]))]
_ (/////generation.execute! directive)
_ (/////generation.save! loop_artifact {.#None} directive)]
(in (_.apply/* initsO+ instantiation)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
index 2b849271b..d75170250 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
@@ -39,11 +39,11 @@
(def: .public register
(-> Register SVar)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register SVar)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index 8a56bf21a..6968c5618 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -1,45 +1,45 @@
(.using
- [library
- [lux {"-" Location ++ i64}
- ["[0]" meta]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" function]
- ["<>" parser
- ["<[0]>" code]]]
- [data
- ["[0]" product]
- ["[0]" text ("[1]#[0]" hash)
- ["%" format {"+" format}]
- [encoding
- ["[0]" utf8]]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]
- ["[0]" sequence]]]
- ["[0]" macro
- [syntax {"+" syntax:}]
- ["[0]" code]]
- [math
- [number {"+" hex}
- ["n" nat]
- ["i" int ("[1]#[0]" interval)]
- ["[0]" i64]]]
- ["@" target
- ["_" r {"+" SVar Expression}]]]]
- ["[0]" /// "_"
- ["[1][0]" reference]
- ["//[1]" /// "_"
- [analysis {"+" Variant}]
- ["[1][0]" synthesis {"+" Synthesis}]
- ["[1][0]" generation]
- ["//[1]" ///
- ["[1][0]" phase]
- [reference
- [variable {"+" Register}]]
- [meta
- [archive {"+" Output Archive}
- ["[0]" artifact {"+" Registry}]]]]]])
+ [library
+ [lux {"-" Location ++ i64}
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["<>" parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" product]
+ ["[0]" text ("[1]#[0]" hash)
+ ["%" format {"+" format}]
+ [encoding
+ ["[0]" utf8]]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]
+ ["[0]" sequence]]]
+ ["[0]" macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]
+ [math
+ [number {"+" hex}
+ ["n" nat]
+ ["i" int ("[1]#[0]" interval)]
+ ["[0]" i64]]]
+ ["@" target
+ ["_" r {"+" SVar Expression}]]]]
+ ["[0]" /// "_"
+ ["[1][0]" reference]
+ ["//[1]" /// "_"
+ [analysis {"+" Variant}]
+ ["[1][0]" synthesis {"+" Synthesis}]
+ ["[1][0]" generation]
+ ["//[1]" ///
+ ["[1][0]" phase]
+ [reference
+ [variable {"+" Register}]]
+ [meta
+ [archive {"+" Output Archive}
+ ["[0]" artifact {"+" Registry}]]]]]])
(def: module_id
0)
@@ -271,11 +271,11 @@
(_.apply (list value) (_.var "is.na")))
isTRUE? (function (_ value)
(_.apply (list value) (_.var "isTRUE")))
- comparison (: (-> (-> Expression Expression) Expression)
- (function (_ field)
- (|> (|> (field sample) (_.= (field reference)))
- (_.or (|> (n/a? (field sample))
- (_.and (n/a? (field reference))))))))]
+ comparison (is (-> (-> Expression Expression) Expression)
+ (function (_ field)
+ (|> (|> (field sample) (_.= (field reference)))
+ (_.or (|> (n/a? (field sample))
+ (_.and (n/a? (field reference))))))))]
(|> (comparison i64_high)
(_.and (comparison i64_low))
isTRUE?)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux
index 50fae65d9..79ed4680c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux
@@ -55,10 +55,10 @@
(type: .public (System expression)
(Interface
- (: (-> Text expression)
- constant')
- (: (-> Text expression)
- variable')))
+ (is (-> Text expression)
+ constant')
+ (is (-> Text expression)
+ variable')))
(def: .public (constant system archive name)
(All (_ anchor expression directive)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
index 1d513b57b..284fa79c6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
@@ -46,11 +46,11 @@
(def: .public register
(-> Register LVar)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register LVar)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (exec expression archive [this that])
(Generator [Synthesis Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
index 6d4193788..f6b20a5d6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
@@ -41,7 +41,7 @@
(def: .public capture
(-> Register LVar)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure inits self function_definition)
(-> (List Expression) Text Expression [Statement Expression])
@@ -77,13 +77,13 @@
arityO (|> arity .int _.int)
limitO (|> arity -- .int _.int)
@num_args (_.local "num_args")
- @self (: _.Location
- (case closureO+
- {.#End}
- (_.global function_name)
+ @self (is _.Location
+ (case closureO+
+ {.#End}
+ (_.global function_name)
- _
- (_.local function_name)))
+ _
+ (_.local function_name)))
initialize_self! (_.set (list (//case.register 0)) @self)
initialize! (list#mix (.function (_ post pre!)
($_ _.then
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
index aeed6ea59..e5cc0a650 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
@@ -39,11 +39,11 @@
(def: .public register
(-> Register Var)
- (|>> (///reference.local //reference.system) :expected))
+ (|>> (///reference.local //reference.system) as_expected))
(def: .public capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: .public (let expression archive [valueS register bodyS])
(Generator [Synthesis Register Synthesis])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
index 2c5cf5a82..9ff5b8f94 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
@@ -1,33 +1,33 @@
(.using
- [library
- [lux {"-" function}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- pipe]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [target
- ["_" scheme {"+" Expression Computation Var}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Generator}]
+ [library
+ [lux {"-" function}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ pipe]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [target
+ ["_" scheme {"+" Expression Computation Var}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Generator}]
+ ["[1][0]" reference]
+ ["[1][0]" case]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" case]
- ["/[1]" // "_"
- ["[1][0]" reference]
+ ["//[1]" /// "_"
+ [analysis {"+" Variant Tuple Abstraction Application Analysis}]
+ [synthesis {"+" Synthesis}]
+ ["[1][0]" generation {"+" Context}]
["//[1]" /// "_"
- [analysis {"+" Variant Tuple Abstraction Application Analysis}]
- [synthesis {"+" Synthesis}]
- ["[1][0]" generation {"+" Context}]
- ["//[1]" /// "_"
- [arity {"+" Arity}]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [reference
- [variable {"+" Register Variable}]]]]]])
+ [arity {"+" Arity}]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [reference
+ [variable {"+" Register Variable}]]]]]])
(def: .public (apply expression archive [functionS argsS+])
(Generator (Application Synthesis))
@@ -38,7 +38,7 @@
(def: capture
(-> Register Var)
- (|>> (///reference.foreign //reference.system) :expected))
+ (|>> (///reference.foreign //reference.system) as_expected))
(def: (with_closure inits function_definition)
(-> (List Expression) Computation (Operation Computation))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
index 13d591126..87abcaff0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
@@ -65,17 +65,17 @@
[locals /.locals]
(in (|> functionS
(//loop.optimization true locals argsS)
- (maybe#each (: (-> [Nat (List Synthesis) Synthesis] Synthesis)
- (function (_ [start inits iteration])
- (case iteration
- (pattern (/.loop/scope [start' inits' output]))
- (if (and (n.= start start')
- (list.empty? inits'))
- (/.loop/scope [start inits output])
- (/.loop/scope [start inits iteration]))
+ (maybe#each (is (-> [Nat (List Synthesis) Synthesis] Synthesis)
+ (function (_ [start inits iteration])
+ (case iteration
+ (pattern (/.loop/scope [start' inits' output]))
+ (if (and (n.= start start')
+ (list.empty? inits'))
+ (/.loop/scope [start inits output])
+ (/.loop/scope [start inits iteration]))
- _
- (/.loop/scope [start inits iteration])))))
+ _
+ (/.loop/scope [start inits iteration])))))
(maybe.else <apply>))))
(in <apply>))
@@ -261,20 +261,20 @@
bodyS (/.with_currying? true
(/.with_locals 2
(phase archive bodyA)))
- abstraction (: (Operation Abstraction)
- (case bodyS
- (pattern (/.function/abstraction [env' down_arity' bodyS']))
- (|> bodyS'
- (grow env')
- (# ! each (function (_ body)
- [/.#environment environment
- /.#arity (++ down_arity')
- /.#body body])))
-
- _
- (in [/.#environment environment
- /.#arity 1
- /.#body bodyS])))
+ abstraction (is (Operation Abstraction)
+ (case bodyS
+ (pattern (/.function/abstraction [env' down_arity' bodyS']))
+ (|> bodyS'
+ (grow env')
+ (# ! each (function (_ body)
+ [/.#environment environment
+ /.#arity (++ down_arity')
+ /.#body body])))
+
+ _
+ (in [/.#environment environment
+ /.#arity 1
+ /.#body bodyS])))
currying? /.currying?]
(in (/.function/abstraction
(if currying?
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
index 85e4d28af..5429a8f0c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
@@ -278,11 +278,11 @@
[{<tag> [[test then] elses]}
(do [! try.monad]
[[redundancy then] (again [redundancy then])
- [redundancy elses] (..list_optimization (: (Optimization [<type> Path])
- (function (_ [redundancy [else_test else_then]])
- (do !
- [[redundancy else_then] (again [redundancy else_then])]
- (in [redundancy [else_test else_then]]))))
+ [redundancy elses] (..list_optimization (is (Optimization [<type> Path])
+ (function (_ [redundancy [else_test else_then]])
+ (do !
+ [[redundancy else_then] (again [redundancy else_then])]
+ (in [redundancy [else_test else_then]]))))
[redundancy elses])]
(in [redundancy {<tag> [[test then] elses]}]))])
([/.#I64_Fork I64]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
index a2a47c775..dbe91632a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -186,8 +186,8 @@
(-> Source (Either [Source Text] [Source a])))
(template: (!with_char+ @source_code_size @source_code @offset @char @else @body)
- [(if (!i/< (:as Int @source_code_size)
- (:as Int @offset))
+ [(if (!i/< (as Int @source_code_size)
+ (as Int @offset))
(let [@char ("lux text char" @offset @source_code)]
@body)
@else)])
@@ -202,7 +202,7 @@
... {.#Left error}
<<otherwise>>
- (:expected <<otherwise>>))])
+ (as_expected <<otherwise>>))])
(template: (!horizontal where offset source_code)
[[(revised .#column ++ where)
@@ -228,8 +228,8 @@
[(inline: (<name> parse where offset source_code)
(-> (Parser Code) Location Offset Text
(Either [Source Text] [Source Code]))
- (loop [source (: Source [(!forward 1 where) offset source_code])
- stack (: (List Code) {.#End})]
+ (loop [source (is Source [(!forward 1 where) offset source_code])
+ stack (is (List Code) {.#End})]
(case (parse source)
{.#Right [source' top]}
(again source' {.#Item top stack})
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
index 3fd47f828..3b1a2ad84 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
@@ -428,7 +428,7 @@
(# (list.equivalence (product.equivalence <equivalence> =)) =
{.#Item reference_item}
{.#Item sample_item})])
- ([#I64_Fork (: (Equivalence I64) i64.equivalence)]
+ ([#I64_Fork (is (Equivalence I64) i64.equivalence)]
[#F64_Fork f.equivalence]
[#Text_Fork text.equivalence])
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index fbcb3c0f9..b1397ef8c 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -27,7 +27,7 @@
[number
["n" nat ("[1]#[0]" equivalence)]]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
[/
["[0]" artifact]
["[0]" registry {"+" Registry}]
@@ -79,16 +79,16 @@
(def: next
(-> Archive module.ID)
- (|>> :representation (the #next)))
+ (|>> representation (the #next)))
(def: .public empty
Archive
- (:abstraction [#next 0
- #resolver (dictionary.empty text.hash)]))
+ (abstraction [#next 0
+ #resolver (dictionary.empty text.hash)]))
(def: .public (id module archive)
(-> descriptor.Module Archive (Try module.ID))
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(case (dictionary.value module /#resolver)
{.#Some [id _]}
{try.#Success id}
@@ -99,7 +99,7 @@
(def: .public (reserve module archive)
(-> descriptor.Module Archive (Try [module.ID Archive]))
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(case (dictionary.value module /#resolver)
{.#Some _}
(exception.except ..module_has_already_been_reserved [module])
@@ -107,20 +107,20 @@
{.#None}
{try.#Success [/#next
(|> archive
- :representation
- (revised #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})]))
+ representation
+ (revised #resolver (dictionary.has module [/#next (is (Maybe (Entry Any)) {.#None})]))
(revised #next ++)
- :abstraction)]})))
+ abstraction)]})))
(def: .public (has module entry archive)
(-> descriptor.Module (Entry Any) Archive (Try Archive))
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(case (dictionary.value module /#resolver)
{.#Some [id {.#None}]}
{try.#Success (|> archive
- :representation
+ representation
(revised ..#resolver (dictionary.has module [id {.#Some entry}]))
- :abstraction)}
+ abstraction)}
{.#Some [id {.#Some [existing_module existing_output existing_registry]}]}
(if (same? (the module.#document existing_module)
@@ -134,7 +134,7 @@
(def: .public entries
(-> Archive (List [descriptor.Module [module.ID (Entry Any)]]))
- (|>> :representation
+ (|>> representation
(the #resolver)
dictionary.entries
(list.all (function (_ [module [module_id entry]])
@@ -142,7 +142,7 @@
(def: .public (find module archive)
(-> descriptor.Module Archive (Try (Entry Any)))
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(case (dictionary.value module /#resolver)
{.#Some [id {.#Some entry}]}
{try.#Success entry}
@@ -164,7 +164,7 @@
(def: .public archived
(-> Archive (List descriptor.Module))
- (|>> :representation
+ (|>> representation
(the #resolver)
dictionary.entries
(list.all (function (_ [module [id descriptor+document]])
@@ -174,7 +174,7 @@
(def: .public (reserved? archive module)
(-> Archive descriptor.Module Bit)
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(case (dictionary.value module /#resolver)
{.#Some [id _]}
true
@@ -184,13 +184,13 @@
(def: .public reserved
(-> Archive (List descriptor.Module))
- (|>> :representation
+ (|>> representation
(the #resolver)
dictionary.keys))
(def: .public reservations
(-> Archive (List [descriptor.Module module.ID]))
- (|>> :representation
+ (|>> representation
(the #resolver)
dictionary.entries
(list#each (function (_ [module [id _]])
@@ -198,9 +198,9 @@
(def: .public (merged additions archive)
(-> Archive Archive Archive)
- (let [[+next +resolver] (:representation additions)]
+ (let [[+next +resolver] (representation additions)]
(|> archive
- :representation
+ representation
(revised #next (n.max +next))
(revised #resolver (function (_ resolver)
(list#mix (function (_ [module [id entry]] resolver)
@@ -212,7 +212,7 @@
resolver))
resolver
(dictionary.entries +resolver))))
- :abstraction)))
+ abstraction)))
(type: Reservation
[descriptor.Module module.ID])
@@ -236,7 +236,7 @@
(def: .public (export version archive)
(-> Version Archive Binary)
- (let [(open "/[0]") (:representation archive)]
+ (let [(open "/[0]") (representation archive)]
(|> /#resolver
dictionary.entries
(list.all (function (_ [module [id descriptor+document]])
@@ -258,10 +258,10 @@
[[actual next reservations] (<binary>.result ..reader binary)
_ (exception.assertion ..version_mismatch [expected actual]
(n#= expected actual))]
- (in (:abstraction
+ (in (abstraction
[#next next
#resolver (list#mix (function (_ [module id] archive)
- (dictionary.has module [id (: (Maybe (Entry Any)) {.#None})] archive))
- (the #resolver (:representation ..empty))
+ (dictionary.has module [id (is (Maybe (Entry Any)) {.#None})] archive))
+ (the #resolver (representation ..empty))
reservations)]))))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
index a124fae6a..7ae44b175 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
@@ -2,7 +2,7 @@
[library
[lux "*"
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
[//
[signature {"+" Signature}]])
@@ -11,9 +11,9 @@
(def: .public signature
(All (_ ?) (-> (Key ?) Signature))
- (|>> :representation))
+ (|>> representation))
(def: .public (key signature sample)
(All (_ d) (-> Signature d (Key d)))
- (:abstraction signature))
+ (abstraction signature))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
index bc74b9c3c..73214b2ab 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
@@ -13,8 +13,8 @@
["[0]" dictionary {"+" Dictionary}]]
[format
["[0]" binary {"+" Writer}]]]
- [type {"+" :sharing}
- abstract]]]
+ [type {"+" sharing}
+ [abstract {"-" pattern}]]]]
[///
["[0]" signature {"+" Signature} ("[1]#[0]" equivalence)]
["[0]" key {"+" Key}]])
@@ -32,40 +32,40 @@
(def: .public (content key document)
(All (_ d) (-> (Key d) (Document Any) (Try d)))
- (let [[document//signature document//content] (:representation document)]
+ (let [[document//signature document//content] (representation document)]
(if (# signature.equivalence =
(key.signature key)
document//signature)
- {try.#Success (:sharing [e]
- (Key e)
- key
-
- e
- (:expected document//content))}
+ {try.#Success (sharing [e]
+ (Key e)
+ key
+
+ e
+ (as_expected document//content))}
(exception.except ..invalid_signature [(key.signature key)
document//signature]))))
(def: .public (document key content)
(All (_ d) (-> (Key d) d (Document d)))
- (:abstraction [#signature (key.signature key)
- #content content]))
+ (abstraction [#signature (key.signature key)
+ #content content]))
(def: .public (marked? key document)
(All (_ d) (-> (Key d) (Document Any) (Try (Document d))))
(do try.monad
[_ (..content key document)]
- (in (:expected document))))
+ (in (as_expected document))))
(def: .public signature
(-> (Document Any) Signature)
- (|>> :representation (the #signature)))
+ (|>> representation (the #signature)))
(def: .public (writer content)
(All (_ d) (-> (Writer d) (Writer (Document d))))
(let [writer ($_ binary.and
signature.writer
content)]
- (|>> :representation writer)))
+ (|>> representation writer)))
(def: .public (parser key it)
(All (_ d) (-> (Key d) (Parser d) (Parser (Document d))))
@@ -76,5 +76,5 @@
(in [])
(<>.lifted (exception.except ..invalid_signature [expected actual])))
it it]
- (in (:abstraction [actual it]))))
+ (in (abstraction [actual it]))))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
index d2921be2e..3e9726924 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
@@ -23,7 +23,7 @@
[macro
["^" pattern]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
["[0]" // "_"
["[0]" unit]
["[1]" artifact {"+" Artifact ID}
@@ -36,12 +36,12 @@
(def: .public empty
Registry
- (:abstraction [#artifacts sequence.empty
- #resolver (dictionary.empty text.hash)]))
+ (abstraction [#artifacts sequence.empty
+ #resolver (dictionary.empty text.hash)]))
(def: .public artifacts
(-> Registry (Sequence [Artifact (Set unit.ID)]))
- (|>> :representation (the #artifacts)))
+ (|>> representation (the #artifacts)))
(def: next
(-> Registry ID)
@@ -52,12 +52,12 @@
(let [id (..next registry)]
[id
(|> registry
- :representation
+ representation
(revised #artifacts (sequence.suffix [[//.#id id
//.#category {//category.#Anonymous}
//.#mandatory? mandatory?]
dependencies]))
- :abstraction)]))
+ abstraction)]))
(template [<tag> <create> <fetch> <type> <name> <+resolver>]
[(def: .public (<create> it mandatory? dependencies registry)
@@ -65,18 +65,18 @@
(let [id (..next registry)]
[id
(|> registry
- :representation
+ representation
(revised #artifacts (sequence.suffix [[//.#id id
//.#category {<tag> it}
//.#mandatory? mandatory?]
dependencies]))
- (revised #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)]))
- :abstraction)]))
+ (revised #resolver (dictionary.has (<name> it) [id (is (Maybe //category.Definition) <+resolver>)]))
+ abstraction)]))
(def: .public (<fetch> registry)
(-> Registry (List <type>))
(|> registry
- :representation
+ representation
(the #artifacts)
sequence.list
(list.all (|>> product.left
@@ -96,7 +96,7 @@
(def: .public (find_definition name registry)
(-> Text Registry (Maybe [ID (Maybe //category.Definition)]))
- (|> (:representation registry)
+ (|> (representation registry)
(the #resolver)
(dictionary.value name)))
@@ -106,37 +106,37 @@
(def: .public writer
(Writer Registry)
- (let [definition (: (Writer //category.Definition)
- ($_ binary.and
- binary.text
- (binary.maybe
- ($_ binary.and
- binary.nat
- binary.nat
- binary.nat
- ))
- ))
- category (: (Writer Category)
- (function (_ value)
- (case value
- (^.template [<nat> <tag> <writer>]
- [{<tag> value}
- ((binary.and binary.nat <writer>) [<nat> value])])
- ([0 //category.#Anonymous binary.any]
- [1 //category.#Definition definition]
- [2 //category.#Analyser binary.text]
- [3 //category.#Synthesizer binary.text]
- [4 //category.#Generator binary.text]
- [5 //category.#Directive binary.text]
- [6 //category.#Custom binary.text]))))
+ (let [definition (is (Writer //category.Definition)
+ ($_ binary.and
+ binary.text
+ (binary.maybe
+ ($_ binary.and
+ binary.nat
+ binary.nat
+ binary.nat
+ ))
+ ))
+ category (is (Writer Category)
+ (function (_ value)
+ (case value
+ (^.template [<nat> <tag> <writer>]
+ [{<tag> value}
+ ((binary.and binary.nat <writer>) [<nat> value])])
+ ([0 //category.#Anonymous binary.any]
+ [1 //category.#Definition definition]
+ [2 //category.#Analyser binary.text]
+ [3 //category.#Synthesizer binary.text]
+ [4 //category.#Generator binary.text]
+ [5 //category.#Directive binary.text]
+ [6 //category.#Custom binary.text]))))
mandatory? binary.bit
- dependency (: (Writer unit.ID)
- (binary.and binary.nat binary.nat))
- dependencies (: (Writer (Set unit.ID))
- (binary.set dependency))
- artifacts (: (Writer (Sequence [Category Bit (Set unit.ID)]))
- (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
- (|>> :representation
+ dependency (is (Writer unit.ID)
+ (binary.and binary.nat binary.nat))
+ dependencies (is (Writer (Set unit.ID))
+ (binary.set dependency))
+ artifacts (is (Writer (Sequence [Category Bit (Set unit.ID)]))
+ (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
+ (|>> representation
(the #artifacts)
(sequence#each (function (_ [it dependencies])
[(the //.#category it)
@@ -150,37 +150,37 @@
(def: .public parser
(Parser Registry)
- (let [definition (: (Parser //category.Definition)
- ($_ <>.and
- <binary>.text
- (<binary>.maybe
- ($_ <>.and
- <binary>.nat
- <binary>.nat
- <binary>.nat
- ))
- ))
- category (: (Parser Category)
- (do [! <>.monad]
- [tag <binary>.nat]
- (case tag
- (^.template [<nat> <tag> <parser>]
- [<nat>
- (# ! each (|>> {<tag>}) <parser>)])
- ([0 //category.#Anonymous <binary>.any]
- [1 //category.#Definition definition]
- [2 //category.#Analyser <binary>.text]
- [3 //category.#Synthesizer <binary>.text]
- [4 //category.#Generator <binary>.text]
- [5 //category.#Directive <binary>.text]
- [6 //category.#Custom <binary>.text])
-
- _ (<>.failure (exception.error ..invalid_category [tag])))))
+ (let [definition (is (Parser //category.Definition)
+ ($_ <>.and
+ <binary>.text
+ (<binary>.maybe
+ ($_ <>.and
+ <binary>.nat
+ <binary>.nat
+ <binary>.nat
+ ))
+ ))
+ category (is (Parser Category)
+ (do [! <>.monad]
+ [tag <binary>.nat]
+ (case tag
+ (^.template [<nat> <tag> <parser>]
+ [<nat>
+ (# ! each (|>> {<tag>}) <parser>)])
+ ([0 //category.#Anonymous <binary>.any]
+ [1 //category.#Definition definition]
+ [2 //category.#Analyser <binary>.text]
+ [3 //category.#Synthesizer <binary>.text]
+ [4 //category.#Generator <binary>.text]
+ [5 //category.#Directive <binary>.text]
+ [6 //category.#Custom <binary>.text])
+
+ _ (<>.failure (exception.error ..invalid_category [tag])))))
mandatory? <binary>.bit
- dependency (: (Parser unit.ID)
- (<>.and <binary>.nat <binary>.nat))
- dependencies (: (Parser (Set unit.ID))
- (<binary>.set unit.hash dependency))]
+ dependency (is (Parser unit.ID)
+ (<>.and <binary>.nat <binary>.nat))
+ dependencies (is (Parser (Set unit.ID))
+ (<binary>.set unit.hash dependency))]
(|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies))
(# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry)
(product.right
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
index 4fd7fdebf..2db68a99d 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
@@ -54,17 +54,17 @@
(def: (ancestry archive)
(-> Archive Graph)
- (let [memo (: (Memo descriptor.Module Ancestry)
- (function (_ again module)
- (do [! state.monad]
- [.let [parents (case (archive.find module archive)
- {try.#Success [module output registry]}
- (the [module.#descriptor descriptor.#references] module)
-
- {try.#Failure error}
- ..fresh)]
- ancestors (monad.each ! again (set.list parents))]
- (in (list#mix set.union parents ancestors)))))
+ (let [memo (is (Memo descriptor.Module Ancestry)
+ (function (_ again module)
+ (do [! state.monad]
+ [.let [parents (case (archive.find module archive)
+ {try.#Success [module output registry]}
+ (the [module.#descriptor descriptor.#references] module)
+
+ {try.#Failure error}
+ ..fresh)]
+ ancestors (monad.each ! again (set.list parents))]
+ (in (list#mix set.union parents ancestors)))))
ancestry (memo.open memo)]
(list#mix (function (_ module memory)
(if (dictionary.key? memory module)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux
index 4d593aeda..869aa2019 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux
@@ -98,5 +98,5 @@
(|> path
(# fs read)
(# ! each (|>> [name]))))))]
- (in (dictionary.of_list text.hash (for @.old (:as (List [Text Binary]) pairs)
+ (in (dictionary.of_list text.hash (for @.old (as (List [Text Binary]) pairs)
pairs)))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
index e393253e1..55701b3f3 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
@@ -68,8 +68,8 @@
(def: .public (purge caches load_order)
(-> (List Cache) (dependency.Order Any) Purge)
(list#mix (function (_ [module_name [@module entry]] purge)
- (let [purged? (: (Predicate descriptor.Module)
- (dictionary.key? purge))]
+ (let [purged? (is (Predicate descriptor.Module)
+ (dictionary.key? purge))]
(if (purged? module_name)
purge
(if (|> entry
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux
index bbc2735e7..99f7da67a 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux
@@ -86,15 +86,15 @@
(def: .public service
(Parser Service)
- (let [compilation (: (Parser Compilation)
- ($_ <>.and
- (<>.some ..host_dependency_parser)
- (<>.some ..library_parser)
- (<>.some ..compiler_parser)
- (<>.some ..source_parser)
- ..target_parser
- ..module_parser
- (<>.else configuration.empty ..configuration_parser)))]
+ (let [compilation (is (Parser Compilation)
+ ($_ <>.and
+ (<>.some ..host_dependency_parser)
+ (<>.some ..library_parser)
+ (<>.some ..compiler_parser)
+ (<>.some ..source_parser)
+ ..target_parser
+ ..module_parser
+ (<>.else configuration.empty ..configuration_parser)))]
($_ <>.or
(<>.after (<cli>.this "build")
compilation)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux
index 9bc446b4d..09eef4deb 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux
@@ -50,10 +50,10 @@
(def: .public parser
(Parser Compiler)
- (let [parameter (: (Parser Text)
- (<| (<>.after (<text>.this ..start))
- (<>.before (<text>.this ..end))
- (<text>.slice (<text>.many! (<text>.none_of! ..end)))))]
+ (let [parameter (is (Parser Text)
+ (<| (<>.after (<text>.this ..start))
+ (<>.before (<text>.this ..end))
+ (<text>.slice (<text>.many! (<text>.none_of! ..end)))))]
(do <>.monad
[module parameter
short parameter
diff --git a/stdlib/source/library/lux/tool/compiler/meta/export.lux b/stdlib/source/library/lux/tool/compiler/meta/export.lux
index 9b21de75b..7eb36ad62 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/export.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/export.lux
@@ -38,9 +38,9 @@
(def: .public ownership
tar.Ownership
- (let [commons (: tar.Owner
- [tar.#name tar.anonymous
- tar.#id tar.no_id])]
+ (let [commons (is tar.Owner
+ [tar.#name tar.anonymous
+ tar.#id tar.no_id])]
[tar.#user commons
tar.#group commons]))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/import.lux b/stdlib/source/library/lux/tool/compiler/meta/import.lux
index c485cb5f7..f0c390e3a 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/import.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/import.lux
@@ -67,8 +67,8 @@
(def: .public (import system libraries)
(-> (file.System Async) (List Library) (Action Import))
- (monad.mix (: (Monad Action)
- (try.with async.monad))
+ (monad.mix (is (Monad Action)
+ (try.with async.monad))
(..import_library system)
(dictionary.empty text.hash)
libraries))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
index 95d9a5e1a..05f766d5d 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -78,15 +78,15 @@
(def: (analysis_state host configuration archive)
(-> Target Configuration Archive (Try .Lux))
(do [! try.monad]
- [modules (: (Try (List [descriptor.Module .Module]))
- (monad.each ! (function (_ module)
- (do !
- [entry (archive.find module archive)
- content (|> entry
- (the [archive.#module module.#document])
- (document.content $.key))]
- (in [module content])))
- (archive.archived archive)))]
+ [modules (is (Try (List [descriptor.Module .Module]))
+ (monad.each ! (function (_ module)
+ (do !
+ [entry (archive.find module archive)
+ content (|> entry
+ (the [archive.#module module.#document])
+ (document.content $.key))]
+ (in [module content])))
+ (archive.archived archive)))]
(in (has .#modules modules (fresh_analysis_state host configuration)))))
(type: Definitions (Dictionary Text Any))
@@ -113,111 +113,111 @@
(-> Text (generation.Host expression directive) module.ID (Sequence [Artifact (Set unit.ID)]) (Dictionary Text Binary) (Document .Module)
(Try [(Document .Module) Bundles Output])))
(do [! try.monad]
- [[definitions bundles] (: (Try [Definitions Bundles Output])
- (loop [input (sequence.list expected)
- definitions (: Definitions
- (dictionary.empty text.hash))
- bundles ..empty_bundles
- output (: Output sequence.empty)]
- (let [[analysers synthesizers generators directives] bundles]
- (case input
- {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']}
- (case (do !
- [data (try.of_maybe (dictionary.value (format (%.nat @artifact) extension) actual))
- .let [context [@module @artifact]
- directive (# host ingest context data)]]
- (case artifact_category
- {category.#Anonymous}
- (do !
- [.let [output (sequence.suffix [@artifact {.#None} data] output)]
- _ (# host re_learn context {.#None} directive)]
- (in [definitions
- [analysers
- synthesizers
- generators
- directives]
- output]))
-
- {category.#Definition [name function_artifact]}
- (let [output (sequence.suffix [@artifact {.#None} data] output)]
- (if (text#= $/program.name name)
- (in [definitions
- [analysers
- synthesizers
- generators
- directives]
- output])
- (do !
- [value (# host re_load context {.#None} directive)]
- (in [(dictionary.has name value definitions)
- [analysers
- synthesizers
- generators
- directives]
- output]))))
+ [[definitions bundles] (is (Try [Definitions Bundles Output])
+ (loop [input (sequence.list expected)
+ definitions (is Definitions
+ (dictionary.empty text.hash))
+ bundles ..empty_bundles
+ output (is Output sequence.empty)]
+ (let [[analysers synthesizers generators directives] bundles]
+ (case input
+ {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']}
+ (case (do !
+ [data (try.of_maybe (dictionary.value (format (%.nat @artifact) extension) actual))
+ .let [context [@module @artifact]
+ directive (# host ingest context data)]]
+ (case artifact_category
+ {category.#Anonymous}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#None} data] output)]
+ _ (# host re_learn context {.#None} directive)]
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output]))
+
+ {category.#Definition [name function_artifact]}
+ (let [output (sequence.suffix [@artifact {.#None} data] output)]
+ (if (text#= $/program.name name)
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output])
+ (do !
+ [value (# host re_load context {.#None} directive)]
+ (in [(dictionary.has name value definitions)
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output]))))
- {category.#Analyser extension}
- (do !
- [.let [output (sequence.suffix [@artifact {.#None} data] output)]
- value (# host re_load context {.#None} directive)]
- (in [definitions
- [(dictionary.has extension (:as analysis.Handler value) analysers)
- synthesizers
- generators
- directives]
- output]))
+ {category.#Analyser extension}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#None} data] output)]
+ value (# host re_load context {.#None} directive)]
+ (in [definitions
+ [(dictionary.has extension (as analysis.Handler value) analysers)
+ synthesizers
+ generators
+ directives]
+ output]))
- {category.#Synthesizer extension}
- (do !
- [.let [output (sequence.suffix [@artifact {.#None} data] output)]
- value (# host re_load context {.#None} directive)]
- (in [definitions
- [analysers
- (dictionary.has extension (:as synthesis.Handler value) synthesizers)
- generators
- directives]
- output]))
+ {category.#Synthesizer extension}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#None} data] output)]
+ value (# host re_load context {.#None} directive)]
+ (in [definitions
+ [analysers
+ (dictionary.has extension (as synthesis.Handler value) synthesizers)
+ generators
+ directives]
+ output]))
- {category.#Generator extension}
- (do !
- [.let [output (sequence.suffix [@artifact {.#None} data] output)]
- value (# host re_load context {.#None} directive)]
- (in [definitions
- [analysers
- synthesizers
- (dictionary.has extension (:as generation.Handler value) generators)
- directives]
- output]))
+ {category.#Generator extension}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#None} data] output)]
+ value (# host re_load context {.#None} directive)]
+ (in [definitions
+ [analysers
+ synthesizers
+ (dictionary.has extension (as generation.Handler value) generators)
+ directives]
+ output]))
- {category.#Directive extension}
- (do !
- [.let [output (sequence.suffix [@artifact {.#None} data] output)]
- value (# host re_load context {.#None} directive)]
- (in [definitions
- [analysers
- synthesizers
- generators
- (dictionary.has extension (:as directive.Handler value) directives)]
- output]))
+ {category.#Directive extension}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#None} data] output)]
+ value (# host re_load context {.#None} directive)]
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ (dictionary.has extension (as directive.Handler value) directives)]
+ output]))
- {category.#Custom name}
- (do !
- [.let [output (sequence.suffix [@artifact {.#Some name} data] output)]
- _ (# host re_learn context {.#Some name} directive)]
- (in [definitions
- [analysers
- synthesizers
- generators
- directives]
- output]))))
- {try.#Success [definitions' bundles' output']}
- (again input' definitions' bundles' output')
+ {category.#Custom name}
+ (do !
+ [.let [output (sequence.suffix [@artifact {.#Some name} data] output)]
+ _ (# host re_learn context {.#Some name} directive)]
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output]))))
+ {try.#Success [definitions' bundles' output']}
+ (again input' definitions' bundles' output')
- failure
- failure)
-
- {.#End}
- {try.#Success [definitions bundles output]}))))
+ failure
+ failure)
+
+ {.#End}
+ {try.#Success [definitions bundles output]}))))
content (document.content $.key document)
definitions (monad.each ! (function (_ [def_name def_global])
(case def_global
@@ -241,7 +241,7 @@
(dictionary.value def_name)
try.of_maybe
(# ! each (function (_ def_value)
- [def_name {.#Type [exported? (:as .Type def_value) labels]}])))))
+ [def_name {.#Type [exported? (as .Type def_value) labels]}])))))
(the .#definitions content))]
(in [(document.document $.key (has .#definitions definitions content))
bundles])))
@@ -252,8 +252,8 @@
(archive.Entry .Module)
(Async (Try [(archive.Entry .Module) Bundles]))))
(do (try.with async.monad)
- [actual (: (Async (Try (Dictionary Text Binary)))
- (cache/module.artifacts async.monad fs context @module))
+ [actual (is (Async (Try (Dictionary Text Binary)))
+ (cache/module.artifacts async.monad fs context @module))
.let [expected (registry.artifacts (the archive.#registry entry))]
[document bundles output] (|> (the [archive.#module module.#document] entry)
(loaded_document (the context.#artifact_extension context) host_environment @module expected actual)
@@ -269,8 +269,8 @@
(def: (cache_parser customs)
(-> (List Custom) (Parser [(module.Module Any) Registry]))
- (case (for @.old (:as (List (Custom Any Any Any))
- customs)
+ (case (for @.old (as (List (Custom Any Any Any))
+ customs)
customs)
{.#End}
(..parser $.key $.parser)
@@ -287,8 +287,8 @@
(Async (Try Cache)))
(with_expansions [<cache> (as_is module_name @module module registry)]
(do [! (try.with async.monad)]
- [data (: (Async (Try Binary))
- (cache/module.cache fs context @module))
+ [data (is (Async (Try Binary))
+ (cache/module.cache fs context @module))
[module registry] (async#in (<binary>.result (..cache_parser customs) data))]
(if (text#= descriptor.runtime module_name)
(in [true <cache>])
@@ -314,7 +314,7 @@
(function (_ [_ [module @module |module| registry]] archive)
(archive.has module
[archive.#module |module|
- archive.#output (: Output sequence.empty)
+ archive.#output (is Output sequence.empty)
archive.#registry registry]
archive))
archive)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
index 00288e42b..3abcfbf5a 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
@@ -173,8 +173,8 @@
(def: .public (listing fs contexts)
(-> (file.System Async) (List Context) (Action Enumeration))
- (let [! (: (Monad Action)
- (try.with async.monad))]
+ (let [! (is (Monad Action)
+ (try.with async.monad))]
(monad.mix !
(function (_ context enumeration)
(do !
@@ -183,6 +183,6 @@
(format context (# fs separator))
context
enumeration)))
- (: Enumeration
- (dictionary.empty text.hash))
+ (is Enumeration
+ (dictionary.empty text.hash))
contexts)))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
index df7f11ce0..ed360caec 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
@@ -1,7 +1,7 @@
(.using
[library
[lux "*"
- [type {"+" :sharing}]
+ [type {"+" sharing}]
[abstract
["[0]" monad {"+" do}]]
[control
@@ -62,12 +62,12 @@
(|> content
(# utf8.codec decoded)
(# ! each
- (|>> :expected
- (:sharing [directive]
- directive
- so_far
-
- directive)
+ (|>> as_expected
+ (sharing [directive]
+ directive
+ so_far
+
+ directive)
(_.then so_far)))))
(_.comment "Lux module"
(_.statement (_.string "")))
@@ -84,8 +84,8 @@
(List [module.ID [Text Binary]])
(Try (List [module.ID [Text Binary]])))
(do [! try.monad]
- [bundle (: (Try (Maybe _.Statement))
- (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))]
+ [bundle (is (Try (Maybe _.Statement))
+ (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))]
(case bundle
{.#None}
(in sink)
@@ -93,7 +93,7 @@
{.#Some bundle}
(let [entry_content (|> (list)
(list#mix _.then bundle)
- (: _.Statement)
+ (is _.Statement)
_.code
(# utf8.codec encoded))]
(in (list& [module_id [(..module_file module_id) entry_content]]
@@ -127,11 +127,11 @@
(let [relative_path (_.do "gsub" (list (_.string main_file)
(_.string (..module_file module_id)))
{.#None}
- (: _.CVar (_.manual "__FILE__")))]
+ (is _.CVar (_.manual "__FILE__")))]
(_.statement (_.require/1 relative_path)))))
(list#mix _.then (_.comment "Lux program"
(_.statement (_.string ""))))
- (: _.Statement)
+ (is _.Statement)
_.code
(# utf8.codec encoded))]]
(in (|> entries
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
index f1dfb0189..c7548669a 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
@@ -1,7 +1,7 @@
(.using
[library
[lux {"-" Module}
- [type {"+" :sharing}]
+ [type {"+" sharing}]
[abstract
["[0]" monad {"+" do}]]
[control
@@ -63,14 +63,14 @@
(|> content
(# encoding.utf8 decoded)
(# try.monad each
- (|>> :expected
- (:sharing [directive]
- directive
- so_far
-
- directive)
+ (|>> as_expected
+ (sharing [directive]
+ directive
+ so_far
+
+ directive)
(..then so_far)))))
- (: _.Expression (_.manual "")))))
+ (is _.Expression (_.manual "")))))
(def: module_file
(-> archive.ID file.Path)
@@ -100,19 +100,19 @@
[Module [archive.ID [Descriptor (Document .Module) Output]]]
(Try tar.Entry))
(do [! try.monad]
- [bundle (: (Try _.Expression)
- (..bundle_module output))
- entry_content (: (Try tar.Content)
- (|> descriptor
- (the descriptor.#references)
- set.list
- (list.all (function (_ module) (dictionary.value module mapping)))
- (list#each (|>> ..module_file _.string _.load_relative/1))
- (list#mix ..then bundle)
- (: _.Expression)
- _.code
- (# encoding.utf8 encoded)
- tar.content))
+ [bundle (is (Try _.Expression)
+ (..bundle_module output))
+ entry_content (is (Try tar.Content)
+ (|> descriptor
+ (the descriptor.#references)
+ set.list
+ (list.all (function (_ module) (dictionary.value module mapping)))
+ (list#each (|>> ..module_file _.string _.load_relative/1))
+ (list#mix ..then bundle)
+ (is _.Expression)
+ _.code
+ (# encoding.utf8 encoded)
+ tar.content))
module_file (tar.path (..module_file module_id))]
(in {tar.#Normal [module_file now ..mode ..ownership entry_content]})))
@@ -125,7 +125,7 @@
(list#each (function (_ [module [module_id [descriptor document output]]])
[module module_id]))
(dictionary.of_list text.hash)
- (: (Dictionary Module archive.ID)))]
+ (is (Dictionary Module archive.ID)))]
entries (monad.each ! (..write_module now mapping) order)]
(in (|> entries
sequence.of_list
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
index 1b867cd4f..37db58b89 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
@@ -1,7 +1,7 @@
(.using
[library
[lux "*"
- [type {"+" :sharing}]
+ [type {"+" sharing}]
[abstract
["[0]" monad {"+" Monad do}]]
[control
@@ -49,12 +49,12 @@
(|> content
(# utf8.codec decoded)
(# try.monad each
- (|>> :expected
- (:sharing [directive]
- directive
- so_far
-
- directive)
+ (|>> as_expected
+ (sharing [directive]
+ directive
+ so_far
+
+ directive)
(sequence so_far)))))
so_far)))