diff options
author | Eduardo Julian | 2021-08-13 04:18:57 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-08-13 04:18:57 -0400 |
commit | e53c1a090eb9cfac3cb23d10d981648d02518ed1 (patch) | |
tree | 6c92c186525b6e73032ebea68765b791bcc27516 /stdlib/source/library/lux/tool/compiler | |
parent | 17629d66062b88b040a2397032f6c08361a5f3a7 (diff) |
Made program: specify its bindings the same way as syntax:.
Diffstat (limited to '')
38 files changed, 96 insertions, 96 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 98d910b10..174058fab 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -189,8 +189,8 @@ _ (///directive.lift_synthesis (extension.with extender synthesizers)) _ (///directive.lift_generation - (extension.with extender (:assume generators))) - _ (extension.with extender (:assume directives))] + (extension.with extender (:expected generators))) + _ (extension.with extender (:expected directives))] (in []))) (///phase.result' state) (\ try.monad map product.left))) @@ -254,7 +254,7 @@ [[state phase_wrapper] (..phase_wrapper archive platform state)] (|> state (initialize_state (extender phase_wrapper) - (:assume (..complete_extensions host_directive_bundle phase_wrapper (:assume bundles))) + (:expected (..complete_extensions host_directive_bundle phase_wrapper (:expected bundles))) analysis_state) (try\map (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper))))))))]] (if (archive.archived? archive archive.runtime_module) @@ -318,7 +318,7 @@ (function (_ lens module) (|> dependence lens - (dictionary.get module) + (dictionary.value module) (maybe.else ..empty)))) transitive_depends_on (transitive_dependency (get@ #depends_on) import) transitive_depended_by (transitive_dependency (get@ #depended_by) module) @@ -340,7 +340,7 @@ [module transitive_depends_on] [import transitive_depended_by])) (update@ #depended_by - ((function.flip update_dependence) + ((function.flipped update_dependence) [module transitive_depends_on] [import transitive_depended_by]))))) @@ -350,7 +350,7 @@ (function (_ from relationship to) (let [targets (|> dependence relationship - (dictionary.get from) + (dictionary.value from) (maybe.else ..empty))] (set.member? targets to))))] (or (dependence? import (get@ #depends_on) module) @@ -400,7 +400,7 @@ initial (Var (Dictionary Module <Pending>)) - (:assume (stm.var (dictionary.empty text.hash)))) + (:expected (stm.var (dictionary.empty text.hash)))) dependence (: (Var Dependence) (stm.var ..independence))] (function (_ compile) @@ -413,7 +413,7 @@ (Async [<Return> (Maybe [<Context> archive.ID <Signal>])]) - (:assume + (:expected (stm.commit (do {! stm.monad} [dependence (if (text\= archive.runtime_module importer) @@ -434,7 +434,7 @@ #.None]) (do ! [@pending (stm.read pending)] - (case (dictionary.get module @pending) + (case (dictionary.value module @pending) (#.Some [return signal]) (in [return #.None]) @@ -512,7 +512,7 @@ not) current) modules))) - :assume)) + :expected)) state)))) (def: (set_current_module module state) @@ -532,7 +532,7 @@ context (///.Compiler <State+> .Module Any) - (:assume + (:expected ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list)))) compiler (..parallel context @@ -557,7 +557,7 @@ (-> <Context> (///.Compilation <State+> .Module Any) (Set Module) (Action [Archive <State+>])) - (:assume recur)) + (:expected recur)) ... TODO: Come up with a less hacky way to prevent duplicate imports. ... This currently assumes that all imports will be specified once in a single .module: form. ... This might not be the case in the future. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index d43a937b1..996272df7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -245,7 +245,7 @@ (do {! try.monad} [casesM (monad.fold ! (function (_ [tagA coverageA] casesSF') - (case (dictionary.get tagA casesSF') + (case (dictionary.value tagA casesSF') (#.Some coverageSF) (do ! [coverageM (merged coverageA coverageSF)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux index c0249441c..db51c3d77 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux @@ -128,7 +128,7 @@ (function (_ state) (|> state (get@ #.modules) - (plist.get module) + (plist.value module) (case> (#.Some _) #1 #.None #0) [state] #try.Success)))) @@ -139,7 +139,7 @@ [self_name meta.current_module_name self meta.current_module] (function (_ state) - (case (plist.get name (get@ #.definitions self)) + (case (plist.value name (get@ #.definitions self)) #.None (#try.Success [(update@ #.modules (plist.has self_name @@ -176,7 +176,7 @@ (-> Text (Operation Any)) (///extension.lift (function (_ state) - (case (|> state (get@ #.modules) (plist.get module_name)) + (case (|> state (get@ #.modules) (plist.value module_name)) (#.Some module) (let [active? (case (get@ #.module_state module) #.Active #1 @@ -196,7 +196,7 @@ (-> Text (Operation Bit)) (///extension.lift (function (_ state) - (case (|> state (get@ #.modules) (plist.get module_name)) + (case (|> state (get@ #.modules) (plist.value module_name)) (#.Some module) (#try.Success [state (case (get@ #.module_state module) @@ -216,7 +216,7 @@ (-> Text (Operation <type>)) (///extension.lift (function (_ state) - (case (|> state (get@ #.modules) (plist.get module_name)) + (case (|> state (get@ #.modules) (plist.value module_name)) (#.Some module) (#try.Success [state (get@ <tag> module)]) @@ -234,7 +234,7 @@ [bindings (..tags module_name) _ (monad.map ! (function (_ tag) - (case (plist.get tag bindings) + (case (plist.value tag bindings) #.None (in []) @@ -258,7 +258,7 @@ (text\= self_name type_module))] (///extension.lift (function (_ state) - (case (|> state (get@ #.modules) (plist.get self_name)) + (case (|> state (get@ #.modules) (plist.value self_name)) (#.Some module) (let [namespaced_tags (list\map (|>> [self_name]) tags)] (#try.Success [(update@ #.modules diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux index f379a9692..ae6034b65 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux @@ -36,7 +36,7 @@ (-> Text Scope (Maybe [Type Variable])) (|> scope (get@ [#.locals #.mappings]) - (plist.get name) + (plist.value name) (maybe\map (function (_ [type value]) [type (#variable.Local value)])))) @@ -79,7 +79,7 @@ (function (_ state) (let [[inner outer] (|> state (get@ #.scopes) - (list.split_with (|>> (reference? name) not)))] + (list.split_when (|>> (reference? name) not)))] (case outer #.End (#.Right [state #.None]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index e123fab83..8f254c5d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -320,7 +320,7 @@ (function (_ [key val] idx->val) (do ! [key (///extension.lift (meta.normal key))] - (case (dictionary.get key tag->idx) + (case (dictionary.value key tag->idx) (#.Some idx) (if (dictionary.key? idx->val idx) (/.except ..cannot_repeat_tag [key record]) @@ -331,7 +331,7 @@ (: (Dictionary Nat Code) (dictionary.empty n.hash)) record) - .let [ordered_tuple (list\map (function (_ idx) (maybe.assume (dictionary.get idx idx->val))) + .let [ordered_tuple (list\map (function (_ idx) (maybe.assume (dictionary.value idx idx->val))) tuple_range)]] (in [ordered_tuple recordT])) )) 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 bfb776fcd..354f40fd2 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 @@ -90,7 +90,7 @@ (All [s i o] (-> (Extender s i o) Text (Handler s i o) (Operation s i o Any))) (function (_ [bundle state]) - (case (dictionary.get name bundle) + (case (dictionary.value name bundle) #.None (#try.Success [[(dictionary.has name (extender handler) bundle) state] []]) @@ -112,7 +112,7 @@ (All [s i o] (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) (function (_ (^@ stateE [bundle state])) - (case (dictionary.get name bundle) + (case (dictionary.value name bundle) (#.Some handler) (((handler name phase) archive parameters) stateE) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 4ef27d1d8..4913607a6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -363,7 +363,7 @@ (phase\map jvm.array (jvm_type elemT)) (#.Primitive class parametersT) - (case (dictionary.get class ..boxes) + (case (dictionary.value class ..boxes) (#.Some [_ primitive_type]) (case parametersT #.End @@ -556,7 +556,7 @@ [jvm.char])) (text.starts_with? descriptor.array_prefix name) - (let [[_ unprefixed] (maybe.assume (text.split_with descriptor.array_prefix name))] + (let [[_ unprefixed] (maybe.assume (text.split_by descriptor.array_prefix name))] (\ phase.monad map jvm.array (check_jvm (#.Primitive unprefixed (list))))) @@ -604,7 +604,7 @@ (def: (check_return type) (-> .Type (Operation (Type Return))) - (if (is? .Any type) + (if (same? .Any type) (phase\in jvm.void) (check_jvm type))) @@ -1116,7 +1116,7 @@ (case (jvm_parser.var? actualJC) (#.Some name) (|> aliasing - (dictionary.get name) + (dictionary.value name) (maybe.else name) jvm.var) @@ -1146,7 +1146,7 @@ (case (jvm_parser.var? actualJC) (#.Some name) (|> aliasing - (dictionary.get name) + (dictionary.value name) (maybe.else name) jvm.var) 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 1cba80e10..04df2b765 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 @@ -335,7 +335,7 @@ handler <type> - (:assume handlerV))) + (:expected handlerV))) _ (/////directive.lift_generation (/////generation.log! (format <description> " " (%.text (:as Text name)))))] (in /////directive.no_requirements)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index b3b4be343..a79807c28 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -84,7 +84,7 @@ (template [<conversion> <name>] [(def: (<name> inputG) (Unary (Bytecode Any)) - (if (is? _.nop <conversion>) + (if (same? _.nop <conversion>) inputG ($_ _.compose inputG @@ -643,7 +643,7 @@ (function (_ extension_name generate archive [class field unboxed]) (do //////.monad [.let [$class (type.class class (list))]] - (case (dictionary.get unboxed ..primitives) + (case (dictionary.value unboxed ..primitives) (#.Some primitive) (in (_.getstatic $class field primitive)) @@ -660,7 +660,7 @@ (do //////.monad [valueG (generate archive valueS) .let [$class (type.class class (list))]] - (case (dictionary.get unboxed ..primitives) + (case (dictionary.value unboxed ..primitives) (#.Some primitive) (in ($_ _.compose valueG @@ -682,7 +682,7 @@ (do //////.monad [objectG (generate archive objectS) .let [$class (type.class class (list)) - getG (case (dictionary.get unboxed ..primitives) + getG (case (dictionary.value unboxed ..primitives) (#.Some primitive) (_.getfield $class field primitive) @@ -702,7 +702,7 @@ [valueG (generate archive valueS) objectG (generate archive objectS) .let [$class (type.class class (list)) - putG (case (dictionary.get unboxed ..primitives) + putG (case (dictionary.value unboxed ..primitives) (#.Some primitive) (_.putfield $class field primitive) @@ -888,7 +888,7 @@ (^ (//////synthesis.variable var)) (|> mapping - (dictionary.get var) + (dictionary.value var) (maybe.else var) //////synthesis.variable) @@ -915,7 +915,7 @@ (case local (^ (//////synthesis.variable local)) (|> mapping - (dictionary.get local) + (dictionary.value local) (maybe.else local) //////synthesis.variable) @@ -1039,7 +1039,7 @@ (list\map (function (_ [foreign_id capture]) [(#//////variable.Foreign foreign_id) (|> global_mapping - (dictionary.get capture) + (dictionary.value capture) maybe.assume)])) (dictionary.from_list //////variable.hash))] [ownerT name diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index db25d1d70..0e0c91e60 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -71,7 +71,7 @@ (in [(|> chars (list\map (|>> .int _.int (_.= @input))) (list\fold (function (_ clause total) - (if (is? _.nil total) + (if (same? _.nil total) clause (_.or clause total))) _.nil)) @@ -123,7 +123,7 @@ (/.install "-" (binary (product.uncurried _.-))) (/.install "*" (binary (product.uncurried _.*))) (/.install "/" (binary (product.uncurried _./))) - (/.install "%" (binary (product.uncurried (function.flip (_.apply/2 (_.var "math.fmod")))))) + (/.install "%" (binary (product.uncurried (function.flipped (_.apply/2 (_.var "math.fmod")))))) (/.install "=" (binary (product.uncurried _.=))) (/.install "<" (binary (product.uncurried _.<))) (/.install "i64" (unary (!unary "math.floor"))) @@ -148,7 +148,7 @@ (|> /.empty (/.install "=" (binary (product.uncurried _.=))) (/.install "<" (binary (product.uncurried _.<))) - (/.install "concat" (binary (product.uncurried (function.flip _.concat)))) + (/.install "concat" (binary (product.uncurried (function.flipped _.concat)))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary //runtime.text//size)) ... TODO: Use version below once the Lua compiler becomes self-hosted. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index c4059fc35..45d6873da 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -75,7 +75,7 @@ (in [(|> chars (list\map (|>> .int _.int (_.=== @input))) (list\fold (function (_ clause total) - (if (is? _.null total) + (if (same? _.null total) clause (_.or clause total))) _.null)) @@ -167,7 +167,7 @@ (|> /.empty (/.install "=" (binary (product.uncurried _.==))) (/.install "<" (binary (product.uncurried _.<))) - (/.install "concat" (binary (product.uncurried (function.flip _.concat)))) + (/.install "concat" (binary (product.uncurried (function.flipped _.concat)))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary //runtime.text//size)) (/.install "char" (binary (product.uncurried //runtime.text//char))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index 5b9eba41e..f683c9b9a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -69,7 +69,7 @@ (in [(|> chars (list\map (|>> .int _.int (_.= @input))) (list\fold (function (_ clause total) - (if (is? _.none total) + (if (same? _.none total) clause (_.or clause total))) _.none)) @@ -146,7 +146,7 @@ (|> /.empty (/.install "=" (binary (product.uncurried _.=))) (/.install "<" (binary (product.uncurried _.<))) - (/.install "concat" (binary (product.uncurried (function.flip _.+)))) + (/.install "concat" (binary (product.uncurried (function.flipped _.+)))) (/.install "index" (trinary ..text::index)) (/.install "size" (unary _.len/1)) (/.install "char" (binary (product.uncurried //runtime.text::char))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index 651f7a62d..db479ccd3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -68,7 +68,7 @@ (in [(|> chars (list\map (|>> .int _.int (_.= @input))) (list\fold (function (_ clause total) - (if (is? _.nil total) + (if (same? _.nil total) clause (_.or clause total))) _.nil)) @@ -151,7 +151,7 @@ (|> /.empty (/.install "=" (binary (product.uncurried _.=))) (/.install "<" (binary (product.uncurried _.<))) - (/.install "concat" (binary (product.uncurried (function.flip _.+)))) + (/.install "concat" (binary (product.uncurried (function.flipped _.+)))) (/.install "index" (trinary text//index)) (/.install "size" (unary (_.the "length"))) (/.install "char" (binary (product.uncurried //runtime.text//char))) 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 624915eed..7bc4f46df 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 @@ -37,11 +37,11 @@ (def: .public register (-> Register Var/1) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register Var/1) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index ce6b2bdc6..917ab8503 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -38,7 +38,7 @@ (def: capture (-> Register Var/1) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure inits function_definition) (-> (List (Expression Any)) (Expression Any) (Operation (Expression Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index 12bce545f..b89ca3c5a 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 @@ -34,7 +34,7 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index 75b54ebe7..cccb72dd5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -36,7 +36,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure @self inits body!) (-> Var (List Expression) Statement [Statement Expression]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index 589d9191d..d21adc3ef 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 @@ -32,11 +32,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index 83db2505d..65930fb75 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -38,7 +38,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure inits @self @args body!) (-> (List Expression) Var (List Var) Statement [Statement Expression]) 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 bfc75d6ca..04cce603a 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 @@ -36,11 +36,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux index f8746bdf2..5cc25a622 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux @@ -38,7 +38,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: input (|>> inc //case.register)) 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 b00d65682..df2a1a3fc 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 @@ -41,11 +41,11 @@ (def: .public register (-> Register SVar) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux index 0304e7a58..b1ce3f5c8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux @@ -40,7 +40,7 @@ (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure function_id @function inits function_definition) (-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux index 87cae6c43..cd41e5f3d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux @@ -38,11 +38,11 @@ (def: .public register (-> Register SVar) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index dbdb0b1d0..fa95d1ba3 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 @@ -42,11 +42,11 @@ (def: .public register (-> Register LVar) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register LVar) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index dc39ac6f7..b64895b0e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -40,7 +40,7 @@ (def: .public capture (-> Register LVar) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure inits self function_definition) (-> (List Expression) Text Expression [Statement Expression]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index b09071726..70dfee409 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -38,11 +38,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :assume)) + (|>> (///reference.local //reference.system) :expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index d52f5d920..a36feb036 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -38,7 +38,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :assume)) + (|>> (///reference.foreign //reference.system) :expected)) (def: (with_closure inits function_definition) (-> (List Expression) Computation (Operation Computation)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 29ee68fac..78dc5dce1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -219,7 +219,7 @@ (def: (declare register redundancy) (-> Register Redundancy (Try Redundancy)) - (case (dictionary.get register redundancy) + (case (dictionary.value register redundancy) #.None (#try.Success (dictionary.has register ..redundant! redundancy)) @@ -228,7 +228,7 @@ (def: (observe register redundancy) (-> Register Redundancy (Try Redundancy)) - (case (dictionary.get register redundancy) + (case (dictionary.value register redundancy) #.None (exception.except ..unknown_register [register]) @@ -368,7 +368,7 @@ redundancy (..declare register redundancy) [redundancy output] (optimization' [redundancy output]) .let [redundant? (|> redundancy - (dictionary.get register) + (dictionary.value register) (maybe.else ..necessary!))]] (in [(dictionary.lacks register redundancy) (#/.Control (if redundant? 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 6db98721b..15539ae10 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -195,7 +195,7 @@ ... (#.Left error) <<otherwise>> - (:assume <<otherwise>>))]) + (:expected <<otherwise>>))]) (template: (!horizontal where offset source_code) [[(update@ #.column inc where) @@ -228,7 +228,7 @@ (recur source' (#.Item top stack)) (#.Left [source' error]) - (if (is? <close> error) + (if (same? <close> error) (#.Right [source' [where (<tag> (list.reversed stack))]]) (#.Left [source' error])))))] @@ -251,7 +251,7 @@ (recur sourceFV (#.Item [field value] stack))) (#.Left [source' error]) - (if (is? ..close_record error) + (if (same? ..close_record error) (#.Right [source' [where (#.Record (list.reversed stack))]]) (#.Left [source' error]))))) @@ -368,7 +368,7 @@ (recur (!inc end) exponent) [["e" "E"] - (if (is? (static ..no_exponent) exponent) + (if (same? (static ..no_exponent) exponent) (<| (!with_char+ source_code//size source_code (!inc end) char/1 <failure>) (`` ("lux syntax char case!" char/1 [[<signs>] @@ -468,7 +468,7 @@ (let [[where offset source_code] source] (!failure ..full_name_parser where offset source_code)) (#.Right [source'' [(|> aliases - (dictionary.get simple) + (dictionary.value simple) (maybe.else simple)) complex]]))) <simple>))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 1d605c120..06a2d5ca8 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -92,7 +92,7 @@ (def: .public (id module archive) (-> Module Archive (Try ID)) (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.get module resolver) + (case (dictionary.value module resolver) (#.Some [id _]) (#try.Success id) @@ -103,7 +103,7 @@ (def: .public (reserve module archive) (-> Module Archive (Try [ID Archive])) (let [(^slots [#..next #..resolver]) (:representation archive)] - (case (dictionary.get module resolver) + (case (dictionary.value module resolver) (#.Some _) (exception.except ..module_has_already_been_reserved [module]) @@ -118,7 +118,7 @@ (def: .public (has module [descriptor document output] archive) (-> Module [Descriptor (Document Any) Output] Archive (Try Archive)) (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.get module resolver) + (case (dictionary.value module resolver) (#.Some [id #.None]) (#try.Success (|> archive :representation @@ -126,7 +126,7 @@ :abstraction)) (#.Some [id (#.Some [existing_descriptor existing_document existing_output])]) - (if (is? document existing_document) + (if (same? document existing_document) ... 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 existing_document document])) @@ -137,7 +137,7 @@ (def: .public (find module archive) (-> Module Archive (Try [Descriptor (Document Any) Output])) (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.get module resolver) + (case (dictionary.value module resolver) (#.Some [id (#.Some entry)]) (#try.Success entry) @@ -170,7 +170,7 @@ (def: .public (reserved? archive module) (-> Archive Module Bit) (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.get module resolver) + (case (dictionary.value module resolver) (#.Some [id _]) bit.yes diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux index e4240e404..de1858b97 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -100,7 +100,7 @@ (-> Text Registry (Maybe ID)) (|> (:representation registry) (get@ #resolver) - (dictionary.get name))) + (dictionary.value name))) (def: .public writer (Writer Registry) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index d9f12d482..30777c282 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -42,7 +42,7 @@ key e - (:assume document//content))) + (:expected document//content))) (exception.except ..invalid_signature [(key.signature key) document//signature])))) @@ -55,7 +55,7 @@ (All [d] (-> (Key d) (Document Any) (Try (Document d)))) (do try.monad [_ (..read key document)] - (in (:assume document)))) + (in (:expected document)))) (def: .public signature (-> (Document Any) Signature) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux index fc6c26067..2df8c36ec 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -75,7 +75,7 @@ (def: (dependency? ancestry target source) (-> Graph Module Module Bit) (let [target_ancestry (|> ancestry - (dictionary.get target) + (dictionary.value target) (maybe.else ..fresh))] (set.member? target_ancestry source))) 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 a1f263f05..c5483ac0c 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -225,7 +225,7 @@ (case input (#.Item [[artifact_id artifact_category] input']) (case (do ! - [data (try.of_maybe (dictionary.get (format (%.nat artifact_id) extension) actual)) + [data (try.of_maybe (dictionary.value (format (%.nat artifact_id) extension) actual)) .let [context [module_id artifact_id] directive (\ host ingest context data)]] (case artifact_category @@ -328,7 +328,7 @@ (#.Definition [exported? type annotations _]) (|> definitions - (dictionary.get def_name) + (dictionary.value def_name) try.of_maybe (\ ! map (|>> [exported? type annotations] #.Definition diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index e65ede1eb..3e797c325 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -93,13 +93,13 @@ (def: (find_library_source_file importer import partial_host_extension module) (-> Module Import Extension Module (Try [file.Path Binary])) (let [path (format module (..full_host_extension partial_host_extension))] - (case (dictionary.get path import) + (case (dictionary.value path import) (#.Some data) (#try.Success [path data]) #.None (let [path (format module ..lux_extension)] - (case (dictionary.get path import) + (case (dictionary.value path import) (#.Some data) (#try.Success [path data]) 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 42a1a378c..90d28197a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -63,7 +63,7 @@ (|> content (\ encoding.utf8 decode) (\ try.monad map - (|>> :assume + (|>> :expected (:sharing [directive] directive so_far @@ -106,7 +106,7 @@ (|> descriptor (get@ #descriptor.references) set.list - (list.all (function (_ module) (dictionary.get module mapping))) + (list.all (function (_ module) (dictionary.value module mapping))) (list\map (|>> ..module_file _.string _.load_relative/1)) (list\fold ..then bundle) (: _.Expression) 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 28f8a3f28..fd6437557 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -45,7 +45,7 @@ (|> content (\ utf8.codec decode) (\ try.monad map - (|>> :assume + (|>> :expected (:sharing [directive] directive so_far |