diff options
author | Eduardo Julian | 2021-08-12 03:12:42 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-08-12 03:12:42 -0400 |
commit | 17629d66062b88b040a2397032f6c08361a5f3a7 (patch) | |
tree | bdc6110750b895667b9e45da5e46bec9609f9a7c /stdlib/source/library/lux/tool/compiler | |
parent | a62ce3f9c2b605e0033f4772b0f64c4525de4d86 (diff) |
Improved binding syntax for "syntax:".
Diffstat (limited to '')
30 files changed, 149 insertions, 140 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index e5ed96552..98d910b10 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -154,10 +154,10 @@ (..compile_runtime! platform)) .let [[descriptor document] [(..runtime_descriptor registry) ..runtime_document]] archive (///phase.lift (if (archive.reserved? archive archive.runtime_module) - (archive.add archive.runtime_module [descriptor document payload] archive) + (archive.has archive.runtime_module [descriptor document payload] archive) (do try.monad [[_ archive] (archive.reserve archive.runtime_module archive)] - (archive.add archive.runtime_module [descriptor document payload] archive))))] + (archive.has archive.runtime_module [descriptor document payload] archive))))] (in [archive [descriptor document payload]]))) (def: (initialize_state extender @@ -328,10 +328,10 @@ (function (_ mapping) (let [with_dependence+transitives (|> mapping - (dictionary.upsert source ..empty (set.add target)) - (dictionary.update source (set.union forward)))] + (dictionary.upsert source ..empty (set.has target)) + (dictionary.revised source (set.union forward)))] (list\fold (function (_ previous) - (dictionary.upsert previous ..empty (set.add target))) + (dictionary.upsert previous ..empty (set.has target))) with_dependence+transitives (set.list backward))))))] (|> dependence @@ -454,7 +454,7 @@ <Pending> (async.async []))] - _ (stm.update (dictionary.put module [return signal]) pending)] + _ (stm.update (dictionary.has module [return signal]) pending)] (in [return (#.Some [[archive state] module_id @@ -566,10 +566,10 @@ (if (set.member? all new) (if (text\= .prelude_module new) (if seen_prelude? - [all (set.add new duplicates) seen_prelude?] + [all (set.has new duplicates) seen_prelude?] [all duplicates true]) - [all (set.add new duplicates) seen_prelude?]) - [(set.add new all) duplicates seen_prelude?])) + [all (set.has new duplicates) seen_prelude?]) + [(set.has new all) duplicates seen_prelude?])) (: [(Set Module) (Set Module) Bit] [all_dependencies ..empty (set.empty? all_dependencies)]) new_dependencies))] @@ -607,7 +607,7 @@ [.let [_ (debug.log! (..module_compilation_log module state)) descriptor (set@ #descriptor.references all_dependencies descriptor)] _ (..cache_module static platform module_id [descriptor document output])] - (case (archive.add module [descriptor document output] archive) + (case (archive.has module [descriptor document output] archive) (#try.Success archive) (in [archive (..with_reset_log state)]) 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 5a47352b4..d43a937b1 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 @@ -152,7 +152,7 @@ (#.Some idx) #.None) (|> (dictionary.empty n.hash) - (dictionary.put idx value_coverage))))))) + (dictionary.has idx value_coverage))))))) (def: (xor left right) (-> Bit Bit Bit) @@ -249,10 +249,10 @@ (#.Some coverageSF) (do ! [coverageM (merged coverageA coverageSF)] - (in (dictionary.put tagA coverageM casesSF'))) + (in (dictionary.has tagA coverageM casesSF'))) #.None - (in (dictionary.put tagA coverageA casesSF')))) + (in (dictionary.has tagA coverageA casesSF')))) casesSF (dictionary.entries casesA))] (in (if (and (or (known_cases? addition_cases) (known_cases? so_far_cases)) 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 4bdb708bd..c0249441c 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 @@ -88,7 +88,7 @@ #.None (function (_ state) (#try.Success [(update@ #.modules - (plist.put self_name (set@ #.module_annotations (#.Some annotations) self)) + (plist.has self_name (set@ #.module_annotations (#.Some annotations) self)) state) []])) @@ -102,11 +102,11 @@ [self_name meta.current_module_name] (function (_ state) (#try.Success [(update@ #.modules - (plist.update self_name (update@ #.imports (function (_ current) - (if (list.any? (text\= module) - current) - current - (#.Item module current))))) + (plist.revised self_name (update@ #.imports (function (_ current) + (if (list.any? (text\= module) + current) + current + (#.Item module current))))) state) []]))))) @@ -117,8 +117,8 @@ [self_name meta.current_module_name] (function (_ state) (#try.Success [(update@ #.modules - (plist.update self_name (update@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text])) - (|>> (#.Item [alias module]))))) + (plist.revised self_name (update@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text])) + (|>> (#.Item [alias module]))))) state) []]))))) @@ -142,7 +142,7 @@ (case (plist.get name (get@ #.definitions self)) #.None (#try.Success [(update@ #.modules - (plist.put self_name + (plist.has self_name (update@ #.definitions (: (-> (List [Text Global]) (List [Text Global])) (|>> (#.Item [name definition]))) @@ -158,7 +158,7 @@ (///extension.lift (function (_ state) (#try.Success [(update@ #.modules - (plist.put name (..empty hash)) + (plist.has name (..empty hash)) state) []])))) @@ -183,7 +183,7 @@ _ #0)] (if active? (#try.Success [(update@ #.modules - (plist.put module_name (set@ #.module_state <tag> module)) + (plist.has module_name (set@ #.module_state <tag> module)) state) []]) ((/.except' can_only_change_state_of_active_module [module_name <tag>]) @@ -262,13 +262,13 @@ (#.Some module) (let [namespaced_tags (list\map (|>> [self_name]) tags)] (#try.Success [(update@ #.modules - (plist.update self_name - (|>> (update@ #.tags (function (_ tag_bindings) - (list\fold (function (_ [idx tag] table) - (plist.put tag [idx namespaced_tags exported? type] table)) - tag_bindings - (list.enumeration tags)))) - (update@ #.types (plist.put type_name [namespaced_tags exported? type])))) + (plist.revised self_name + (|>> (update@ #.tags (function (_ tag_bindings) + (list\fold (function (_ [idx tag] table) + (plist.has tag [idx namespaced_tags exported? type] table)) + tag_bindings + (list.enumeration tags)))) + (update@ #.types (plist.has type_name [namespaced_tags exported? type])))) state) []])) #.None 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 351c396e0..f379a9692 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 @@ -93,7 +93,7 @@ (#.Item (update@ #.captured (: (-> Foreign Foreign) (|>> (update@ #.counter inc) - (update@ #.mappings (plist.put name [ref_type (product.left ref+inner)])))) + (update@ #.mappings (plist.has name [ref_type (product.left ref+inner)])))) scope) (product.right ref+inner))])) [init_ref #.End] @@ -116,7 +116,7 @@ new_head (update@ #.locals (: (-> Local Local) (|>> (update@ #.counter inc) - (update@ #.mappings (plist.put name [type new_var_id])))) + (update@ #.mappings (plist.has name [type new_var_id])))) head)] (case (///.result' [bundle (set@ #.scopes (#.Item new_head tail) state)] action) 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 f5f5d89c8..e123fab83 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 @@ -324,7 +324,7 @@ (#.Some idx) (if (dictionary.key? idx->val idx) (/.except ..cannot_repeat_tag [key record]) - (in (dictionary.put idx val idx->val))) + (in (dictionary.has idx val idx->val))) #.None (/.except ..tag_does_not_belong_to_record [key 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 3142451e4..bfb776fcd 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 @@ -92,7 +92,7 @@ (function (_ [bundle state]) (case (dictionary.get name bundle) #.None - (#try.Success [[(dictionary.put name (extender handler) bundle) state] + (#try.Success [[(dictionary.has name (extender handler) bundle) state] []]) _ 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 27ce292a0..4ef27d1d8 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 @@ -1933,7 +1933,7 @@ (in [var exT]))) vars)] (in (list\fold (function (_ [varJ varT] mapping) - (dictionary.put (jvm_parser.name varJ) varT mapping)) + (dictionary.has (jvm_parser.name varJ) varT mapping)) mapping pairings)))) @@ -1942,7 +1942,7 @@ (do phase.monad [override_mapping (..override_mapping mapping supers parent_type)] (in (list\fold (function (_ [super_var bound_type] mapping) - (dictionary.put super_var bound_type mapping)) + (dictionary.has super_var bound_type mapping)) mapping override_mapping)))) @@ -2071,7 +2071,7 @@ (list\fold (function (_ [expected actual] mapping) (case (jvm_parser.var? actual) (#.Some actual) - (dictionary.put actual expected mapping) + (dictionary.has actual expected mapping) #.None mapping)) @@ -2128,7 +2128,7 @@ parameters (typeA.with_env (..parameter_types parameters)) .let [mapping (list\fold (function (_ [parameterJ parameterT] mapping) - (dictionary.put (jvm_parser.name parameterJ) + (dictionary.has (jvm_parser.name parameterJ) parameterT mapping)) luxT.fresh diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux index a6ce28fc1..3e6c7a0ef 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux @@ -19,7 +19,7 @@ (All [s i o] (-> Text (Handler s i o) (-> (Bundle s i o) (Bundle s i o)))) - (dictionary.put name anonymous)) + (dictionary.has name anonymous)) (def: .public (prefix prefix) (All [s i o] 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 505ae3bd3..04e197099 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 @@ -264,7 +264,7 @@ (typeA.with_env (jvm.parameter_types parameters))) .let [mapping (list\fold (function (_ [parameterJ parameterT] mapping) - (dictionary.put (parser.name parameterJ) parameterT mapping)) + (dictionary.has (parser.name parameterJ) parameterT mapping)) luxT.fresh parameters)] super_classT (directive.lift_analysis @@ -303,5 +303,5 @@ (<| (bundle.prefix "jvm") (|> bundle.empty ... TODO: Finish handling methods and un-comment. - ... (dictionary.put "class" jvm::class) + ... (dictionary.has "class" jvm::class) ))) 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 6e3ca3a70..1cba80e10 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 @@ -429,14 +429,14 @@ (Bundle anchor expression directive))) (<| (///bundle.prefix "def") (|> ///bundle.empty - (dictionary.put "module" def::module) - (dictionary.put "alias" def::alias) - (dictionary.put "type tagged" (def::type_tagged expander host_analysis)) - (dictionary.put "analysis" (def::analysis anchorT,expressionT,directiveT extender)) - (dictionary.put "synthesis" (def::synthesis anchorT,expressionT,directiveT extender)) - (dictionary.put "generation" (def::generation anchorT,expressionT,directiveT extender)) - (dictionary.put "directive" (def::directive anchorT,expressionT,directiveT extender)) - (dictionary.put "program" (def::program program)) + (dictionary.has "module" def::module) + (dictionary.has "alias" def::alias) + (dictionary.has "type tagged" (def::type_tagged expander host_analysis)) + (dictionary.has "analysis" (def::analysis anchorT,expressionT,directiveT extender)) + (dictionary.has "synthesis" (def::synthesis anchorT,expressionT,directiveT extender)) + (dictionary.has "generation" (def::generation anchorT,expressionT,directiveT extender)) + (dictionary.has "directive" (def::directive anchorT,expressionT,directiveT extender)) + (dictionary.has "program" (def::program program)) ))) (def: .public (bundle expander host_analysis program anchorT,expressionT,directiveT extender) @@ -449,5 +449,5 @@ (Bundle anchor expression directive))) (<| (///bundle.prefix "lux") (|> ///bundle.empty - (dictionary.put "def" (lux::def expander host_analysis)) + (dictionary.has "def" (lux::def expander host_analysis)) (dictionary.merged (..bundle::def expander host_analysis program anchorT,expressionT,directiveT extender))))) 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 957407cc8..c4059fc35 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 @@ -84,7 +84,7 @@ .let [foreigns (|> conditionals (list\map (|>> product.right synthesis.path/then //case.dependencies)) (list& (//case.dependencies (synthesis.path/then else))) - list.concat + list.joined (set.of_list _.hash) set.list) @expression (_.constant (reference.artifact [context_module context_artifact])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index 172a4d13c..db8c9b18e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -87,8 +87,8 @@ (-> (Expression Any) (Computation Any)) (|>> [1 #1] ..variant)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -96,13 +96,13 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index aeeb17528..b59e5ce37 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -21,7 +21,8 @@ [/// ["#" phase]]]]) -(syntax: (Vector {size s.nat} elemT) +(syntax: (Vector [size s.nat + elemT <code>.any]) (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public (Nullary of) (-> (Vector 0 of) of)) @@ -30,7 +31,9 @@ (type: .public (Trinary of) (-> (Vector 3 of) of)) (type: .public (Variadic of) (-> (List of) of)) -(syntax: (arity: {arity s.nat} {name s.local_identifier} type) +(syntax: (arity: [arity s.nat + name s.local_identifier + type <code>.any]) (with_identifiers [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive] (do {! meta.monad} [g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))] @@ -45,7 +48,7 @@ [(~+ (|> g!input+ (list\map (function (_ g!input) (list g!input (` ((~ g!phase) (~ g!archive) (~ g!input)))))) - list.concat))] + list.joined))] ((~' in) ((~ g!extension) [(~+ g!input+)]))) (~' _) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index 84e546a41..57916d38a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -85,8 +85,8 @@ (-> Var (-> Var Expression) Statement) (_.define name (definition name))) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -94,13 +94,13 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (macro.with_identifiers [g!_ runtime] (let [runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index 5ba5d0f5e..a1c3d7ca2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -102,8 +102,8 @@ (-> Var (-> Var Statement) Statement) (definition name)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -111,16 +111,16 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) (def: module_id 0) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 62238c960..6f69ba6e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -70,8 +70,8 @@ (-> Constant (-> Constant Statement) Statement) (definition name)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -79,16 +79,16 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) (def: module_id 0) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 360d33002..e26aca84a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -109,8 +109,8 @@ (-> SVar (-> SVar (Statement Any)) (Statement Any)) (definition name)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -118,13 +118,13 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (case declaration (#.Left name) (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 18de8ffef..e6134cb95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -34,7 +34,8 @@ (type: .public Bundle (Dict Text Proc)) -(syntax: (Vector {size s.nat} elemT) +(syntax: (Vector [{size s.nat} + elemT <code>.any]) (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public Nullary (-> (Vector +0 Expression) Expression)) @@ -47,7 +48,7 @@ (def: .public (install name unnamed) (-> Text (-> Text Proc) (-> Bundle Bundle)) - (dict.put name (unnamed name))) + (dict.has name (unnamed name))) (def: .public (prefix prefix bundle) (-> Text Bundle Bundle) @@ -62,7 +63,8 @@ "Expected: " (|> expected .int %i) "\n" " Actual: " (|> actual .int %i))) -(syntax: (arity: {name s.local_identifier} {arity s.nat}) +(syntax: (arity: [name s.local_identifier + arity s.nat]) (with_identifiers [g!_ g!proc g!name g!translate g!inputs] (do {@ macro.monad} [g!input+ (monad.seq @ (list.repeated arity (macro.identifier "input")))] @@ -77,7 +79,7 @@ [(~+ (|> g!input+ (list/map (function (_ g!input) (list g!input (` ((~ g!translate) (~ g!input)))))) - list.concat))] + list.joined))] ((~' in) ((~ g!proc) [(~+ g!input+)]))) (~' _) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 1bcb51d73..36e86df65 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -76,8 +76,8 @@ ... else (.int input))) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -85,13 +85,13 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 424d8b14b..1bcb1d528 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -71,8 +71,8 @@ (-> LVar (-> LVar Statement) Statement) (definition name)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -80,16 +80,16 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.local (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) (def: module_id 0) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index c6d6f4da8..c52ecd6dd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -6,7 +6,7 @@ [control ["ex" exception (#+ exception:)] [parser - ["s" code]]] + ["<.>" code]]] [data ["." product] ["." text] @@ -28,7 +28,8 @@ ["#/" // #_ ["#." synthesis (#+ Synthesis)]]]]) -(syntax: (Vector {size s.nat} elemT) +(syntax: (Vector [size <code>.nat + elemT <code>.any]) (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public Nullary (-> (Vector 0 Expression) Computation)) @@ -37,7 +38,8 @@ (type: .public Trinary (-> (Vector 3 Expression) Computation)) (type: .public Variadic (-> (List Expression) Computation)) -(syntax: (arity: {name s.local_identifier} {arity s.nat}) +(syntax: (arity: [name <code>.local_identifier + arity <code>.nat]) (with_identifiers [g!_ g!extension g!name g!phase g!inputs] (do {! macro.monad} [g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))] @@ -51,7 +53,7 @@ [(~+ (|> g!input+ (list\map (function (_ g!input) (list g!input (` ((~ g!phase) (~ g!input)))))) - list.concat))] + list.joined))] ((~' in) ((~ g!extension) [(~+ g!input+)]))) (~' _) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index f5f293f92..95dfef826 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -58,8 +58,8 @@ (def: .public unit (_.string /////synthesis.unit)) -(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} - body) +(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier)) + body <code>.any]) (do {! meta.monad} [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars @@ -67,13 +67,13 @@ (list\map (function (_ [id var]) (list (code.local_identifier var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) - list.concat))] + list.joined))] (~ body))))))) -(syntax: (runtime: {declaration (<>.or <code>.local_identifier +(syntax: (runtime: [declaration (<>.or <code>.local_identifier (<code>.form (<>.and <code>.local_identifier - (<>.some <code>.local_identifier))))} - code) + (<>.some <code>.local_identifier)))) + code <code>.any]) (do meta.monad [runtime_id meta.seed] (macro.with_identifiers [g!_] 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 875b2ca60..7f2666d8b 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 @@ -341,7 +341,7 @@ path_storage (^ (/.path/bind register)) - (update@ #bindings (set.add register) + (update@ #bindings (set.has register) path_storage) (#/.Bit_Fork _ default otherwise) @@ -378,10 +378,10 @@ (#/.Reference (#///reference.Variable (#///reference/variable.Local register))) (if (set.member? (get@ #bindings synthesis_storage) register) synthesis_storage - (update@ #dependencies (set.add (#///reference/variable.Local register)) synthesis_storage)) + (update@ #dependencies (set.has (#///reference/variable.Local register)) synthesis_storage)) (#/.Reference (#///reference.Variable var)) - (update@ #dependencies (set.add var) synthesis_storage) + (update@ #dependencies (set.has var) synthesis_storage) (^ (/.function/apply [functionS argsS])) (list\fold for_synthesis synthesis_storage (#.Item functionS argsS)) @@ -397,7 +397,7 @@ (^ (/.branch/let [inputS register exprS])) (update@ #dependencies (set.union (|> synthesis_storage - (update@ #bindings (set.add register)) + (update@ #bindings (set.has register)) (for_synthesis exprS) (get@ #dependencies))) (for_synthesis inputS synthesis_storage)) 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 41d618cc3..29ee68fac 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 @@ -182,7 +182,7 @@ (let [extension (|> amount list.indices (list\map (n.+ offset)))] [extension (list\fold (function (_ register redundancy) - (dictionary.put register ..necessary! redundancy)) + (dictionary.has register ..necessary! redundancy)) redundancy extension)])) @@ -221,7 +221,7 @@ (-> Register Redundancy (Try Redundancy)) (case (dictionary.get register redundancy) #.None - (#try.Success (dictionary.put register ..redundant! redundancy)) + (#try.Success (dictionary.has register ..redundant! redundancy)) (#.Some _) (exception.except ..redundant_declaration [register]))) @@ -233,7 +233,7 @@ (exception.except ..unknown_register [register]) (#.Some _) - (#try.Success (dictionary.put register ..necessary! redundancy)))) + (#try.Success (dictionary.has register ..necessary! redundancy)))) (def: (format redundancy) (%.Format Redundancy) @@ -310,7 +310,7 @@ (and (set.member? bindings register) redundant?))) (list\map product.left))]] - (in [(list\fold dictionary.remove redundancy (set.list bindings)) + (in [(list\fold dictionary.lacks redundancy (set.list bindings)) (|> redundants (list.sorted n.>) (list\fold (..remove_local_from_path ..remove_local) (#/.Seq pre post)))])) @@ -370,7 +370,7 @@ .let [redundant? (|> redundancy (dictionary.get register) (maybe.else ..necessary!))]] - (in [(dictionary.remove register redundancy) + (in [(dictionary.lacks register redundancy) (#/.Control (if redundant? (#/.Branch (#/.Case input (#/.Seq #/.Pop @@ -405,7 +405,7 @@ [[redundancy inits] (..list_optimization optimization' [redundancy inits]) .let [[extension redundancy] (..extended start (list.size inits) redundancy)] [redundancy iteration] (optimization' [redundancy iteration])] - (in [(list\fold dictionary.remove redundancy extension) + (in [(list\fold dictionary.lacks redundancy extension) (#/.Control (#/.Loop (#/.Scope [start inits iteration])))])) (#/.Recur resets) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 348a7ced9..1d605c120 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -111,18 +111,18 @@ (#try.Success [next (|> archive :representation - (update@ #..resolver (dictionary.put module [next #.None])) + (update@ #..resolver (dictionary.has module [next #.None])) (update@ #..next inc) :abstraction)])))) - (def: .public (add module [descriptor document output] archive) + (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) (#.Some [id #.None]) (#try.Success (|> archive :representation - (update@ #..resolver (dictionary.put module [id (#.Some [descriptor document output])])) + (update@ #..resolver (dictionary.has module [id (#.Some [descriptor document output])])) :abstraction)) (#.Some [id (#.Some [existing_descriptor existing_document existing_output])]) @@ -201,7 +201,7 @@ (list\fold (function (_ [module [id entry]] resolver) (case entry (#.Some _) - (dictionary.put module [id entry] resolver) + (dictionary.has module [id entry] resolver) #.None resolver)) @@ -280,7 +280,7 @@ (in (:abstraction {#next next #resolver (list\fold (function (_ [module id] archive) - (dictionary.put module [id #.None] archive)) + (dictionary.has module [id #.None] archive)) (get@ #resolver (:representation ..empty)) reservations)})))) ) 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 11aa363fd..e4240e404 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -75,7 +75,7 @@ :representation (update@ #artifacts (row.add {#id id #category (<tag> name)})) - (update@ #resolver (dictionary.put name id)) + (update@ #resolver (dictionary.has name id)) :abstraction)])) (def: .public (<fetch> registry) 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 66a903ca1..fc6c26067 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -47,7 +47,7 @@ (def: .public graph (-> (List Dependency) Graph) (list\fold (function (_ [module imports] graph) - (dictionary.put module imports graph)) + (dictionary.has module imports graph)) ..empty)) (def: (ancestry archive) 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 a87c3840b..a1f263f05 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -251,7 +251,7 @@ output]) (do ! [value (\ host re_load context #.None directive)] - (in [(dictionary.put name value definitions) + (in [(dictionary.has name value definitions) [analysers synthesizers generators @@ -263,7 +263,7 @@ [.let [output (row.add [artifact_id #.None data] output)] value (\ host re_load context #.None directive)] (in [definitions - [(dictionary.put extension (:as analysis.Handler value) analysers) + [(dictionary.has extension (:as analysis.Handler value) analysers) synthesizers generators directives] @@ -275,7 +275,7 @@ value (\ host re_load context #.None directive)] (in [definitions [analysers - (dictionary.put extension (:as synthesis.Handler value) synthesizers) + (dictionary.has extension (:as synthesis.Handler value) synthesizers) generators directives] output])) @@ -287,7 +287,7 @@ (in [definitions [analysers synthesizers - (dictionary.put extension (:as generation.Handler value) generators) + (dictionary.has extension (:as generation.Handler value) generators) directives] output])) @@ -299,7 +299,7 @@ [analysers synthesizers generators - (dictionary.put extension (:as directive.Handler value) directives)] + (dictionary.has extension (:as directive.Handler value) directives)] output])) (#artifact.Custom name) @@ -393,7 +393,7 @@ (get@ #descriptor.references) set.list (list.any? purged?)) - (dictionary.put module_name module_id purge) + (dictionary.has module_name module_id purge) purge)))) (..initial_purge caches) load_order)) @@ -424,7 +424,7 @@ (list\map product.right) (monad.fold try.monad (function (_ [module [module_id [descriptor document]]] archive) - (archive.add module [descriptor document (: Output row.empty)] archive)) + (archive.has module [descriptor document (: Output row.empty)] archive)) archive) (\ try.monad map (dependency.load_order $.key)) (\ try.monad join) @@ -444,7 +444,7 @@ (do {! try.monad} [archive (monad.fold ! (function (_ [[module descriptor,document,output] _bundle] archive) - (archive.add module descriptor,document,output archive)) + (archive.has module descriptor,document,output archive)) archive loaded_caches) analysis_state (..analysis_state (get@ #static.host static) archive)] 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 993b2264d..06ef9b25b 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -227,12 +227,12 @@ (case (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new entry_path) sink) (#try.Failure error) (recur entries - (set.add entry_path duplicates) + (set.has entry_path duplicates) sink) (#try.Success _) (let [[entry_size entry_data] (read_jar_entry entry input)] - (recur (set.add entry_path entries) + (recur (set.has entry_path entries) duplicates (do_to sink (java/util/zip/ZipOutputStream::write entry_data +0 (.int entry_size)) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index 5bfdac402..d1cecbe50 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -10,7 +10,7 @@ ["ex" exception (#+ Exception exception:)] ["." io] [parser - ["s" code]]] + ["<.>" code]]] [data ["." product] ["." text @@ -81,7 +81,9 @@ (function (_ state) (try\map (|>> [state]) error))) -(syntax: .public (assertion exception message test) +(syntax: .public (assertion [exception <code>.any + message <code>.any + test <code>.any]) (in (list (` (if (~ test) (\ ..monad (~' in) []) (..except (~ exception) (~ message))))))) |