diff options
author | Eduardo Julian | 2022-03-14 03:33:01 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-03-14 03:33:01 -0400 |
commit | 93eb82e1bf6d2f2a6b3b0adb85f4ab93cbb766a9 (patch) | |
tree | 9301db84130bb3714d57db1196e80e7325b7f880 /stdlib/source/library/lux/tool/compiler | |
parent | b8681fd206d5b5076b9737ee54f0cb0405a898d6 (diff) |
De-sigil-ification: @
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
44 files changed, 507 insertions, 507 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 7f815abf9..48a1fb475 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -110,8 +110,8 @@ {.#Right [source' output]} (let [[location _] output] {try.#Success [[bundle (|> compiler - (with@ .#source source') - (with@ .#location location))] + (has .#source source') + (has .#location location))] [source' output]]})))) (type: (Operation a) @@ -128,13 +128,13 @@ (///directive.Operation anchor expression directive [Source (Payload directive)]))) (do ///phase.monad - [.let [module (value@ ///.#module input)] + [.let [module (the ///.#module input)] _ (///directive.set_current_module module)] (///directive.lifted_analysis (do [! ///phase.monad] [_ (moduleA.create hash module) _ (monad.each ! moduleA.import dependencies) - .let [source (///analysis.source (value@ ///.#module input) (value@ ///.#code input))] + .let [source (///analysis.source (the ///.#module input) (the ///.#code input))] _ (///analysis.set_source_code source)] (in [source [///generation.empty_buffer registry.empty]]))))) @@ -223,13 +223,13 @@ (def: (default_dependencies prelude input) (-> descriptor.Module ///.Input (List descriptor.Module)) (list& descriptor.runtime - (if (text#= prelude (value@ ///.#module input)) + (if (text#= prelude (the ///.#module input)) (list) (list prelude)))) (def: module_aliases (-> .Module Aliases) - (|>> (value@ .#module_aliases) (dictionary.of_list text.hash))) + (|>> (the .#module_aliases) (dictionary.of_list text.hash))) (def: .public (compiler wrapper expander prelude write_directive) (All (_ anchor expression directive) @@ -241,10 +241,10 @@ [///.#dependencies dependencies ///.#process (function (_ state archive) (do [! try.monad] - [.let [hash (text#hash (value@ ///.#code input))] + [.let [hash (text#hash (the ///.#code input))] [state [source buffer]] (<| (///phase.result' state) (..begin dependencies hash input)) - .let [module (value@ ///.#module input)]] + .let [module (the ///.#module input)]] (loop [iteration (<| (///phase.result' state) (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))] (do ! @@ -255,7 +255,7 @@ [[state [analysis_module [final_buffer final_registry]]] (///phase.result' state (..end module)) .let [descriptor [descriptor.#hash hash descriptor.#name module - descriptor.#file (value@ ///.#file input) + descriptor.#file (the ///.#file input) descriptor.#references (set.of_list text.hash dependencies) descriptor.#state {.#Compiled}]]] (in [state @@ -271,7 +271,7 @@ (let [[temporary_buffer temporary_registry] temporary_payload] (in [state {.#Left [///.#dependencies (|> requirements - (value@ ///directive.#imports) + (the ///directive.#imports) (list#each product.left)) ///.#process (function (_ state archive) (again (<| (///phase.result' state) @@ -285,7 +285,7 @@ _ (///directive.lifted_generation (///generation.set_registry temporary_registry)) _ (|> requirements - (value@ ///directive.#referrals) + (the ///directive.#referrals) (monad.each ! (execute! archive))) temporary_payload (..get_current_payload temporary_payload)] (..iteration wrapper archive expander module source temporary_payload (..module_aliases analysis_module))))))]}])) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 6aa9f8b77..1bccf29e7 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -112,7 +112,7 @@ (All (_ <type_vars> document) (-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document) (Async (Try Any)))) - (let [system (value@ #&file_system platform) + (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)))] @@ -120,22 +120,22 @@ [_ (: (Async (Try Any)) (cache/module.enable! async.monad system context @module)) _ (for [@.python (|> entry - (value@ archive.#output) + (the archive.#output) sequence.list (list.sub 128) (monad.each ! (monad.each ! write_artifact!)) (: (Action (List (List Any)))))] (|> entry - (value@ archive.#output) + (the archive.#output) sequence.list (monad.each ..monad write_artifact!) (: (Action (List Any))))) document (# async.monad in - (document.marked? key (value@ [archive.#module module.#document] entry)))] + (document.marked? key (the [archive.#module module.#document] entry)))] (|> [(|> entry - (value@ archive.#module) - (with@ module.#document document)) - (value@ archive.#registry entry)] + (the archive.#module) + (has module.#document document)) + (the archive.#registry entry)] (_.result (..writer format)) (cache/module.cache! system context @module))))) @@ -151,7 +151,7 @@ (-> <Platform> (///generation.Operation <type_vars> [Registry Output]))) (do ///phase.monad [_ ..initialize_buffer!] - (value@ #runtime platform))) + (the #runtime platform))) (def: runtime_descriptor Descriptor @@ -226,7 +226,7 @@ (All (_ <type_vars>) (-> Archive <Platform> <State+> (Try [<State+> ///phase.Wrapper]))) (|> archive - ((value@ #phase_wrapper platform)) + ((the #phase_wrapper platform)) ///directive.lifted_generation (///phase.result' state))) @@ -262,17 +262,17 @@ Import (List _io.Context) Configuration (Async (Try [<State+> Archive ///phase.Wrapper])))) (do [! (try.with async.monad)] - [.let [state (//init.state (value@ context.#host context) + [.let [state (//init.state (the context.#host context) module compilation_configuration expander host_analysis - (value@ #host platform) - (value@ #phase platform) + (the #host platform) + (the #phase platform) generation_bundle)] _ (: (Async (Try Any)) - (cache.enable! async.monad (value@ #&file_system platform) context)) - [archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (value@ #host platform) (value@ #&file_system platform) context import compilation_sources) + (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+> @@ -306,11 +306,11 @@ (def: (module_compilation_log module) (All (_ <type_vars>) (-> descriptor.Module <State+> Text)) - (|>> (value@ [extension.#state - ///directive.#generation - ///directive.#state - extension.#state - ///generation.#log]) + (|>> (the [extension.#state + ///directive.#generation + ///directive.#state + extension.#state + ///generation.#log]) (sequence#mix (function (_ right left) (format left ..compilation_log_separator right)) module))) @@ -318,12 +318,12 @@ (def: with_reset_log (All (_ <type_vars>) (-> <State+> <State+>)) - (with@ [extension.#state - ///directive.#generation - ///directive.#state - extension.#state - ///generation.#log] - sequence.empty)) + (has [extension.#state + ///directive.#generation + ///directive.#state + extension.#state + ///generation.#log] + sequence.empty)) (def: empty (Set descriptor.Module) @@ -351,8 +351,8 @@ lens (dictionary.value module) (maybe.else ..empty)))) - transitive_depends_on (transitive_dependency (value@ #depends_on) import) - transitive_depended_by (transitive_dependency (value@ #depended_by) module) + 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]) @@ -366,14 +366,14 @@ with_dependence+transitives (set.list backward))))))] (|> dependence - (revised@ #depends_on - (update_dependence - [module transitive_depends_on] - [import transitive_depended_by])) - (revised@ #depended_by - ((function.flipped update_dependence) - [module transitive_depends_on] - [import transitive_depended_by]))))) + (revised #depends_on + (update_dependence + [module transitive_depends_on] + [import transitive_depended_by])) + (revised #depended_by + ((function.flipped update_dependence) + [module transitive_depends_on] + [import transitive_depended_by]))))) (def: (circular_dependency? module import dependence) (-> descriptor.Module descriptor.Module Dependence Bit) @@ -384,8 +384,8 @@ (dictionary.value from) (maybe.else ..empty))] (set.member? targets to))))] - (or (dependence? import (value@ #depends_on) module) - (dependence? module (value@ #depended_by) import)))) + (or (dependence? import (the #depends_on) module) + (dependence? module (the #depended_by) import)))) (exception: .public (module_cannot_import_itself [module descriptor.Module]) (exception.report @@ -444,8 +444,8 @@ (All (_ <type_vars>) (-> <State+> <State+> (Try <State+>))) (do try.monad - [inherited (with_extensions (value@ <path> from) (value@ <path> state))] - (in (with@ <path> inherited state))))] + [inherited (with_extensions (the <path> from) (the <path> state))] + (in (has <path> inherited state))))] [with_analysis_extensions [extension.#state ///directive.#analysis ///directive.#state extension.#bundle]] [with_synthesis_extensions [extension.#state ///directive.#synthesis ///directive.#state extension.#bundle]] @@ -593,7 +593,7 @@ (do ! [entry (archive.find module archive) lux_module (|> entry - (value@ [archive.#module module.#document]) + (the [archive.#module module.#document]) (document.content $.key))] (in [module lux_module]))) (archive.archived archive)) @@ -602,21 +602,21 @@ (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)))))] + (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)))))] state (monad.mix ! with_all_extensions state extended_states)] (in (with_modules state)))) @@ -687,7 +687,7 @@ (-> descriptor.Module Lux_Context (///.Compilation <State+> .Module Any) (Try [<State+> (Either (///.Compilation <State+> .Module Any) (archive.Entry Any))]))) - ((value@ ///.#process compilation) + ((the ///.#process compilation) ... TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. ... TODO: The context shouldn't need to be re-set either. (|> (///directive.set_current_module module) @@ -700,7 +700,7 @@ (All (_ <type_vars>) (-> ///phase.Wrapper Expander <Platform> (///.Compiler <State+> .Module Any))) - (let [instancer (//init.compiler phase_wrapper expander syntax.prelude (value@ #write platform))] + (let [instancer (//init.compiler phase_wrapper expander syntax.prelude (the #write platform))] (instancer $.key (list)))) (def: (custom_compiler import context platform compilation_sources compiler @@ -716,10 +716,10 @@ all_dependencies (: (Set descriptor.Module) (set.of_list text.hash (list)))] (do [! (try.with async.monad)] - [.let [new_dependencies (value@ ///.#dependencies compilation) + [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] [archive _] (any|after_imports customs import! module duplicates new_dependencies archive)] - (case ((value@ ///.#process compilation) state archive) + (case ((the ///.#process compilation) state archive) {try.#Success [state more|done]} (case more|done {.#Left more} @@ -734,7 +734,7 @@ {.#Right entry} (do ! - [.let [entry (with@ [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)] + [.let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)] _ (..cache_module context platform @module custom_key custom_format entry)] (async#in (do try.monad [archive (archive.has module entry archive)] @@ -742,7 +742,7 @@ {try.#Failure error} (do ! - [_ (cache/archive.cache! (value@ #&file_system platform) context archive)] + [_ (cache/archive.cache! (the #&file_system platform) context archive)] (async#in {try.#Failure error}))))))) (def: (lux_compiler import context platform compilation_sources compiler compilation) @@ -756,7 +756,7 @@ all_dependencies (: (Set descriptor.Module) (set.of_list text.hash (list)))] (do [! (try.with async.monad)] - [.let [new_dependencies (value@ ///.#dependencies compilation) + [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] [archive state] (lux|after_imports customs import! module duplicates new_dependencies [archive state])] (case (next_compilation module [archive state] compilation) @@ -783,7 +783,7 @@ {.#Some console} (console.write_line report console))] <else>))) - .let [entry (with@ [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)] + .let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)] _ (..cache_module context platform @module $.key $.writer (:as (archive.Entry .Module) entry))] (async#in (do try.monad [archive (archive.has module entry archive)] @@ -792,7 +792,7 @@ {try.#Failure error} (do ! - [_ (cache/archive.cache! (value@ #&file_system platform) context archive)] + [_ (cache/archive.cache! (the #&file_system platform) context archive)] (async#in {try.#Failure error}))))))) (for [@.old (as_is (def: Fake_State @@ -814,11 +814,11 @@ Lux_Compiler)) (function (_ all_customs importer import! @module [archive lux_state] module) (do [! (try.with async.monad)] - [input (io.read (value@ #&file_system platform) + [input (io.read (the #&file_system platform) importer import compilation_sources - (value@ context.#host_module_extension context) + (the context.#host_module_extension context) module)] (loop [customs (for [@.old (:as (List (///.Custom Fake_State Fake_Document Fake_Object)) all_customs)] @@ -854,22 +854,22 @@ (def: (custom import! it) (All (_ <type_vars>) (-> Lux_Importer compiler.Compiler (Async (Try [Lux_Context (List Text) Any])))) - (let [/#definition (value@ compiler.#definition it) + (let [/#definition (the compiler.#definition it) [/#module /#name] /#definition] (do ..monad [context (import! (list) descriptor.runtime /#module) .let [[archive state] context - meta_state (value@ [extension.#state - ///directive.#analysis - ///directive.#state - extension.#state] - state)] + meta_state (the [extension.#state + ///directive.#analysis + ///directive.#state + extension.#state] + state)] [_ /#type /#value] (|> /#definition meta.export (meta.result meta_state) async#in)] (async#in (if (check.subsumes? ..Custom /#type) - {try.#Success [context (value@ compiler.#parameters it) /#value]} + {try.#Success [context (the compiler.#parameters it) /#value]} (exception.except ..invalid_custom_compiler [/#definition /#type])))))) (def: .public (compile lux_compiler phase_wrapper import file_context expander platform compilation context) 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 650842124..1828747ab 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -252,10 +252,10 @@ (def: .public (with_source_code source action) (All (_ a) (-> Source (Operation a) (Operation a))) (function (_ [bundle state]) - (let [old_source (value@ .#source state)] - (.case (action [bundle (with@ .#source source state)]) + (let [old_source (the .#source state)] + (.case (action [bundle (has .#source source state)]) {try.#Success [[bundle' state'] output]} - {try.#Success [[bundle' (with@ .#source old_source state')] + {try.#Success [[bundle' (has .#source old_source state')] output]} failure @@ -263,8 +263,8 @@ (def: .public (with_current_module name) (All (_ a) (-> Text (Operation a) (Operation a))) - (extension.localized (value@ .#current_module) - (with@ .#current_module) + (extension.localized (the .#current_module) + (has .#current_module) (function.constant {.#Some name}))) (def: .public (with_location location action) @@ -272,10 +272,10 @@ (if (text#= "" (product.left location)) action (function (_ [bundle state]) - (let [old_location (value@ .#location state)] - (.case (action [bundle (with@ .#location location state)]) + (let [old_location (the .#location state)] + (.case (action [bundle (has .#location location state)]) {try.#Success [[bundle' state'] output]} - {try.#Success [[bundle' (with@ .#location old_location state')] + {try.#Success [[bundle' (has .#location old_location state')] output]} failure @@ -289,14 +289,14 @@ (def: .public (failure error) (-> Text Operation) (function (_ [bundle state]) - {try.#Failure (located (value@ .#location state) error)})) + {try.#Failure (located (the .#location state) error)})) (def: .public (of_try it) (All (_ a) (-> (Try a) (Operation a))) (function (_ [bundle state]) (.case it {try.#Failure error} - {try.#Failure (located (value@ .#location state) error)} + {try.#Failure (located (the .#location state) error)} {try.#Success it} {try.#Success [[bundle state] it]}))) @@ -318,7 +318,7 @@ (action bundle,state)) {try.#Failure error} (let [[bundle state] bundle,state] - {try.#Failure (located (value@ .#location state) error)}) + {try.#Failure (located (the .#location state) error)}) success success))) @@ -332,7 +332,7 @@ (template [<name> <type> <field> <value>] [(def: .public (<name> value) (-> <type> (Operation Any)) - (extension.update (with@ <field> <value>)))] + (extension.update (has <field> <value>)))] [set_source_code Source .#source value] [set_current_module Text .#current_module {.#Some value}] 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 a3084664d..39fcf63e7 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 @@ -83,13 +83,13 @@ (do ///.monad [self_name meta.current_module_name] (function (_ state) - {try.#Success [(revised@ .#modules - (plist.revised self_name (revised@ .#imports (function (_ current) - (if (list.any? (text#= module) - current) - current - {.#Item module current})))) - state) + {try.#Success [(revised .#modules + (plist.revised self_name (revised .#imports (function (_ current) + (if (list.any? (text#= module) + current) + current + {.#Item module current})))) + state) []]})))) (def: .public (alias alias module) @@ -98,10 +98,10 @@ (do ///.monad [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]})))) - state) + {try.#Success [(revised .#modules + (plist.revised self_name (revised .#module_aliases (: (-> (List [Text Text]) (List [Text Text])) + (|>> {.#Item [alias module]})))) + state) []]})))) (def: .public (exists? module) @@ -109,7 +109,7 @@ (///extension.lifted (function (_ state) (|> state - (value@ .#modules) + (the .#modules) (plist.value module) (case> {.#Some _} #1 {.#None} #0) [state] {try.#Success})))) @@ -121,15 +121,15 @@ [self_name meta.current_module_name self meta.current_module] (function (_ state) - (case (plist.value name (value@ .#definitions self)) + (case (plist.value name (the .#definitions self)) {.#None} - {try.#Success [(revised@ .#modules - (plist.has self_name - (revised@ .#definitions - (: (-> (List [Text Global]) (List [Text Global])) - (|>> {.#Item [name definition]})) - self)) - state) + {try.#Success [(revised .#modules + (plist.has self_name + (revised .#definitions + (: (-> (List [Text Global]) (List [Text Global])) + (|>> {.#Item [name definition]})) + self)) + state) []]} {.#Some already_existing} @@ -140,9 +140,9 @@ (-> Nat Text (Operation Any)) (///extension.lifted (function (_ state) - {try.#Success [(revised@ .#modules - (plist.has name (..empty hash)) - state) + {try.#Success [(revised .#modules + (plist.has name (..empty hash)) + state) []]}))) (def: .public (with hash name action) @@ -159,15 +159,15 @@ (-> Text (Operation Any)) (///extension.lifted (function (_ state) - (case (|> state (value@ .#modules) (plist.value module_name)) + (case (|> state (the .#modules) (plist.value module_name)) {.#Some module} - (let [active? (case (value@ .#module_state module) + (let [active? (case (the .#module_state module) {.#Active} #1 _ #0)] (if active? - {try.#Success [(revised@ .#modules - (plist.has module_name (with@ .#module_state {<tag>} module)) - state) + {try.#Success [(revised .#modules + (plist.has module_name (has .#module_state {<tag>} module)) + state) []]} ((///extension.up (/.except ..can_only_change_state_of_active_module [module_name {<tag>}])) state))) @@ -180,10 +180,10 @@ (-> Text (Operation Bit)) (///extension.lifted (function (_ state) - (case (|> state (value@ .#modules) (plist.value module_name)) + (case (|> state (the .#modules) (plist.value module_name)) {.#Some module} {try.#Success [state - (case (value@ .#module_state module) + (case (the .#module_state module) {<tag>} #1 _ #0)]} 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 d3187458a..42ccf412d 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 @@ -32,13 +32,13 @@ (def: (local? name scope) (-> Text Scope Bit) (|> scope - (value@ [.#locals .#mappings]) + (the [.#locals .#mappings]) (plist.contains? name))) (def: (local name scope) (-> Text Scope (Maybe [Type Variable])) (|> scope - (value@ [.#locals .#mappings]) + (the [.#locals .#mappings]) (plist.value name) (maybe#each (function (_ [type value]) [type {variable.#Local value}])))) @@ -46,13 +46,13 @@ (def: (captured? name scope) (-> Text Scope Bit) (|> scope - (value@ [.#captured .#mappings]) + (the [.#captured .#mappings]) (plist.contains? name))) (def: (captured name scope) (-> Text Scope (Maybe [Type Variable])) (loop [idx 0 - mappings (value@ [.#captured .#mappings] scope)] + mappings (the [.#captured .#mappings] scope)] (case mappings {.#Item [_name [_source_type _source_ref]] mappings'} (if (text#= name _name) @@ -81,7 +81,7 @@ (extension.lifted (function (_ state) (let [[inner outer] (|> state - (value@ .#scopes) + (the .#scopes) (list.split_when (|>> (reference? name))))] (case outer {.#End} @@ -92,17 +92,17 @@ (..reference name top_outer)) [ref inner'] (list#mix (: (-> Scope [Variable (List Scope)] [Variable (List Scope)]) (function (_ scope ref+inner) - [{variable.#Foreign (value@ [.#captured .#counter] scope)} - {.#Item (revised@ .#captured - (: (-> Foreign Foreign) - (|>> (revised@ .#counter ++) - (revised@ .#mappings (plist.has name [ref_type (product.left ref+inner)])))) - scope) + [{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)}])) [init_ref {.#End}] (list.reversed inner)) scopes (list#composite inner' outer)] - {.#Right [(with@ .#scopes scopes state) + {.#Right [(has .#scopes scopes state) {.#Some [ref_type ref]}]}) ))))) @@ -112,23 +112,23 @@ (def: .public (with_local [name type] action) (All (_ a) (-> [Text Type] (Operation a) (Operation a))) (function (_ [bundle state]) - (case (value@ .#scopes state) + (case (the .#scopes state) {.#Item head tail} - (let [old_mappings (value@ [.#locals .#mappings] head) - new_var_id (value@ [.#locals .#counter] head) - new_head (revised@ .#locals - (: (-> Local Local) - (|>> (revised@ .#counter ++) - (revised@ .#mappings (plist.has name [type new_var_id])))) - head)] - (case (phase.result' [bundle (with@ .#scopes {.#Item new_head tail} state)] + (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])))) + head)] + (case (phase.result' [bundle (has .#scopes {.#Item new_head tail} state)] action) {try.#Success [[bundle' state'] output]} - (case (value@ .#scopes state') + (case (the .#scopes state') {.#Item head' tail'} - (let [scopes' {.#Item (with@ .#locals (value@ .#locals head) head') + (let [scopes' {.#Item (has .#locals (the .#locals head) head') tail'}] - {try.#Success [[bundle' (with@ .#scopes scopes' state')] + {try.#Success [[bundle' (has .#scopes scopes' state')] output]}) _ @@ -153,9 +153,9 @@ (def: .public (reset action) (All (_ a) (-> (Operation a) (Operation a))) (function (_ [bundle state]) - (case (action [bundle (with@ .#scopes (list ..empty) state)]) + (case (action [bundle (has .#scopes (list ..empty) state)]) {try.#Success [[bundle' state'] output]} - {try.#Success [[bundle' (with@ .#scopes (value@ .#scopes state) state')] + {try.#Success [[bundle' (has .#scopes (the .#scopes state) state')] output]} failure @@ -164,11 +164,11 @@ (def: .public (with action) (All (_ a) (-> (Operation a) (Operation [Scope a]))) (function (_ [bundle state]) - (case (action [bundle (revised@ .#scopes (|>> {.#Item ..empty}) state)]) + (case (action [bundle (revised .#scopes (|>> {.#Item ..empty}) state)]) {try.#Success [[bundle' state'] output]} - (case (value@ .#scopes state') + (case (the .#scopes state') {.#Item head tail} - {try.#Success [[bundle' (with@ .#scopes tail state')] + {try.#Success [[bundle' (has .#scopes tail state')] [head output]]} {.#End} @@ -181,14 +181,14 @@ (Operation Register) (extension.lifted (function (_ state) - (case (value@ .#scopes state) + (case (the .#scopes state) {.#Item top _} - {try.#Success [state (value@ [.#locals .#counter] top)]} + {try.#Success [state (the [.#locals .#counter] top)]} {.#End} (exception.except ..no_scope []))))) (def: .public environment (-> Scope (Environment Variable)) - (|>> (value@ [.#captured .#mappings]) + (|>> (the [.#captured .#mappings]) (list#each (function (_ [_ [_ ref]]) ref)))) 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 e8f045d1e..f8002874f 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 @@ -26,10 +26,10 @@ (def: .public (check action) (All (_ a) (-> (Check a) (Operation a))) - (function (_ (^@ stateE [bundle state])) - (case (action (value@ .#type_context state)) + (function (_ (^let stateE [bundle state])) + (case (action (the .#type_context state)) {try.#Success [context' output]} - {try.#Success [[bundle (with@ .#type_context context' state)] + {try.#Success [[bundle (has .#type_context context' state)] output]} {try.#Failure error} @@ -60,12 +60,12 @@ (def: .public (expecting expected) (All (_ a) (-> Type (Operation a) (Operation a))) - (extension.localized (value@ .#expected) (with@ .#expected) + (extension.localized (the .#expected) (has .#expected) (function.constant {.#Some expected}))) (def: .public fresh (All (_ a) (-> (Operation a) (Operation a))) - (extension.localized (value@ .#type_context) (with@ .#type_context) + (extension.localized (the .#type_context) (has .#type_context) (function.constant check.fresh_context))) (def: .public (inference actualT) @@ -78,8 +78,8 @@ ... [pre check.context ... it (check.check expectedT actualT) ... post check.context - ... .let [pre#var_counter (value@ .#var_counter pre)]] - ... (if (n.< (value@ .#var_counter post) + ... .let [pre#var_counter (the .#var_counter pre)]] + ... (if (n.< (the .#var_counter post) ... pre#var_counter) ... (do ! ... [.let [new! (: (-> [Nat (Maybe Type)] (Maybe Nat)) @@ -88,7 +88,7 @@ ... {.#Some id} ... {.#None}))) ... new_vars (|> post - ... (value@ .#var_bindings) + ... (the .#var_bindings) ... (list.all new!))] ... _ (monad.each ! (function (_ @new) ... (do ! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux index 94b7a7894..d9bf832a3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -52,8 +52,8 @@ (def: .public (merge_requirements left right) (-> Requirements Requirements Requirements) - [#imports (list#composite (value@ #imports left) (value@ #imports right)) - #referrals (list#composite (value@ #referrals left) (value@ #referrals right))]) + [#imports (list#composite (the #imports left) (the #imports right)) + #referrals (list#composite (the #referrals left) (the #referrals right))]) (template [<special> <general>] [(type: .public (<special> anchor expression directive) @@ -71,7 +71,7 @@ (All (_ anchor expression directive) (Operation anchor expression directive <phase>)) (function (_ [bundle state]) - {try.#Success [[bundle state] (value@ [<component> ..#phase] state)]}))] + {try.#Success [[bundle state] (the [<component> ..#phase] state)]}))] [analysis ..#analysis analysis.Phase] [synthesis ..#synthesis synthesis.Phase] @@ -83,8 +83,8 @@ (All (_ anchor expression directive output) (-> (<operation> output) (Operation anchor expression directive output))) - (|>> (phase.sub [(value@ [<component> ..#state]) - (with@ [<component> ..#state])]) + (|>> (phase.sub [(the [<component> ..#state]) + (has [<component> ..#state])]) extension.lifted))] [lifted_analysis ..#analysis analysis.Operation] 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 2953b2886..e439110f9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -124,9 +124,9 @@ (All (_ anchor expression directive output) <with_type>) (function (_ body) (function (_ [bundle state]) - (case (body [bundle (with@ <tag> {.#Some <with_value>} state)]) + (case (body [bundle (has <tag> {.#Some <with_value>} state)]) {try.#Success [[bundle' state'] output]} - {try.#Success [[bundle' (with@ <tag> (value@ <tag> state) state')] + {try.#Success [[bundle' (has <tag> (the <tag> state) state')] output]} {try.#Failure error} @@ -135,8 +135,8 @@ (def: .public <get> (All (_ anchor expression directive) (Operation anchor expression directive <get_type>)) - (function (_ (^@ stateE [bundle state])) - (case (value@ <tag> state) + (function (_ (^let stateE [bundle state])) + (case (the <tag> state) {.#Some output} {try.#Success [stateE output]} @@ -147,7 +147,7 @@ (All (_ anchor expression directive) (-> <get_type> (Operation anchor expression directive Any))) (function (_ [bundle state]) - {try.#Success [[bundle (with@ <tag> {.#Some value} state)] + {try.#Success [[bundle (has <tag> {.#Some value} state)] []]}))] [#anchor @@ -168,22 +168,22 @@ (def: .public get_registry (All (_ anchor expression directive) (Operation anchor expression directive Registry)) - (function (_ (^@ stateE [bundle state])) - {try.#Success [stateE (value@ #registry state)]})) + (function (_ (^let stateE [bundle state])) + {try.#Success [stateE (the #registry state)]})) (def: .public (set_registry value) (All (_ anchor expression directive) (-> Registry (Operation anchor expression directive Any))) (function (_ [bundle state]) - {try.#Success [[bundle (with@ #registry value state)] + {try.#Success [[bundle (has #registry value state)] []]})) (def: .public next (All (_ anchor expression directive) (Operation anchor expression directive Nat)) (do phase.monad - [count (extension.read (value@ #counter)) - _ (extension.update (revised@ #counter ++))] + [count (extension.read (the #counter)) + _ (extension.update (revised #counter ++))] (in count))) (def: .public (symbol prefix) @@ -194,18 +194,18 @@ (def: .public (enter_module module) (All (_ anchor expression directive) (-> descriptor.Module (Operation anchor expression directive Any))) - (extension.update (with@ #module module))) + (extension.update (has #module module))) (def: .public module (All (_ anchor expression directive) (Operation anchor expression directive descriptor.Module)) - (extension.read (value@ #module))) + (extension.read (the #module))) (def: .public (evaluate! label code) (All (_ anchor expression directive) (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any))) - (function (_ (^@ state+ [bundle state])) - (case (# (value@ #host state) evaluate label code) + (function (_ (^let state+ [bundle state])) + (case (# (the #host state) evaluate label code) {try.#Success output} {try.#Success [state+ output]} @@ -215,8 +215,8 @@ (def: .public (execute! code) (All (_ anchor expression directive) (-> directive (Operation anchor expression directive Any))) - (function (_ (^@ state+ [bundle state])) - (case (# (value@ #host state) execute code) + (function (_ (^let state+ [bundle state])) + (case (# (the #host state) execute code) {try.#Success output} {try.#Success [state+ output]} @@ -226,8 +226,8 @@ (def: .public (define! context custom code) (All (_ anchor expression directive) (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive]))) - (function (_ (^@ stateE [bundle state])) - (case (# (value@ #host state) define context custom code) + (function (_ (^let stateE [bundle state])) + (case (# (the #host state) define context custom code) {try.#Success output} {try.#Success [stateE output]} @@ -238,13 +238,13 @@ (All (_ anchor expression directive) (-> artifact.ID (Maybe Text) directive (Operation anchor expression directive Any))) (do [! phase.monad] - [?buffer (extension.read (value@ #buffer))] + [?buffer (extension.read (the #buffer))] (case ?buffer {.#Some buffer} ... TODO: Optimize by no longer checking for overwrites... (if (sequence.any? (|>> product.left (n.= artifact_id)) buffer) (phase.except ..cannot_overwrite_output [artifact_id]) - (extension.update (with@ #buffer {.#Some (sequence.suffix [artifact_id custom code] buffer)}))) + (extension.update (has #buffer {.#Some (sequence.suffix [artifact_id custom code] buffer)}))) {.#None} (phase.except ..no_buffer_for_saving_code [artifact_id])))) @@ -253,9 +253,9 @@ [(`` (def: .public (<name> it (~~ (template.spliced <inputs>)) dependencies) (All (_ anchor expression directive) (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID))) - (function (_ (^@ stateE [bundle state])) - (let [[id registry'] (<artifact> it <mandatory?> dependencies (value@ #registry state))] - {try.#Success [[bundle (with@ #registry registry' state)] + (function (_ (^let stateE [bundle state])) + (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))] + {try.#Success [[bundle (has #registry registry' state)] id]}))))] [category.Definition mandatory? [mandatory?] [Bit] learn registry.definition] @@ -276,12 +276,12 @@ (def: .public (remember archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive unit.ID))) - (function (_ (^@ stateE [bundle state])) + (function (_ (^let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) - registry (if (text#= (value@ #module state) _module) - {try.#Success (value@ #registry state)} + registry (if (text#= (the #module state) _module) + {try.#Success (the #registry state)} (do try.monad [[_module output registry] (archive.find _module archive)] {try.#Success registry}))] @@ -295,12 +295,12 @@ (def: .public (definition archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)]))) - (function (_ (^@ stateE [bundle state])) + (function (_ (^let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) - registry (if (text#= (value@ #module state) _module) - {try.#Success (value@ #registry state)} + registry (if (text#= (the #module state) _module) + {try.#Success (the #registry state)} (do try.monad [[_module output registry] (archive.find _module archive)] {try.#Success registry}))] @@ -316,7 +316,7 @@ (def: .public (module_id module archive) (All (_ anchor expression directive) (-> descriptor.Module Archive (Operation anchor expression directive module.ID))) - (function (_ (^@ stateE [bundle state])) + (function (_ (^let stateE [bundle state])) (do try.monad [@module (archive.id module archive)] (in [stateE @module])))) @@ -324,14 +324,14 @@ (def: .public (context archive) (All (_ anchor expression directive) (-> Archive (Operation anchor expression directive unit.ID))) - (function (_ (^@ stateE [bundle state])) - (case (value@ #context state) + (function (_ (^let stateE [bundle state])) + (case (the #context state) {.#None} (exception.except ..no_context []) {.#Some id} (do try.monad - [@module (archive.id (value@ #module state) archive)] + [@module (archive.id (the #module state) archive)] (in [stateE [@module id]]))))) (def: .public (with_context @artifact body) @@ -341,8 +341,8 @@ (Operation anchor expression directive a))) (function (_ [bundle state]) (do try.monad - [[[bundle' state'] output] (body [bundle (with@ #context {.#Some @artifact} state)])] - (in [[bundle' (with@ #context (value@ #context state) state')] + [[[bundle' state'] output] (body [bundle (has #context {.#Some @artifact} state)])] + (in [[bundle' (has #context (the #context state) state')] output])))) (def: .public (with_registry_shift shift body) @@ -352,24 +352,24 @@ (Operation anchor expression directive a))) (function (_ [bundle state]) (do try.monad - [[[bundle' state'] output] (body [bundle (with@ #registry_shift shift state)])] - (in [[bundle' (with@ #registry_shift (value@ #registry_shift state) state')] + [[[bundle' state'] output] (body [bundle (has #registry_shift shift state)])] + (in [[bundle' (has #registry_shift (the #registry_shift state) state')] output])))) (def: .public (with_new_context archive dependencies body) (All (_ anchor expression directive a) (-> Archive (Set unit.ID) (Operation anchor expression directive a) (Operation anchor expression directive [unit.ID a]))) - (function (_ (^@ stateE [bundle state])) - (let [[@artifact registry'] (registry.resource false dependencies (value@ #registry state)) - @artifact (n.+ @artifact (value@ #registry_shift state))] + (function (_ (^let stateE [bundle state])) + (let [[@artifact registry'] (registry.resource false dependencies (the #registry state)) + @artifact (n.+ @artifact (the #registry_shift state))] (do try.monad [[[bundle' state'] output] (body [bundle (|> state - (with@ #registry registry') - (with@ #context {.#Some @artifact}) - (revised@ #interim_artifacts (|>> {.#Item @artifact})))]) - @module (archive.id (value@ #module state) archive)] - (in [[bundle' (with@ #context (value@ #context state) state')] + (has #registry registry') + (has #context {.#Some @artifact}) + (revised #interim_artifacts (|>> {.#Item @artifact})))]) + @module (archive.id (the #module state) archive)] + (in [[bundle' (has #context (the #context state) state')] [[@module @artifact] output]]))))) @@ -378,7 +378,7 @@ (-> Text (Operation anchor expression directive Any))) (function (_ [bundle state]) {try.#Success [[bundle - (revised@ #log (sequence.suffix message) state)] + (revised #log (sequence.suffix message) state)] []]})) (def: .public (with_interim_artifacts archive body) @@ -386,12 +386,12 @@ (-> Archive (Operation anchor expression directive a) (Operation anchor expression directive [(List unit.ID) a]))) (do phase.monad - [module (extension.read (value@ #module))] + [module (extension.read (the #module))] (function (_ state+) (do try.monad [@module (archive.id module archive) [[bundle' state'] output] (body state+)] (in [[bundle' - (with@ #interim_artifacts (list) state')] - [(list#each (|>> [@module]) (value@ #interim_artifacts state')) + (has #interim_artifacts (list) state')] + [(list#each (|>> [@module]) (the #interim_artifacts state')) output]]))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux index 7b24ab177..f38a33f0d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -48,7 +48,7 @@ {.#Definition [exported? actualT _]} (do ! [_ (/type.inference actualT) - (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> @@ -63,7 +63,7 @@ {.#Type [exported? value labels]} (do ! [_ (/type.inference .Type) - (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> 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 670b54765..f5be4859f 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 @@ -82,13 +82,13 @@ (do [! //.monad] [state //.state .let [compiler_eval (meta_eval archive - (value@ [//extension.#state /.#analysis /.#state //extension.#bundle] state) + (the [//extension.#state /.#analysis /.#state //extension.#bundle] state) (evaluation.evaluator expander - (value@ [//extension.#state /.#synthesis /.#state] state) - (value@ [//extension.#state /.#generation /.#state] state) - (value@ [//extension.#state /.#generation /.#phase] state))) + (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)))] - _ (//.with (with@ [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] + _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code (^ [_ {.#Form (list& [_ {.#Text name}] inputs)}]) (//extension.apply archive again [name inputs]) @@ -116,7 +116,7 @@ (case expansion (^ (list& <lux_def_module> referrals)) (|> (again archive <lux_def_module>) - (# ! each (revised@ /.#referrals (list#composite referrals)))) + (# ! each (revised /.#referrals (list#composite referrals)))) _ (..requiring again archive expansion))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index 0f1848eff..b4e91c905 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -117,7 +117,7 @@ (def: .public (apply archive phase [name parameters]) (All (_ s i o) (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) - (function (_ (^@ stateE [bundle state])) + (function (_ (^let stateE [bundle state])) (case (dictionary.value name bundle) {.#Some handler} (((handler name phase) archive parameters) 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 3374c4ba4..a69d511f3 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 @@ -894,9 +894,9 @@ selfT {.#Primitive name (list#each product.right parameters)}] state (extension.lifted phase.state) methods (monad.each ! (..method_definition archive super interfaces [mapping selfT] - [(value@ [directive.#analysis directive.#phase] state) - (value@ [directive.#synthesis directive.#phase] state) - (value@ [directive.#generation directive.#phase] state)]) + [(the [directive.#analysis directive.#phase] state) + (the [directive.#synthesis directive.#phase] state) + (the [directive.#generation directive.#phase] state)]) methods) .let [all_dependencies (cache.all (list#each product.left methods))] bytecode (<| (# ! each (format.result class.writer)) 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 889d400b0..3680787de 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 @@ -99,9 +99,9 @@ (-> Archive Type Code (Operation anchor expression directive [Type expression Any]))) (do phase.monad [state (///.lifted phase.state) - .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) - synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) - generate (value@ [/////directive.#generation /////directive.#phase] state)] + .let [analyse (the [/////directive.#analysis /////directive.#phase] state) + synthesize (the [/////directive.#synthesis /////directive.#phase] state) + generate (the [/////directive.#generation /////directive.#phase] state)] [_ codeA] (<| /////directive.lifted_analysis scope.with typeA.fresh @@ -145,9 +145,9 @@ (Operation anchor expression directive [Type expression Any]))) (do [! phase.monad] [state (///.lifted phase.state) - .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) - synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) - generate (value@ [/////directive.#generation /////directive.#phase] state)] + .let [analyse (the [/////directive.#analysis /////directive.#phase] state) + synthesize (the [/////directive.#synthesis /////directive.#phase] state) + generate (the [/////directive.#generation /////directive.#phase] state)] [_ code//type codeA] (/////directive.lifted_analysis (scope.with (typeA.fresh @@ -198,9 +198,9 @@ (Operation anchor expression directive [expression Any]))) (do phase.monad [state (///.lifted phase.state) - .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) - synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) - generate (value@ [/////directive.#generation /////directive.#phase] state)] + .let [analyse (the [/////directive.#analysis /////directive.#phase] state) + synthesize (the [/////directive.#synthesis /////directive.#phase] state) + generate (the [/////directive.#generation /////directive.#phase] state)] [_ codeA] (<| /////directive.lifted_analysis scope.with typeA.fresh @@ -223,17 +223,17 @@ (do phase.monad [[bundle state] phase.state .let [eval (/////analysis/evaluation.evaluator expander - (value@ [/////directive.#synthesis /////directive.#state] state) - (value@ [/////directive.#generation /////directive.#state] state) - (value@ [/////directive.#generation /////directive.#phase] state)) - previous_analysis_extensions (value@ [/////directive.#analysis /////directive.#state ///.#bundle] state)]] + (the [/////directive.#synthesis /////directive.#state] state) + (the [/////directive.#generation /////directive.#state] state) + (the [/////directive.#generation /////directive.#phase] state)) + 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)))])) - state)]))) + (revised [/////directive.#analysis /////directive.#state] + (: (-> /////analysis.State+ /////analysis.State+) + (|>> product.right + [(|> previous_analysis_extensions + (dictionary.merged (///analysis.bundle eval host_analysis)))])) + state)]))) (def: (announce_definition! short type) (All (_ anchor expression directive) @@ -369,8 +369,8 @@ (function (_ extension_name phase archive [alias def_name]) (do phase.monad [_ (///.lifted - (phase.sub [(value@ [/////directive.#analysis /////directive.#state]) - (with@ [/////directive.#analysis /////directive.#state])] + (phase.sub [(the [/////directive.#analysis /////directive.#state]) + (has [/////directive.#analysis /////directive.#state])] (define_alias alias def_name)))] (in /////directive.no_requirements)))])) @@ -522,9 +522,9 @@ (^ (list programC)) (do phase.monad [state (///.lifted phase.state) - .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) - synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) - generate (value@ [/////directive.#generation /////directive.#phase] state)] + .let [analyse (the [/////directive.#analysis /////directive.#phase] state) + synthesize (the [/////directive.#synthesis /////directive.#phase] state) + generate (the [/////directive.#generation /////directive.#phase] state)] programS (prepare_program archive analyse synthesize programC) current_module (/////directive.lifted_analysis (///.lifted meta.current_module_name)) 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 0f063ea82..09ab89d42 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 @@ -1,39 +1,39 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [data - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix monoid)] - ["[0]" set]]] - [math - [number - ["n" nat]]] - [target - ["_" common_lisp {"+" Expression Var/1}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [data + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix monoid)] + ["[0]" set]]] + [math + [number + ["n" nat]]] + [target + ["_" common_lisp {"+" Expression Var/1}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register Var/1) @@ -248,7 +248,7 @@ pattern_matching! (pattern_matching $output expression archive pathP) .let [storage (|> pathP ////synthesis/case.storage - (value@ ////synthesis/case.#bindings) + (the ////synthesis/case.#bindings) set.list (list#each (function (_ register) [(..register register) 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 4a5ee59f0..c90729050 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 @@ -97,9 +97,9 @@ (do ///////phase.monad [valueO (expression archive valueS)] (in (list#mix (function (_ side source) - (.let [method (.if (value@ member.#right? side) - (//runtime.tuple//right (_.i32 (.int (value@ member.#lefts side)))) - (//runtime.tuple//left (_.i32 (.int (value@ member.#lefts side)))))] + (.let [method (.if (the member.#right? side) + (//runtime.tuple//right (_.i32 (.int (the member.#lefts side)))) + (//runtime.tuple//left (_.i32 (.int (the member.#lefts side)))))] (method source))) valueO (list.reversed pathP))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 325700c72..6504a5f55 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -300,9 +300,9 @@ (do phase.monad [record! (phase archive recordS)] (in (list#mix (function (_ step so_far!) - (.let [next! (.if (value@ member.#right? step) - (..right_projection (value@ member.#lefts step)) - (..left_projection (value@ member.#lefts step)))] + (.let [next! (.if (the member.#right? step) + (..right_projection (the member.#lefts step)) + (..left_projection (the member.#lefts step)))] ($_ _.composite so_far! next!))) 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 1ad5f6df6..7e879516a 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 @@ -83,9 +83,9 @@ (do ///////phase.monad [valueO (expression archive valueS)] (in (list#mix (function (_ side source) - (.let [method (.if (value@ member.#right? side) - (//runtime.tuple//right (_.int (.int (value@ member.#lefts side)))) - (//runtime.tuple//left (_.int (.int (value@ member.#lefts side)))))] + (.let [method (.if (the member.#right? side) + (//runtime.tuple//right (_.int (.int (the member.#lefts side)))) + (//runtime.tuple//left (_.int (.int (the member.#lefts side)))))] (method source))) valueO (list.reversed pathP))))) @@ -271,7 +271,7 @@ (def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage - (value@ ////synthesis/case.#dependencies) + (the ////synthesis/case.#dependencies) set.list (list#each (function (_ variable) (.case variable 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 d65c81d6a..54685bfff 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 @@ -1,38 +1,38 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [math - [number - ["i" int]]] - [target - ["_" php {"+" Expression Var Statement}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [math + [number + ["i" int]]] + [target + ["_" php {"+" Expression Var Statement}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register Var) @@ -260,7 +260,7 @@ (def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage - (value@ ////synthesis/case.#dependencies) + (the ////synthesis/case.#dependencies) set.list (list#each (function (_ variable) (.case variable 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 8b10f2833..bfb3ebdc8 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 @@ -110,10 +110,10 @@ (do ///////phase.monad [valueO (expression archive valueS)] (in (list#mix (function (_ side source) - (.let [method (.if (value@ member.#right? side) + (.let [method (.if (the member.#right? side) //runtime.tuple::right //runtime.tuple::left)] - (method (_.int (.int (value@ member.#lefts side))) + (method (_.int (.int (the member.#lefts side))) source))) valueO (list.reversed pathP))))) @@ -320,7 +320,7 @@ (def: .public dependencies (-> Path (List SVar)) (|>> case.storage - (value@ case.#dependencies) + (the case.#dependencies) set.list (list#each (function (_ variable) (.case variable 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 ec725005a..d4abe4b2b 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 @@ -111,9 +111,9 @@ (do ///////phase.monad [valueO (expression archive valueS)] (in (list#mix (function (_ side source) - (.let [method (.if (value@ member.#right? side) - (//runtime.tuple//right (_.int (.int (value@ member.#lefts side)))) - (//runtime.tuple//left (_.int (.int (value@ member.#lefts side)))))] + (.let [method (.if (the member.#right? side) + (//runtime.tuple//right (_.int (.int (the member.#lefts side)))) + (//runtime.tuple//left (_.int (.int (the member.#lefts side)))))] (method source))) valueO (list.reversed pathP))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index d711e963a..ae74e45f3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -62,8 +62,8 @@ (case structure {///complex.#Variant variant} (do phase.monad - [valueS (optimization' (value@ ///complex.#value variant))] - (in (/.variant (with@ ///complex.#value valueS variant)))) + [valueS (optimization' (the ///complex.#value variant))] + (in (/.variant (has ///complex.#value valueS variant)))) {///complex.#Tuple tuple} (|> tuple diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index ebab6fe8a..1bf6357f7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -371,8 +371,8 @@ path_storage (^ (/.path/bind register)) - (revised@ #bindings (set.has register) - path_storage) + (revised #bindings (set.has register) + path_storage) {/.#Bit_Fork _ default otherwise} (|> (case otherwise @@ -410,12 +410,12 @@ (list#mix for_synthesis synthesis_storage members) {/.#Reference {///reference.#Variable {///reference/variable.#Local register}}} - (if (set.member? (value@ #bindings synthesis_storage) register) + (if (set.member? (the #bindings synthesis_storage) register) synthesis_storage - (revised@ #dependencies (set.has {///reference/variable.#Local register}) synthesis_storage)) + (revised #dependencies (set.has {///reference/variable.#Local register}) synthesis_storage)) {/.#Reference {///reference.#Variable var}} - (revised@ #dependencies (set.has var) synthesis_storage) + (revised #dependencies (set.has var) synthesis_storage) (^ (/.function/apply [functionS argsS])) (list#mix for_synthesis synthesis_storage {.#Item functionS argsS}) @@ -424,20 +424,20 @@ (list#mix for_synthesis synthesis_storage environment) (^ (/.branch/case [inputS pathS])) - (revised@ #dependencies - (set.union (value@ #dependencies (for_path pathS synthesis_storage))) - (for_synthesis inputS synthesis_storage)) + (revised #dependencies + (set.union (the #dependencies (for_path pathS synthesis_storage))) + (for_synthesis inputS synthesis_storage)) (^ (/.branch/exec [before after])) (list#mix for_synthesis synthesis_storage (list before after)) (^ (/.branch/let [inputS register exprS])) - (revised@ #dependencies - (set.union (|> synthesis_storage - (revised@ #bindings (set.has register)) - (for_synthesis exprS) - (value@ #dependencies))) - (for_synthesis inputS synthesis_storage)) + (revised #dependencies + (set.union (|> synthesis_storage + (revised #bindings (set.has register)) + (for_synthesis exprS) + (the #dependencies))) + (for_synthesis inputS synthesis_storage)) (^ (/.branch/if [testS thenS elseS])) (list#mix for_synthesis synthesis_storage (list testS thenS elseS)) @@ -446,15 +446,15 @@ (for_synthesis whole synthesis_storage) (^ (/.loop/scope [start initsS+ iterationS])) - (revised@ #dependencies - (set.union (|> synthesis_storage - (revised@ #bindings (set.union (|> initsS+ - list.enumeration - (list#each (|>> product.left (n.+ start))) - (set.of_list n.hash)))) - (for_synthesis iterationS) - (value@ #dependencies))) - (list#mix for_synthesis synthesis_storage initsS+)) + (revised #dependencies + (set.union (|> synthesis_storage + (revised #bindings (set.union (|> initsS+ + list.enumeration + (list#each (|>> product.left (n.+ start))) + (set.of_list n.hash)))) + (for_synthesis iterationS) + (the #dependencies))) + (list#mix for_synthesis synthesis_storage initsS+)) (^ (/.loop/again replacementsS+)) (list#mix for_synthesis synthesis_storage replacementsS+) 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 8e37a6714..c08117adc 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 @@ -57,7 +57,7 @@ (with_expansions [<apply> (as_is (/.function/apply [funcS argsS]))] (case funcS (^ (/.function/abstraction functionS)) - (if (n.= (value@ /.#arity functionS) + (if (n.= (the /.#arity functionS) (list.size argsS)) (do ! [locals /.locals] @@ -279,7 +279,7 @@ (case (//loop.optimization false 1 (list) abstraction) {.#Some [startL initsL bodyL]} [/.#environment environment - /.#arity (value@ /.#arity abstraction) + /.#arity (the /.#arity abstraction) /.#body (/.loop/scope [startL initsL bodyL])] {.#None} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 75ddb63b0..f3d6b8b68 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -87,9 +87,9 @@ (case structure {analysis/complex.#Variant variant} (do maybe.monad - [value' (|> variant (value@ analysis/complex.#value) (again false))] + [value' (|> variant (the analysis/complex.#value) (again false))] (in (|> variant - (with@ analysis/complex.#value value') + (has analysis/complex.#value value') /.variant))) {analysis/complex.#Tuple tuple} @@ -148,10 +148,10 @@ (^ (/.loop/scope scope)) (do [! maybe.monad] [inits' (|> scope - (value@ /.#inits) + (the /.#inits) (monad.each ! (again false))) - iteration' (again return? (value@ /.#iteration scope))] - (in (/.loop/scope [/.#start (|> scope (value@ /.#start) (register_optimization offset)) + iteration' (again return? (the /.#iteration scope))] + (in (/.loop/scope [/.#start (|> scope (the /.#start) (register_optimization offset)) /.#inits inits' /.#iteration iteration']))) @@ -211,6 +211,6 @@ (def: .public (optimization true_loop? offset inits functionS) (-> Bit Register (List Synthesis) Abstraction (Maybe [Register (List Synthesis) Synthesis])) - (|> (value@ /.#body functionS) - (body_optimization true_loop? offset (value@ /.#environment functionS) (value@ /.#arity functionS)) + (|> (the /.#body functionS) + (body_optimization true_loop? offset (the /.#environment functionS) (the /.#arity functionS)) (maybe#each (|>> [offset inits])))) 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 1108cfbc4..0b1d000b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -205,7 +205,7 @@ (:expected <<otherwise>>))]) (template: (!horizontal where offset source_code) - [[(revised@ .#column ++ where) + [[(revised .#column ++ where) (!++ offset) source_code]]) @@ -264,7 +264,7 @@ (<| (let [g!content (!clip offset g!end source_code)]) (!guarantee_no_new_lines where offset source_code g!content) {.#Right [[(let [size (!n/- offset g!end)] - (revised@ .#column (|>> (!n/+ size) (!n/+ 2)) where)) + (revised .#column (|>> (!n/+ size) (!n/+ 2)) where)) (!++ g!end) source_code] [where @@ -410,7 +410,7 @@ (signed_parser source_code//size offset where (!++/2 offset) source_code) (!full_symbol_parser offset [where (!++ offset) source_code] where @aliases .#Symbol)))]) -(with_expansions [<output> {.#Right [[(revised@ .#column (|>> (!n/+ (!n/- start end))) where) +(with_expansions [<output> {.#Right [[(revised .#column (|>> (!n/+ (!n/- start end))) where) end source_code] (!clip start end source_code)]}] @@ -483,7 +483,7 @@ (def: (bit_syntax value [where offset/0 source_code]) (-> Bit (Parser Code)) - {.#Right [[(revised@ .#column (|>> !++/2) where) + {.#Right [[(revised .#column (|>> !++/2) where) (!++/2 offset/0) source_code] [where {.#Bit value}]]}) 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 819c44a5f..1d8b9e6d3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -203,11 +203,11 @@ (template [<with> <query> <tag> <type>] [(def: .public (<with> value) (-> <type> (All (_ a) (-> (Operation a) (Operation a)))) - (extension.temporary (with@ <tag> value))) + (extension.temporary (has <tag> value))) (def: .public <query> (Operation <type>) - (extension.read (value@ <tag>)))] + (extension.read (the <tag>)))] [with_locals locals #locals Nat] [with_currying? currying? #currying? Bit] @@ -383,12 +383,12 @@ {#Loop loop} (case loop {#Scope scope} - (|> (format (%.nat (value@ #start scope)) - " " (|> (value@ #inits scope) + (|> (format (%.nat (the #start scope)) + " " (|> (the #inits scope) (list#each %synthesis) (text.interposed " ") (text.enclosed ["[" "]"])) - " " (%synthesis (value@ #iteration scope))) + " " (%synthesis (the #iteration scope))) (text.enclosed ["{#loop " "}"])) {#Again args} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux index 4e1ed910b..e6c9fb680 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux @@ -20,7 +20,7 @@ (def: .public (format it) (%.Format Member) - (%.format "[" (%.nat (value@ #lefts it)) " " (%.bit (value@ #right? it)) "]")) + (%.format "[" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "]")) (def: .public hash (Hash Member) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux index dd9bf4223..045681ac2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux @@ -20,7 +20,7 @@ (def: .public (format it) (%.Format Side) - (%.format "{" (%.nat (value@ #lefts it)) " " (%.bit (value@ #right? it)) "}")) + (%.format "{" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "}")) (def: .public hash (Hash Side) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 4ec08ed90..a63bde0a1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Module} + [lux {"-" Module has} [abstract ["[0]" equivalence {"+" Equivalence}] ["[0]" monad {"+" do}]] @@ -79,7 +79,7 @@ (def: next (-> Archive module.ID) - (|>> :representation (value@ #next))) + (|>> :representation (the #next))) (def: .public empty Archive @@ -108,8 +108,8 @@ {try.#Success [/#next (|> archive :representation - (revised@ #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})])) - (revised@ #next ++) + (revised #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})])) + (revised #next ++) :abstraction)]}))) (def: .public (has module entry archive) @@ -119,15 +119,15 @@ {.#Some [id {.#None}]} {try.#Success (|> archive :representation - (revised@ ..#resolver (dictionary.has module [id {.#Some entry}])) + (revised ..#resolver (dictionary.has module [id {.#Some entry}])) :abstraction)} {.#Some [id {.#Some [existing_module existing_output existing_registry]}]} - (if (same? (value@ module.#document existing_module) - (value@ [#module module.#document] entry)) + (if (same? (the module.#document existing_module) + (the [#module module.#document] entry)) ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy... {try.#Success archive} - (exception.except ..cannot_replace_document [module (value@ module.#document existing_module) (value@ [#module module.#document] entry)])) + (exception.except ..cannot_replace_document [module (the module.#document existing_module) (the [#module module.#document] entry)])) {.#None} (exception.except ..module_must_be_reserved_before_it_can_be_added [module])))) @@ -135,7 +135,7 @@ (def: .public entries (-> Archive (List [descriptor.Module [module.ID (Entry Any)]])) (|>> :representation - (value@ #resolver) + (the #resolver) dictionary.entries (list.all (function (_ [module [module_id entry]]) (# maybe.monad each (|>> [module_id] [module]) entry))))) @@ -165,7 +165,7 @@ (def: .public archived (-> Archive (List descriptor.Module)) (|>> :representation - (value@ #resolver) + (the #resolver) dictionary.entries (list.all (function (_ [module [id descriptor+document]]) (case descriptor+document @@ -185,13 +185,13 @@ (def: .public reserved (-> Archive (List descriptor.Module)) (|>> :representation - (value@ #resolver) + (the #resolver) dictionary.keys)) (def: .public reservations (-> Archive (List [descriptor.Module module.ID])) (|>> :representation - (value@ #resolver) + (the #resolver) dictionary.entries (list#each (function (_ [module [id _]]) [module id])))) @@ -201,17 +201,17 @@ (let [[+next +resolver] (:representation additions)] (|> archive :representation - (revised@ #next (n.max +next)) - (revised@ #resolver (function (_ resolver) - (list#mix (function (_ [module [id entry]] resolver) - (case entry - {.#Some _} - (dictionary.has module [id entry] resolver) - - {.#None} - resolver)) - resolver - (dictionary.entries +resolver)))) + (revised #next (n.max +next)) + (revised #resolver (function (_ resolver) + (list#mix (function (_ [module [id entry]] resolver) + (case entry + {.#Some _} + (dictionary.has module [id entry] resolver) + + {.#None} + resolver)) + resolver + (dictionary.entries +resolver)))) :abstraction))) (type: Reservation @@ -262,6 +262,6 @@ [#next next #resolver (list#mix (function (_ [module id] archive) (dictionary.has module [id (: (Maybe (Entry Any)) {.#None})] archive)) - (value@ #resolver (:representation ..empty)) + (the #resolver (:representation ..empty)) reservations)])))) ) 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 144895928..9a97cc0ec 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 @@ -58,7 +58,7 @@ (def: .public signature (-> (Document Any) Signature) - (|>> :representation (value@ #signature))) + (|>> :representation (the #signature))) (def: .public (writer content) (All (_ d) (-> (Writer d) (Writer (Document d)))) 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 6489b6fb7..be3619845 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -39,7 +39,7 @@ (def: .public artifacts (-> Registry (Sequence [Artifact (Set unit.ID)])) - (|>> :representation (value@ #artifacts))) + (|>> :representation (the #artifacts))) (def: next (-> Registry ID) @@ -51,10 +51,10 @@ [id (|> registry :representation - (revised@ #artifacts (sequence.suffix [[//.#id id - //.#category {//category.#Anonymous} - //.#mandatory? mandatory?] - dependencies])) + (revised #artifacts (sequence.suffix [[//.#id id + //.#category {//category.#Anonymous} + //.#mandatory? mandatory?] + dependencies])) :abstraction)])) (template [<tag> <create> <fetch> <type> <name> <+resolver>] @@ -64,21 +64,21 @@ [id (|> registry :representation - (revised@ #artifacts (sequence.suffix [[//.#id id - //.#category {<tag> it} - //.#mandatory? mandatory?] - dependencies])) - (revised@ #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)])) + (revised #artifacts (sequence.suffix [[//.#id id + //.#category {<tag> it} + //.#mandatory? mandatory?] + dependencies])) + (revised #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)])) :abstraction)])) (def: .public (<fetch> registry) (-> Registry (List <type>)) (|> registry :representation - (value@ #artifacts) + (the #artifacts) sequence.list (list.all (|>> product.left - (value@ //.#category) + (the //.#category) (case> {<tag> it} {.#Some it} _ {.#None})))))] @@ -94,7 +94,7 @@ (def: .public (find_definition name registry) (-> Text Registry (Maybe [ID (Maybe //category.Definition)])) (|> (:representation registry) - (value@ #resolver) + (the #resolver) (dictionary.value name))) (def: .public (id name registry) @@ -134,10 +134,10 @@ artifacts (: (Writer (Sequence [Category Bit (Set unit.ID)])) (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))] (|>> :representation - (value@ #artifacts) + (the #artifacts) (sequence#each (function (_ [it dependencies]) - [(value@ //.#category it) - (value@ //.#mandatory? it) + [(the //.#category it) + (the //.#mandatory? it) dependencies])) artifacts))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux index 533ed6cb0..235913727 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux @@ -33,7 +33,7 @@ (def: .public (description signature) (-> Signature Text) - (format (%.symbol (value@ #name signature)) " " (version.format (value@ #version signature)))) + (format (%.symbol (the #name signature)) " " (version.format (the #version signature)))) (def: .public writer (Writer Signature) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux index ed2e00876..9412bbb0b 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux @@ -38,6 +38,6 @@ (def: .public (format it) (%.Format ID) - (%.format (%.nat (value@ #module it)) + (%.format (%.nat (the #module it)) "." - (%.nat (value@ #artifact it)))) + (%.nat (the #artifact it)))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache.lux b/stdlib/source/library/lux/tool/compiler/meta/cache.lux index 6b4194359..72470f228 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache.lux @@ -18,8 +18,8 @@ (def: .public (path fs context) (All (_ !) (-> (file.System !) Context file.Path)) (let [/ (# fs separator)] - (format (value@ context.#target context) - / (value@ context.#host context) + (format (the context.#target context) + / (the context.#host context) / (version.format //.version)))) (def: .public (enabled? fs context) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux index fd63495d1..ca2689c18 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux @@ -26,7 +26,7 @@ (format (//module.path fs context @module) (# fs separator) (%.nat @artifact) - (value@ context.#artifact_extension context))) + (the context.#artifact_extension context))) (def: .public (cache fs context @module @artifact) (All (_ !) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index 9bce830d6..f1c4a4806 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -83,7 +83,7 @@ (case value {analysis/complex.#Variant value} (|> value - (value@ analysis/complex.#value) + (the analysis/complex.#value) references) {analysis/complex.#Tuple value} @@ -131,7 +131,7 @@ (case value {synthesis.#Scope value} (|> value - (value@ synthesis.#iteration) + (the synthesis.#iteration) references) {synthesis.#Again value} @@ -143,7 +143,7 @@ (case value {synthesis.#Abstraction value} (|> value - (value@ synthesis.#body) + (the synthesis.#body) references) {synthesis.#Apply function arguments} @@ -193,8 +193,8 @@ registry.artifacts sequence.list (list#each (function (_ [artifact dependencies]) - [[module_id (value@ artifact.#id artifact)] - (value@ artifact.#mandatory? artifact) + [[module_id (the artifact.#id artifact)] + (the artifact.#mandatory? artifact) dependencies]))))) list.together (list#mix (function (_ [artifact_id mandatory? dependencies] 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 01c37431f..4fd7fdebf 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 @@ -59,7 +59,7 @@ (do [! state.monad] [.let [parents (case (archive.find module archive) {try.#Success [module output registry]} - (value@ [module.#descriptor descriptor.#references] module) + (the [module.#descriptor descriptor.#references] module) {try.#Failure error} ..fresh)] @@ -95,5 +95,5 @@ (do try.monad [module_id (archive.id module archive) entry (archive.find module archive) - document (document.marked? key (value@ [archive.#module module.#document] entry))] - (in [module [module_id (with@ [archive.#module module.#document] document entry)]]))))))) + document (document.marked? key (the [archive.#module module.#document] entry))] + (in [module [module_id (has [archive.#module module.#document] document entry)]]))))))) 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 c5f2f577a..e393253e1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux @@ -50,12 +50,12 @@ (def: .public (valid? expected actual) (-> Descriptor Input Bit) - (and (text#= (value@ descriptor.#name expected) - (value@ ////.#module actual)) - (text#= (value@ descriptor.#file expected) - (value@ ////.#file actual)) - (n.= (value@ descriptor.#hash expected) - (value@ ////.#hash actual)))) + (and (text#= (the descriptor.#name expected) + (the ////.#module actual)) + (text#= (the descriptor.#file expected) + (the ////.#file actual)) + (n.= (the descriptor.#hash expected) + (the ////.#hash actual)))) (def: initial (-> (List Cache) Purge) @@ -73,7 +73,7 @@ (if (purged? module_name) purge (if (|> entry - (value@ [archive.#module module.#descriptor descriptor.#references]) + (the [archive.#module module.#descriptor descriptor.#references]) set.list (list.any? purged?)) (dictionary.has module_name @module purge) 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 212006bbe..a807e083c 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -81,11 +81,11 @@ (do ! [entry (archive.find module archive) content (|> entry - (value@ [archive.#module module.#document]) + (the [archive.#module module.#document]) (document.content $.key))] (in [module content]))) (archive.archived archive)))] - (in (with@ .#modules modules (fresh_analysis_state host configuration))))) + (in (has .#modules modules (fresh_analysis_state host configuration))))) (type: Definitions (Dictionary Text Any)) (type: Analysers (Dictionary Text analysis.Handler)) @@ -240,8 +240,8 @@ try.of_maybe (# ! each (function (_ def_value) [def_name {.#Type [exported? (:as .Type def_value) labels]}]))))) - (value@ .#definitions content))] - (in [(document.document $.key (with@ .#definitions definitions content)) + (the .#definitions content))] + (in [(document.document $.key (has .#definitions definitions content)) bundles]))) (def: (load_definitions fs context @module host_environment entry) @@ -252,13 +252,13 @@ (do (try.with async.monad) [actual (: (Async (Try (Dictionary Text Binary))) (cache/module.artifacts async.monad fs context @module)) - .let [expected (registry.artifacts (value@ archive.#registry entry))] - [document bundles output] (|> (value@ [archive.#module module.#document] entry) - (loaded_document (value@ context.#artifact_extension context) host_environment @module expected actual) + .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) async#in)] (in [(|> entry - (with@ [archive.#module module.#document] document) - (with@ archive.#output output)) + (has [archive.#module module.#document] document) + (has archive.#output output)) bundles]))) (def: pseudo_module @@ -291,8 +291,8 @@ (if (text#= descriptor.runtime module_name) (in [true <cache>]) (do ! - [input (//context.read fs ..pseudo_module import contexts (value@ context.#host_module_extension context) module_name)] - (in [(cache/purge.valid? (value@ module.#descriptor module) input) <cache>])))))) + [input (//context.read fs ..pseudo_module import contexts (the context.#host_module_extension context) module_name)] + (in [(cache/purge.valid? (the module.#descriptor module) input) <cache>])))))) (def: (pre_loaded_caches customs fs context import contexts archive) (-> (List Custom) (file.System Async) Context Import (List //.Context) Archive @@ -354,7 +354,7 @@ (archive.has module entry archive)) archive loaded_caches) - analysis_state (..analysis_state (value@ context.#host context) configuration archive)] + analysis_state (..analysis_state (the context.#host context) configuration archive)] (in [archive analysis_state (list#mix (function (_ [_ [+analysers +synthesizers +generators +directives]] @@ -380,5 +380,5 @@ {try.#Failure error} (in {try.#Success [archive.empty - (fresh_analysis_state (value@ context.#host context) configuration) + (fresh_analysis_state (the context.#host context) configuration) ..empty_bundles]})))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux index 5b0bd0438..a92bdbbe1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux @@ -37,8 +37,8 @@ (-> (cache/module.Order Any) Order) (list#each (function (_ [module [module_id entry]]) (|> entry - (value@ archive.#registry) + (the archive.#registry) registry.artifacts sequence.list - (list#each (|>> product.left (value@ artifact.#id))) + (list#each (|>> product.left (the artifact.#id))) [module_id])))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index 99c9a316b..4e1c841b5 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -152,7 +152,7 @@ (maybe#each (|>> name.internal name.read)) (maybe.else (runtime.class_name [module artifact])) (text.replaced "." "/") - (text.suffix (value@ context.#artifact_extension static)))] + (text.suffix (the context.#artifact_extension static)))] (do try.monad [_ (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new class_path) sink)] (in (do_to sink @@ -266,7 +266,7 @@ .let [buffer (java/io/ByteArrayOutputStream::new (ffi.as_int (.int ..mebi_byte)))] sink (|> order (list#each (function (_ [module [module_id entry]]) - [module_id (value@ archive.#output entry)])) + [module_id (the archive.#output entry)])) (monad.mix ! (..write_module static necessary_dependencies) (java/util/jar/JarOutputStream::new buffer (..manifest program)))) [entries duplicates sink] (|> host_dependencies 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 85eb525cf..df7f11ce0 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux @@ -85,7 +85,7 @@ (Try (List [module.ID [Text Binary]]))) (do [! try.monad] [bundle (: (Try (Maybe _.Statement)) - (..bundle_module module module_id necessary_dependencies (value@ archive.#output entry)))] + (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))] (case bundle {.#None} (in sink) 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 f46a71e8e..f1dfb0189 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -1,48 +1,48 @@ (.using - [library - [lux {"-" Module} - [type {"+" :sharing}] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try {"+" Try}]] - [data - [binary {"+" Binary}] - ["[0]" product] - ["[0]" text - ["%" format {"+" format}] - ["[0]" encoding]] - [collection - ["[0]" sequence] - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" dictionary {"+" Dictionary}] - ["[0]" set]] - [format - ["[0]" tar] - ["[0]" binary]]] - [target - ["_" scheme]] - [time - ["[0]" instant {"+" Instant}]] - [world - ["[0]" file]]]] - [program - [compositor - ["[0]" static {"+" Static}]]] - ["[0]" // {"+" Packager} + [library + [lux {"-" Module} + [type {"+" :sharing}] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try {"+" Try}]] + [data + [binary {"+" Binary}] + ["[0]" product] + ["[0]" text + ["%" format {"+" format}] + ["[0]" encoding]] + [collection + ["[0]" sequence] + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" dictionary {"+" Dictionary}] + ["[0]" set]] + [format + ["[0]" tar] + ["[0]" binary]]] + [target + ["_" scheme]] + [time + ["[0]" instant {"+" Instant}]] + [world + ["[0]" file]]]] + [program + [compositor + ["[0]" static {"+" Static}]]] + ["[0]" // {"+" Packager} + [// + ["[0]" archive {"+" Output} + ["[0]" descriptor {"+" Module Descriptor}] + ["[0]" artifact] + ["[0]" document {"+" Document}]] + [cache + ["[0]" dependency]] + ["[0]" io "_" + ["[1]" archive]] [// - ["[0]" archive {"+" Output} - ["[0]" descriptor {"+" Module Descriptor}] - ["[0]" artifact] - ["[0]" document {"+" Document}]] - [cache - ["[0]" dependency]] - ["[0]" io "_" - ["[1]" archive]] - [// - [language - ["$" lux - [generation {"+" Context}]]]]]]) + [language + ["$" lux + [generation {"+" Context}]]]]]]) ... TODO: Delete ASAP (type: (Action ! a) @@ -104,7 +104,7 @@ (..bundle_module output)) entry_content (: (Try tar.Content) (|> descriptor - (value@ descriptor.#references) + (the descriptor.#references) set.list (list.all (function (_ module) (dictionary.value module mapping))) (list#each (|>> ..module_file _.string _.load_relative/1)) 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 f3cc4f7a0..1b867cd4f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -71,7 +71,7 @@ order (cache/module.load_order $.key archive)] (|> order (list#each (function (_ [module [module_id entry]]) - [module_id (value@ archive.#output entry)])) + [module_id (the archive.#output entry)])) (monad.mix ! (..write_module necessary_dependencies sequence) header) (# ! each (|>> scope code |