aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2021-08-01 03:36:11 -0400
committerEduardo Julian2021-08-01 03:36:11 -0400
commitbcd70df3568d71f14763959f454c15d8164e2d15 (patch)
tree2ec5fa437d008af01b8e3887f532a2b6064cddb5 /stdlib/source/library/lux/tool/compiler
parentfa320d22d0d7888feddcabe43a2bc9f1e0335032 (diff)
Even more renamings.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux160
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux136
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/context.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux4
73 files changed, 333 insertions, 333 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 8b668b60f..1a8617f53 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -84,8 +84,8 @@
(-> (///directive.State+ anchor expression directive)
(///directive.State+ anchor expression directive))))
(function (_ [directive_extensions sub_state])
- [(dictionary.merge directive_extensions
- (luxD.bundle expander host_analysis program anchorT,expressionT,directiveT extender))
+ [(dictionary.merged directive_extensions
+ (luxD.bundle expander host_analysis program anchorT,expressionT,directiveT extender))
sub_state]))
(type: Reader
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index c5f2cfb8e..1848c28bc 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -136,13 +136,13 @@
{#descriptor.hash 0
#descriptor.name archive.runtime_module
#descriptor.file ""
- #descriptor.references (set.new text.hash)
+ #descriptor.references (set.empty text.hash)
#descriptor.state #.Compiled
#descriptor.registry registry})
(def: runtime_document
(Document .Module)
- (document.write $.key (module.new 0)))
+ (document.write $.key (module.empty 0)))
(def: (process_runtime archive platform)
(All [<type_vars>]
@@ -219,7 +219,7 @@
[analysers
synthesizers
generators
- (dictionary.merge directives (host_directive_bundle phase_wrapper))])
+ (dictionary.merged directives (host_directive_bundle phase_wrapper))])
(def: #export (initialize static module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender
import compilation_sources)
@@ -297,7 +297,7 @@
(def: empty
(Set Module)
- (set.new text.hash))
+ (set.empty text.hash))
(type: Mapping
(Dictionary Module (Set Module)))
@@ -308,7 +308,7 @@
(def: independence
Dependence
- (let [empty (dictionary.new text.hash)]
+ (let [empty (dictionary.empty text.hash)]
{#depends_on empty
#depended_by empty}))
@@ -394,7 +394,7 @@
initial
(Var (Dictionary Module <Pending>))
- (:assume (stm.var (dictionary.new text.hash))))
+ (:assume (stm.var (dictionary.empty text.hash))))
dependence (: (Var Dependence)
(stm.var ..independence))]
(function (_ compile)
@@ -471,7 +471,7 @@
(#try.Success [resulting_archive resulting_state])
(stm.commit (do stm.monad
[[_ [merged_archive _]] (stm.update (function (_ [archive state])
- [(archive.merge resulting_archive archive)
+ [(archive.merged resulting_archive archive)
state])
current)]
(in (#try.Success [merged_archive resulting_state])))))
@@ -565,7 +565,7 @@
(monad.seq ..monad))
#let [archive (|> archive,document+
(list\map product.left)
- (list\fold archive.merge archive))]]
+ (list\fold archive.merged archive))]]
(in [archive (try.assumed
(..updated_state archive state))])))]
(case ((get@ #///.process compilation)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux
index e5c8e654d..f8ddeff8e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux
@@ -104,4 +104,4 @@
(Key .Module)
(key.key {#signature.name (name_of ..compiler)
#signature.version /version.version}
- (module.new 0)))
+ (module.empty 0)))
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 f188f3c7d..02100305d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- nat int rev)
+ [lux (#- Variant Tuple nat int rev)
[abstract
[equivalence (#+ Equivalence)]
[hash (#+ Hash)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index b99a93f73..c7b843385 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -220,7 +220,7 @@
(do !
[nextA next]
(in [(list) nextA]))
- (list.reverse matches))]
+ (list.reversed matches))]
(in [(/.pattern/tuple memberP+)
thenA])))
@@ -312,7 +312,7 @@
branchesT)
outputHC (|> outputH product.left /coverage.determine)
outputTC (monad.map ! (|>> product.left /coverage.determine) outputT)
- _ (.case (monad.fold try.monad /coverage.merge outputHC outputTC)
+ _ (.case (monad.fold try.monad /coverage.merged outputHC outputTC)
(#try.Success coverage)
(///.assertion non_exhaustive_pattern_matching [inputC branches coverage]
(/coverage.exhaustive? coverage))
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 3760c86cc..7799be183 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
@@ -121,7 +121,7 @@
## Tuple patterns can be exhaustive if there is exhaustiveness for all of
## their sub-patterns.
(#/.Complex (#/.Tuple membersP+))
- (case (list.reverse membersP+)
+ (case (list.reversed membersP+)
(^or #.End (#.Item _ #.End))
(/.except ..invalid_tuple_pattern [])
@@ -151,7 +151,7 @@
(in (#Variant (if right?
(#.Some idx)
#.None)
- (|> (dictionary.new n.hash)
+ (|> (dictionary.empty n.hash)
(dictionary.put idx value_coverage)))))))
(def: (xor left right)
@@ -217,7 +217,7 @@
## necessary to merge them all to figure out if the entire
## pattern-matching expression is exhaustive and whether it contains
## redundant patterns.
-(def: #export (merge addition so_far)
+(def: #export (merged addition so_far)
(-> Coverage Coverage (Try Coverage))
(case [addition so_far]
[#Partial #Partial]
@@ -246,7 +246,7 @@
(case (dictionary.get tagA casesSF')
(#.Some coverageSF)
(do !
- [coverageM (merge coverageA coverageSF)]
+ [coverageM (merged coverageA coverageSF)]
(in (dictionary.put tagA coverageM casesSF')))
#.None
@@ -271,7 +271,7 @@
## Same prefix
[#1 #0]
(do try.monad
- [rightM (merge rightA rightSF)]
+ [rightM (merged rightA rightSF)]
(if (exhaustive? rightM)
## If all that follows is exhaustive, then it can be safely dropped
## (since only the "left" part would influence whether the
@@ -282,7 +282,7 @@
## Same suffix
[#0 #1]
(do try.monad
- [leftM (merge leftA leftSF)]
+ [leftM (merged leftA leftSF)]
(in (#Seq leftM rightA)))
## The 2 sequences cannot possibly be merged.
@@ -332,7 +332,7 @@
(in [#.None (list coverageA)])
(#.Item altSF altsSF')
- (case (merge coverageA altSF)
+ (case (merged coverageA altSF)
(#try.Success altMSF)
(case altMSF
(#Alt _)
@@ -356,7 +356,7 @@
(recur successA' possibilitiesSF'))
#.None
- (case (list.reverse possibilitiesSF)
+ (case (list.reversed possibilitiesSF)
(#.Item last prevs)
(in (list\fold (function (_ left right) (#Alt left right))
last
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 31ce0998c..e9e68deb3 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
@@ -97,7 +97,7 @@
scope)
(product.right ref+inner))]))
[init_ref #.End]
- (list.reverse inner))
+ (list.reversed inner))
scopes (list\compose inner' outer)]
(#.Right [(set@ #.scopes scopes state)
(#.Some [ref_type ref])]))
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 f3e9d30a1..4ecca3d1a 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
@@ -329,7 +329,7 @@
#.None
(/.except ..tag_does_not_belong_to_record [key recordT]))))
(: (Dictionary Nat Code)
- (dictionary.new n.hash))
+ (dictionary.empty n.hash))
record)
#let [ordered_tuple (list\map (function (_ idx) (maybe.assume (dictionary.get idx idx->val)))
tuple_range)]]
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 d0f8db7c5..aa78e8ade 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
@@ -48,7 +48,7 @@
(def: #export empty
Bundle
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
(type: #export (State s i o)
{#bundle (Bundle s i o)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux
index 93e1c6d1f..0def3e75d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux
@@ -12,5 +12,5 @@
(def: #export (bundle eval host_specific)
(-> Eval Bundle Bundle)
- (dictionary.merge host_specific
- (/lux.bundle eval)))
+ (dictionary.merged host_specific
+ (/lux.bundle eval)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
index 4f185f810..64a9b36b0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux
@@ -208,8 +208,8 @@
Bundle
(<| (bundle.prefix "js")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
(bundle.install "constant" js::constant)
(bundle.install "apply" js::apply)
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 acaf79ae9..0a60511ab 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
@@ -698,50 +698,50 @@
Bundle
(<| (///bundle.prefix "array")
(|> ///bundle.empty
- (dictionary.merge (<| (///bundle.prefix "length")
- (|> ///bundle.empty
- (///bundle.install (reflection.reflection reflection.boolean) (primitive_array_length_handler jvm.boolean))
- (///bundle.install (reflection.reflection reflection.byte) (primitive_array_length_handler jvm.byte))
- (///bundle.install (reflection.reflection reflection.short) (primitive_array_length_handler jvm.short))
- (///bundle.install (reflection.reflection reflection.int) (primitive_array_length_handler jvm.int))
- (///bundle.install (reflection.reflection reflection.long) (primitive_array_length_handler jvm.long))
- (///bundle.install (reflection.reflection reflection.float) (primitive_array_length_handler jvm.float))
- (///bundle.install (reflection.reflection reflection.double) (primitive_array_length_handler jvm.double))
- (///bundle.install (reflection.reflection reflection.char) (primitive_array_length_handler jvm.char))
- (///bundle.install "object" array::length::object))))
- (dictionary.merge (<| (///bundle.prefix "new")
- (|> ///bundle.empty
- (///bundle.install (reflection.reflection reflection.boolean) (new_primitive_array_handler jvm.boolean))
- (///bundle.install (reflection.reflection reflection.byte) (new_primitive_array_handler jvm.byte))
- (///bundle.install (reflection.reflection reflection.short) (new_primitive_array_handler jvm.short))
- (///bundle.install (reflection.reflection reflection.int) (new_primitive_array_handler jvm.int))
- (///bundle.install (reflection.reflection reflection.long) (new_primitive_array_handler jvm.long))
- (///bundle.install (reflection.reflection reflection.float) (new_primitive_array_handler jvm.float))
- (///bundle.install (reflection.reflection reflection.double) (new_primitive_array_handler jvm.double))
- (///bundle.install (reflection.reflection reflection.char) (new_primitive_array_handler jvm.char))
- (///bundle.install "object" array::new::object))))
- (dictionary.merge (<| (///bundle.prefix "read")
- (|> ///bundle.empty
- (///bundle.install (reflection.reflection reflection.boolean) (read_primitive_array_handler ..boolean jvm.boolean))
- (///bundle.install (reflection.reflection reflection.byte) (read_primitive_array_handler ..byte jvm.byte))
- (///bundle.install (reflection.reflection reflection.short) (read_primitive_array_handler ..short jvm.short))
- (///bundle.install (reflection.reflection reflection.int) (read_primitive_array_handler ..int jvm.int))
- (///bundle.install (reflection.reflection reflection.long) (read_primitive_array_handler ..long jvm.long))
- (///bundle.install (reflection.reflection reflection.float) (read_primitive_array_handler ..float jvm.float))
- (///bundle.install (reflection.reflection reflection.double) (read_primitive_array_handler ..double jvm.double))
- (///bundle.install (reflection.reflection reflection.char) (read_primitive_array_handler ..char jvm.char))
- (///bundle.install "object" array::read::object))))
- (dictionary.merge (<| (///bundle.prefix "write")
- (|> ///bundle.empty
- (///bundle.install (reflection.reflection reflection.boolean) (write_primitive_array_handler ..boolean jvm.boolean))
- (///bundle.install (reflection.reflection reflection.byte) (write_primitive_array_handler ..byte jvm.byte))
- (///bundle.install (reflection.reflection reflection.short) (write_primitive_array_handler ..short jvm.short))
- (///bundle.install (reflection.reflection reflection.int) (write_primitive_array_handler ..int jvm.int))
- (///bundle.install (reflection.reflection reflection.long) (write_primitive_array_handler ..long jvm.long))
- (///bundle.install (reflection.reflection reflection.float) (write_primitive_array_handler ..float jvm.float))
- (///bundle.install (reflection.reflection reflection.double) (write_primitive_array_handler ..double jvm.double))
- (///bundle.install (reflection.reflection reflection.char) (write_primitive_array_handler ..char jvm.char))
- (///bundle.install "object" array::write::object))))
+ (dictionary.merged (<| (///bundle.prefix "length")
+ (|> ///bundle.empty
+ (///bundle.install (reflection.reflection reflection.boolean) (primitive_array_length_handler jvm.boolean))
+ (///bundle.install (reflection.reflection reflection.byte) (primitive_array_length_handler jvm.byte))
+ (///bundle.install (reflection.reflection reflection.short) (primitive_array_length_handler jvm.short))
+ (///bundle.install (reflection.reflection reflection.int) (primitive_array_length_handler jvm.int))
+ (///bundle.install (reflection.reflection reflection.long) (primitive_array_length_handler jvm.long))
+ (///bundle.install (reflection.reflection reflection.float) (primitive_array_length_handler jvm.float))
+ (///bundle.install (reflection.reflection reflection.double) (primitive_array_length_handler jvm.double))
+ (///bundle.install (reflection.reflection reflection.char) (primitive_array_length_handler jvm.char))
+ (///bundle.install "object" array::length::object))))
+ (dictionary.merged (<| (///bundle.prefix "new")
+ (|> ///bundle.empty
+ (///bundle.install (reflection.reflection reflection.boolean) (new_primitive_array_handler jvm.boolean))
+ (///bundle.install (reflection.reflection reflection.byte) (new_primitive_array_handler jvm.byte))
+ (///bundle.install (reflection.reflection reflection.short) (new_primitive_array_handler jvm.short))
+ (///bundle.install (reflection.reflection reflection.int) (new_primitive_array_handler jvm.int))
+ (///bundle.install (reflection.reflection reflection.long) (new_primitive_array_handler jvm.long))
+ (///bundle.install (reflection.reflection reflection.float) (new_primitive_array_handler jvm.float))
+ (///bundle.install (reflection.reflection reflection.double) (new_primitive_array_handler jvm.double))
+ (///bundle.install (reflection.reflection reflection.char) (new_primitive_array_handler jvm.char))
+ (///bundle.install "object" array::new::object))))
+ (dictionary.merged (<| (///bundle.prefix "read")
+ (|> ///bundle.empty
+ (///bundle.install (reflection.reflection reflection.boolean) (read_primitive_array_handler ..boolean jvm.boolean))
+ (///bundle.install (reflection.reflection reflection.byte) (read_primitive_array_handler ..byte jvm.byte))
+ (///bundle.install (reflection.reflection reflection.short) (read_primitive_array_handler ..short jvm.short))
+ (///bundle.install (reflection.reflection reflection.int) (read_primitive_array_handler ..int jvm.int))
+ (///bundle.install (reflection.reflection reflection.long) (read_primitive_array_handler ..long jvm.long))
+ (///bundle.install (reflection.reflection reflection.float) (read_primitive_array_handler ..float jvm.float))
+ (///bundle.install (reflection.reflection reflection.double) (read_primitive_array_handler ..double jvm.double))
+ (///bundle.install (reflection.reflection reflection.char) (read_primitive_array_handler ..char jvm.char))
+ (///bundle.install "object" array::read::object))))
+ (dictionary.merged (<| (///bundle.prefix "write")
+ (|> ///bundle.empty
+ (///bundle.install (reflection.reflection reflection.boolean) (write_primitive_array_handler ..boolean jvm.boolean))
+ (///bundle.install (reflection.reflection reflection.byte) (write_primitive_array_handler ..byte jvm.byte))
+ (///bundle.install (reflection.reflection reflection.short) (write_primitive_array_handler ..short jvm.short))
+ (///bundle.install (reflection.reflection reflection.int) (write_primitive_array_handler ..int jvm.int))
+ (///bundle.install (reflection.reflection reflection.long) (write_primitive_array_handler ..long jvm.long))
+ (///bundle.install (reflection.reflection reflection.float) (write_primitive_array_handler ..float jvm.float))
+ (///bundle.install (reflection.reflection reflection.double) (write_primitive_array_handler ..double jvm.double))
+ (///bundle.install (reflection.reflection reflection.char) (write_primitive_array_handler ..char jvm.char))
+ (///bundle.install "object" array::write::object))))
)))
(def: object::null
@@ -1163,11 +1163,11 @@
(-> (List Text) (List Text) [(List .Type) Mapping])
(let [jvm_tvars (list\compose owner_tvars method_tvars)
lux_tvars (|> jvm_tvars
- list.reverse
+ list.reversed
list.enumeration
(list\map (function (_ [idx name])
[name (idx_to_parameter idx)]))
- list.reverse)
+ list.reversed)
num_owner_tvars (list.size owner_tvars)
owner_tvarsT (|> lux_tvars (list.take num_owner_tvars) (list\map product.right))
mapping (dictionary.of_list text.hash lux_tvars)]
@@ -1295,8 +1295,8 @@
(function (_ method)
(do !
[#let [expected_method_tvars (method_type_variables method)
- aliasing (dictionary.merge (..aliasing expected_class_tvars actual_class_tvars)
- (..aliasing expected_method_tvars actual_method_tvars))]
+ aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars)
+ (..aliasing expected_method_tvars actual_method_tvars))]
passes? (check_method aliasing class method_name method_style inputsJT method)]
(\ ! map (if passes?
(|>> #Pass)
@@ -1326,8 +1326,8 @@
(monad.map ! (function (_ constructor)
(do !
[#let [expected_method_tvars (constructor_type_variables constructor)
- aliasing (dictionary.merge (..aliasing expected_class_tvars actual_class_tvars)
- (..aliasing expected_method_tvars actual_method_tvars))]
+ aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars)
+ (..aliasing expected_method_tvars actual_method_tvars))]
passes? (check_constructor aliasing class inputsJT constructor)]
(\ ! map
(if passes? (|>> #Pass) (|>> #Hint))
@@ -1476,22 +1476,22 @@
(-> java/lang/ClassLoader Bundle)
(<| (///bundle.prefix "member")
(|> ///bundle.empty
- (dictionary.merge (<| (///bundle.prefix "get")
- (|> ///bundle.empty
- (///bundle.install "static" (get::static class_loader))
- (///bundle.install "virtual" (get::virtual class_loader)))))
- (dictionary.merge (<| (///bundle.prefix "put")
- (|> ///bundle.empty
- (///bundle.install "static" (put::static class_loader))
- (///bundle.install "virtual" (put::virtual class_loader)))))
- (dictionary.merge (<| (///bundle.prefix "invoke")
- (|> ///bundle.empty
- (///bundle.install "static" (invoke::static class_loader))
- (///bundle.install "virtual" (invoke::virtual class_loader))
- (///bundle.install "special" (invoke::special class_loader))
- (///bundle.install "interface" (invoke::interface class_loader))
- (///bundle.install "constructor" (invoke::constructor class_loader))
- )))
+ (dictionary.merged (<| (///bundle.prefix "get")
+ (|> ///bundle.empty
+ (///bundle.install "static" (get::static class_loader))
+ (///bundle.install "virtual" (get::virtual class_loader)))))
+ (dictionary.merged (<| (///bundle.prefix "put")
+ (|> ///bundle.empty
+ (///bundle.install "static" (put::static class_loader))
+ (///bundle.install "virtual" (put::virtual class_loader)))))
+ (dictionary.merged (<| (///bundle.prefix "invoke")
+ (|> ///bundle.empty
+ (///bundle.install "static" (invoke::static class_loader))
+ (///bundle.install "virtual" (invoke::virtual class_loader))
+ (///bundle.install "special" (invoke::special class_loader))
+ (///bundle.install "interface" (invoke::interface class_loader))
+ (///bundle.install "constructor" (invoke::constructor class_loader))
+ )))
)))
(type: #export (Annotation_Parameter a)
@@ -1686,7 +1686,7 @@
arguments)
[scope bodyA] (|> arguments'
(#.Item [self_name selfT])
- list.reverse
+ list.reversed
(list\fold scope.with_local (analyse archive body))
(typeA.with_type .Any)
/////analysis.with_scope)]
@@ -1762,7 +1762,7 @@
arguments)
[scope bodyA] (|> arguments'
(#.Item [self_name selfT])
- list.reverse
+ list.reversed
(list\fold scope.with_local (analyse archive body))
(typeA.with_type returnT)
/////analysis.with_scope)]
@@ -1835,7 +1835,7 @@
(in [name luxT])))
arguments)
[scope bodyA] (|> arguments'
- list.reverse
+ list.reversed
(list\fold scope.with_local (analyse archive body))
(typeA.with_type returnT)
/////analysis.with_scope)]
@@ -2002,7 +2002,7 @@
returnT (boxed_reflection_return mapping return)
[scope bodyA] (|> arguments'
(#.Item [self_name selfT])
- list.reverse
+ list.reversed
(list\fold scope.with_local (analyse archive body))
(typeA.with_type returnT)
/////analysis.with_scope)]
@@ -2173,14 +2173,14 @@
(-> java/lang/ClassLoader Bundle)
(<| (///bundle.prefix "jvm")
(|> ///bundle.empty
- (dictionary.merge bundle::conversion)
- (dictionary.merge bundle::int)
- (dictionary.merge bundle::long)
- (dictionary.merge bundle::float)
- (dictionary.merge bundle::double)
- (dictionary.merge bundle::char)
- (dictionary.merge bundle::array)
- (dictionary.merge (bundle::object class_loader))
- (dictionary.merge (bundle::member class_loader))
- (dictionary.merge (bundle::class class_loader))
+ (dictionary.merged bundle::conversion)
+ (dictionary.merged bundle::int)
+ (dictionary.merged bundle::long)
+ (dictionary.merged bundle::float)
+ (dictionary.merged bundle::double)
+ (dictionary.merged bundle::char)
+ (dictionary.merged bundle::array)
+ (dictionary.merged (bundle::object class_loader))
+ (dictionary.merged (bundle::member class_loader))
+ (dictionary.merged (bundle::class class_loader))
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
index 9fc9ce902..923880ebd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux
@@ -239,9 +239,9 @@
Bundle
(<| (bundle.prefix "lua")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
- (dictionary.merge bundle::utf8)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
+ (dictionary.merged bundle::utf8)
(bundle.install "constant" lua::constant)
(bundle.install "apply" lua::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
index 78d3b7aac..906b54e23 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -293,9 +293,9 @@
(-> Eval Bundle)
(<| (///bundle.prefix "lux")
(|> ///bundle.empty
- (dictionary.merge (bundle::lux eval))
- (dictionary.merge bundle::i64)
- (dictionary.merge bundle::f64)
- (dictionary.merge bundle::text)
- (dictionary.merge bundle::io)
+ (dictionary.merged (bundle::lux eval))
+ (dictionary.merged bundle::i64)
+ (dictionary.merged bundle::f64)
+ (dictionary.merged bundle::text)
+ (dictionary.merged bundle::io)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux
index 40cf1f094..0a7fc2d7d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux
@@ -204,8 +204,8 @@
Bundle
(<| (bundle.prefix "php")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
(bundle.install "constant" php::constant)
(bundle.install "apply" php::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux
index 6d5e3290f..b5a81bc65 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux
@@ -220,8 +220,8 @@
Bundle
(<| (bundle.prefix "python")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
(bundle.install "constant" python::constant)
(bundle.install "import" python::import)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux
index 65650c837..a5328bc54 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux
@@ -189,8 +189,8 @@
Bundle
(<| (bundle.prefix "ruby")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
(bundle.install "constant" ruby::constant)
(bundle.install "apply" ruby::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux
index 8e309a9de..5a6776b13 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux
@@ -149,8 +149,8 @@
Bundle
(<| (bundle.prefix "scheme")
(|> bundle.empty
- (dictionary.merge bundle::array)
- (dictionary.merge bundle::object)
+ (dictionary.merged bundle::array)
+ (dictionary.merged bundle::object)
(bundle.install "constant" scheme::constant)
(bundle.install "apply" scheme::apply)
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 95b04daa2..1869c6ff4 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
@@ -13,7 +13,7 @@
(def: #export empty
Bundle
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
(def: #export (install name anonymous)
(All [s i o]
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 d70b59aef..d12359d68 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
@@ -448,4 +448,4 @@
(<| (///bundle.prefix "lux")
(|> ///bundle.empty
(dictionary.put "def" (lux::def expander host_analysis))
- (dictionary.merge (..bundle::def expander host_analysis program anchorT,expressionT,directiveT extender)))))
+ (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/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux
index f42aa31ff..740236dc8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
index 602c40504..4900dea03 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
@@ -172,9 +172,9 @@
Bundle
(<| (/.prefix "lux")
(|> /.empty
- (dictionary.merge lux_procs)
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged lux_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux
index ba83e257f..64db8196b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
index da9bbc7f8..33267e376 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
@@ -184,8 +184,8 @@
Bundle
(<| (/.prefix "lux")
(|> lux_procs
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
index 8e9464e77..6bb747d54 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux
@@ -150,8 +150,8 @@
Bundle
(<| (/.prefix "js")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
(/.install "constant" js::constant)
(/.install "apply" js::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux
index 396c3284e..16a34222e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux
@@ -14,7 +14,7 @@
(def: #export bundle
Bundle
- ($_ dictionary.merge
+ ($_ dictionary.merged
/common.bundle
/host.bundle
))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
index 354537c19..78c75a17b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
@@ -408,7 +408,7 @@
Bundle
(<| (/////bundle.prefix "lux")
(|> bundle::lux
- (dictionary.merge ..bundle::i64)
- (dictionary.merge ..bundle::f64)
- (dictionary.merge ..bundle::text)
- (dictionary.merge ..bundle::io))))
+ (dictionary.merged ..bundle::i64)
+ (dictionary.merged ..bundle::f64)
+ (dictionary.merged ..bundle::text)
+ (dictionary.merged ..bundle::io))))
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 58ac1efc1..2c78f5988 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
@@ -462,50 +462,50 @@
Bundle
(<| (/////bundle.prefix "array")
(|> /////bundle.empty
- (dictionary.merge (<| (/////bundle.prefix "length")
- (|> /////bundle.empty
- (/////bundle.install (reflection.reflection reflection.boolean) (primitive_array_length_handler type.boolean))
- (/////bundle.install (reflection.reflection reflection.byte) (primitive_array_length_handler type.byte))
- (/////bundle.install (reflection.reflection reflection.short) (primitive_array_length_handler type.short))
- (/////bundle.install (reflection.reflection reflection.int) (primitive_array_length_handler type.int))
- (/////bundle.install (reflection.reflection reflection.long) (primitive_array_length_handler type.long))
- (/////bundle.install (reflection.reflection reflection.float) (primitive_array_length_handler type.float))
- (/////bundle.install (reflection.reflection reflection.double) (primitive_array_length_handler type.double))
- (/////bundle.install (reflection.reflection reflection.char) (primitive_array_length_handler type.char))
- (/////bundle.install "object" array::length::object))))
- (dictionary.merge (<| (/////bundle.prefix "new")
- (|> /////bundle.empty
- (/////bundle.install (reflection.reflection reflection.boolean) (new_primitive_array_handler __.t_boolean))
- (/////bundle.install (reflection.reflection reflection.byte) (new_primitive_array_handler __.t_byte))
- (/////bundle.install (reflection.reflection reflection.short) (new_primitive_array_handler __.t_short))
- (/////bundle.install (reflection.reflection reflection.int) (new_primitive_array_handler __.t_int))
- (/////bundle.install (reflection.reflection reflection.long) (new_primitive_array_handler __.t_long))
- (/////bundle.install (reflection.reflection reflection.float) (new_primitive_array_handler __.t_float))
- (/////bundle.install (reflection.reflection reflection.double) (new_primitive_array_handler __.t_double))
- (/////bundle.install (reflection.reflection reflection.char) (new_primitive_array_handler __.t_char))
- (/////bundle.install "object" array::new::object))))
- (dictionary.merge (<| (/////bundle.prefix "read")
- (|> /////bundle.empty
- (/////bundle.install (reflection.reflection reflection.boolean) (read_primitive_array_handler type.boolean _.baload))
- (/////bundle.install (reflection.reflection reflection.byte) (read_primitive_array_handler type.byte _.baload))
- (/////bundle.install (reflection.reflection reflection.short) (read_primitive_array_handler type.short _.saload))
- (/////bundle.install (reflection.reflection reflection.int) (read_primitive_array_handler type.int _.iaload))
- (/////bundle.install (reflection.reflection reflection.long) (read_primitive_array_handler type.long _.laload))
- (/////bundle.install (reflection.reflection reflection.float) (read_primitive_array_handler type.float _.faload))
- (/////bundle.install (reflection.reflection reflection.double) (read_primitive_array_handler type.double _.daload))
- (/////bundle.install (reflection.reflection reflection.char) (read_primitive_array_handler type.char _.caload))
- (/////bundle.install "object" array::read::object))))
- (dictionary.merge (<| (/////bundle.prefix "write")
- (|> /////bundle.empty
- (/////bundle.install (reflection.reflection reflection.boolean) (write_primitive_array_handler type.boolean _.bastore))
- (/////bundle.install (reflection.reflection reflection.byte) (write_primitive_array_handler type.byte _.bastore))
- (/////bundle.install (reflection.reflection reflection.short) (write_primitive_array_handler type.short _.sastore))
- (/////bundle.install (reflection.reflection reflection.int) (write_primitive_array_handler type.int _.iastore))
- (/////bundle.install (reflection.reflection reflection.long) (write_primitive_array_handler type.long _.lastore))
- (/////bundle.install (reflection.reflection reflection.float) (write_primitive_array_handler type.float _.fastore))
- (/////bundle.install (reflection.reflection reflection.double) (write_primitive_array_handler type.double _.dastore))
- (/////bundle.install (reflection.reflection reflection.char) (write_primitive_array_handler type.char _.castore))
- (/////bundle.install "object" array::write::object))))
+ (dictionary.merged (<| (/////bundle.prefix "length")
+ (|> /////bundle.empty
+ (/////bundle.install (reflection.reflection reflection.boolean) (primitive_array_length_handler type.boolean))
+ (/////bundle.install (reflection.reflection reflection.byte) (primitive_array_length_handler type.byte))
+ (/////bundle.install (reflection.reflection reflection.short) (primitive_array_length_handler type.short))
+ (/////bundle.install (reflection.reflection reflection.int) (primitive_array_length_handler type.int))
+ (/////bundle.install (reflection.reflection reflection.long) (primitive_array_length_handler type.long))
+ (/////bundle.install (reflection.reflection reflection.float) (primitive_array_length_handler type.float))
+ (/////bundle.install (reflection.reflection reflection.double) (primitive_array_length_handler type.double))
+ (/////bundle.install (reflection.reflection reflection.char) (primitive_array_length_handler type.char))
+ (/////bundle.install "object" array::length::object))))
+ (dictionary.merged (<| (/////bundle.prefix "new")
+ (|> /////bundle.empty
+ (/////bundle.install (reflection.reflection reflection.boolean) (new_primitive_array_handler __.t_boolean))
+ (/////bundle.install (reflection.reflection reflection.byte) (new_primitive_array_handler __.t_byte))
+ (/////bundle.install (reflection.reflection reflection.short) (new_primitive_array_handler __.t_short))
+ (/////bundle.install (reflection.reflection reflection.int) (new_primitive_array_handler __.t_int))
+ (/////bundle.install (reflection.reflection reflection.long) (new_primitive_array_handler __.t_long))
+ (/////bundle.install (reflection.reflection reflection.float) (new_primitive_array_handler __.t_float))
+ (/////bundle.install (reflection.reflection reflection.double) (new_primitive_array_handler __.t_double))
+ (/////bundle.install (reflection.reflection reflection.char) (new_primitive_array_handler __.t_char))
+ (/////bundle.install "object" array::new::object))))
+ (dictionary.merged (<| (/////bundle.prefix "read")
+ (|> /////bundle.empty
+ (/////bundle.install (reflection.reflection reflection.boolean) (read_primitive_array_handler type.boolean _.baload))
+ (/////bundle.install (reflection.reflection reflection.byte) (read_primitive_array_handler type.byte _.baload))
+ (/////bundle.install (reflection.reflection reflection.short) (read_primitive_array_handler type.short _.saload))
+ (/////bundle.install (reflection.reflection reflection.int) (read_primitive_array_handler type.int _.iaload))
+ (/////bundle.install (reflection.reflection reflection.long) (read_primitive_array_handler type.long _.laload))
+ (/////bundle.install (reflection.reflection reflection.float) (read_primitive_array_handler type.float _.faload))
+ (/////bundle.install (reflection.reflection reflection.double) (read_primitive_array_handler type.double _.daload))
+ (/////bundle.install (reflection.reflection reflection.char) (read_primitive_array_handler type.char _.caload))
+ (/////bundle.install "object" array::read::object))))
+ (dictionary.merged (<| (/////bundle.prefix "write")
+ (|> /////bundle.empty
+ (/////bundle.install (reflection.reflection reflection.boolean) (write_primitive_array_handler type.boolean _.bastore))
+ (/////bundle.install (reflection.reflection reflection.byte) (write_primitive_array_handler type.byte _.bastore))
+ (/////bundle.install (reflection.reflection reflection.short) (write_primitive_array_handler type.short _.sastore))
+ (/////bundle.install (reflection.reflection reflection.int) (write_primitive_array_handler type.int _.iastore))
+ (/////bundle.install (reflection.reflection reflection.long) (write_primitive_array_handler type.long _.lastore))
+ (/////bundle.install (reflection.reflection reflection.float) (write_primitive_array_handler type.float _.fastore))
+ (/////bundle.install (reflection.reflection reflection.double) (write_primitive_array_handler type.double _.dastore))
+ (/////bundle.install (reflection.reflection reflection.char) (write_primitive_array_handler type.char _.castore))
+ (/////bundle.install "object" array::write::object))))
)))
(def: (object::null _)
@@ -796,21 +796,21 @@
Bundle
(<| (/////bundle.prefix "member")
(|> (: Bundle /////bundle.empty)
- (dictionary.merge (<| (/////bundle.prefix "get")
- (|> (: Bundle /////bundle.empty)
- (/////bundle.install "static" get::static)
- (/////bundle.install "virtual" get::virtual))))
- (dictionary.merge (<| (/////bundle.prefix "put")
- (|> (: Bundle /////bundle.empty)
- (/////bundle.install "static" put::static)
- (/////bundle.install "virtual" put::virtual))))
- (dictionary.merge (<| (/////bundle.prefix "invoke")
- (|> (: Bundle /////bundle.empty)
- (/////bundle.install "static" invoke::static)
- (/////bundle.install "virtual" invoke::virtual)
- (/////bundle.install "special" invoke::special)
- (/////bundle.install "interface" invoke::interface)
- (/////bundle.install "constructor" invoke::constructor))))
+ (dictionary.merged (<| (/////bundle.prefix "get")
+ (|> (: Bundle /////bundle.empty)
+ (/////bundle.install "static" get::static)
+ (/////bundle.install "virtual" get::virtual))))
+ (dictionary.merged (<| (/////bundle.prefix "put")
+ (|> (: Bundle /////bundle.empty)
+ (/////bundle.install "static" put::static)
+ (/////bundle.install "virtual" put::virtual))))
+ (dictionary.merged (<| (/////bundle.prefix "invoke")
+ (|> (: Bundle /////bundle.empty)
+ (/////bundle.install "static" invoke::static)
+ (/////bundle.install "virtual" invoke::virtual)
+ (/////bundle.install "special" invoke::special)
+ (/////bundle.install "interface" invoke::interface)
+ (/////bundle.install "constructor" invoke::constructor))))
)))
(def: annotation_parameter
@@ -1094,13 +1094,13 @@
Bundle
(<| (/////bundle.prefix "jvm")
(|> ..bundle::conversion
- (dictionary.merge ..bundle::int)
- (dictionary.merge ..bundle::long)
- (dictionary.merge ..bundle::float)
- (dictionary.merge ..bundle::double)
- (dictionary.merge ..bundle::char)
- (dictionary.merge ..bundle::array)
- (dictionary.merge ..bundle::object)
- (dictionary.merge ..bundle::member)
- (dictionary.merge ..bundle::class)
+ (dictionary.merged ..bundle::int)
+ (dictionary.merged ..bundle::long)
+ (dictionary.merged ..bundle::float)
+ (dictionary.merged ..bundle::double)
+ (dictionary.merged ..bundle::char)
+ (dictionary.merged ..bundle::array)
+ (dictionary.merged ..bundle::object)
+ (dictionary.merged ..bundle::member)
+ (dictionary.merged ..bundle::class)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
index 1f1bd7f91..492f43b94 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
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 e8022f806..3c8338304 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
@@ -174,8 +174,8 @@
Bundle
(<| (/.prefix "lux")
(|> lux_procs
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
index 35d895177..a66a198c7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
@@ -187,9 +187,9 @@
Bundle
(<| (/.prefix "lua")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
- (dictionary.merge ..utf8)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
+ (dictionary.merged ..utf8)
(/.install "constant" lua::constant)
(/.install "apply" lua::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux
index 751e67a85..6805ccc27 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
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 3925bec4b..ca4de50cf 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
@@ -185,8 +185,8 @@
Bundle
(<| (/.prefix "lux")
(|> /.empty
- (dictionary.merge lux_procs)
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs))))
+ (dictionary.merged lux_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
index a8ef44fc8..39ddd3df9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
@@ -133,8 +133,8 @@
Bundle
(<| (/.prefix "php")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
(/.install "constant" php::constant)
(/.install "apply" php::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux
index 2309732f3..55e2e4756 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
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 d9c7fe72f..81107aba9 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
@@ -164,8 +164,8 @@
Bundle
(<| (/.prefix "lux")
(|> lux_procs
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
index a9215898d..56393387f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
@@ -154,8 +154,8 @@
Bundle
(<| (/.prefix "python")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
(/.install "constant" python::constant)
(/.install "import" python::import)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux
index 7ca8195f7..f137406ab 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
index 87c1e59cc..8604be023 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux
@@ -171,9 +171,9 @@
Bundle
(<| (/.prefix "lux")
(|> /.empty
- ## (dictionary.merge lux_procs)
- (dictionary.merge i64_procs)
- ## (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- ## (dictionary.merge io_procs)
+ ## (dictionary.merged lux_procs)
+ (dictionary.merged i64_procs)
+ ## (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ ## (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux
index 417ccf847..dfeee165e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
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 970566967..7eb4e2a5b 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
@@ -179,8 +179,8 @@
Bundle
(<| (/.prefix "lux")
(|> lux_procs
- (dictionary.merge ..i64_procs)
- (dictionary.merge ..f64_procs)
- (dictionary.merge ..text_procs)
- (dictionary.merge ..io_procs)
+ (dictionary.merged ..i64_procs)
+ (dictionary.merged ..f64_procs)
+ (dictionary.merged ..text_procs)
+ (dictionary.merged ..io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
index 0d0f94f50..9e6df81c7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
@@ -126,8 +126,8 @@
Bundle
(<| (/.prefix "ruby")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
(/.install "constant" ruby::constant)
(/.install "apply" ruby::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux
index 7245ac4f6..9d74e5fc6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux
@@ -14,5 +14,5 @@
(def: #export bundle
Bundle
- (dictionary.merge /common.bundle
- /host.bundle))
+ (dictionary.merged /common.bundle
+ /host.bundle))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
index 3663f845a..e725c9b95 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
@@ -167,9 +167,9 @@
Bundle
(<| (/.prefix "lux")
(|> /.empty
- (dictionary.merge lux_procs)
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged lux_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
index 23f6056ae..0552946f9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
@@ -100,8 +100,8 @@
Bundle
(<| (/.prefix "scheme")
(|> /.empty
- (dictionary.merge ..array)
- (dictionary.merge ..object)
+ (dictionary.merged ..array)
+ (dictionary.merged ..object)
(/.install "constant" scheme::constant)
(/.install "apply" scheme::apply)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
index ee472fe92..f5d416ee1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
@@ -130,8 +130,8 @@
Bundle
(<| (bundle.prefix "lux")
(|> lux_procs
- (dictionary.merge i64_procs)
- (dictionary.merge f64_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged f64_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
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 7beef96cb..7758725c1 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
@@ -85,7 +85,7 @@
[#.Right //runtime.tuple//right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: @savepoint (_.var "lux_pm_cursor_savepoint"))
(def: @cursor (_.var "lux_pm_cursor"))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
index de6b0a500..dcb7daa43 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
@@ -38,7 +38,7 @@
(if initial?
(_.define variable value)
(_.set variable value)))))
- list.reverse
+ list.reversed
(list\fold _.then body)))
(def: #export (scope! statement expression archive [start initsS+ bodyS])
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 04d5926a7..bdf4fb89c 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
@@ -250,7 +250,7 @@
(..right_projection lefts))]
(_.compose so_far next)))
recordG
- (list.reverse path)))))
+ (list.reversed path)))))
(def: #export (case phase archive [valueS path])
(Generator [Synthesis Path])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
index ba6cb27ef..f8961db37 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
@@ -66,7 +66,7 @@
(list\map product.left)
(monad.seq _.monad))
(|> updatesG
- list.reverse
+ list.reversed
(list\map product.right)
(monad.seq _.monad))
(_.goto @begin)))))
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 2114acc89..0e1b681c4 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
@@ -71,7 +71,7 @@
[#.Right //runtime.tuple//right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: #export (if expression archive [testS thenS elseS])
(Generator [Synthesis Synthesis Synthesis])
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 af27eb9fc..5eb23e1a9 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
@@ -92,7 +92,7 @@
[#.Right //runtime.tuple//right]))]
(method source)))
valueG
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: @savepoint (_.var "lux_pm_savepoint"))
(def: @cursor (_.var "lux_pm_cursor"))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
index 8da358393..08a124e2c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
@@ -104,9 +104,9 @@
Bundle
(<| (bundle.prefix "lux")
(|> lux_procs
- (dictionary.merge i64_procs)
- (dictionary.merge int_procs)
- (dictionary.merge frac_procs)
- (dictionary.merge text_procs)
- (dictionary.merge io_procs)
+ (dictionary.merged i64_procs)
+ (dictionary.merged int_procs)
+ (dictionary.merged frac_procs)
+ (dictionary.merged text_procs)
+ (dictionary.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
index 82fe69b94..630e222e5 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
@@ -44,7 +44,7 @@
(list\map (function (_ [register value])
(let [variable (//case.register (n.+ offset register))]
(_.set! variable value))))
- list.reverse
+ list.reversed
(list\fold _.then body)))
(def: #export (scope! statement expression archive [start initsS+ bodyS])
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 a3f993150..cdfaf74fe 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
@@ -97,7 +97,7 @@
[#.Right //runtime.tuple::right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: @savepoint (_.var "lux_pm_savepoint"))
(def: @cursor (_.var "lux_pm_cursor"))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
index 066925e96..830154cbd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
@@ -38,7 +38,7 @@
(list\map (function (_ [register value])
(_.set (list (//case.register (n.+ offset register)))
value)))
- list.reverse
+ list.reversed
(list\fold _.then body)))
(def: #export (set_scope body!)
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 133ce1fa8..8ef713643 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
@@ -75,7 +75,7 @@
[#.Right //runtime.tuple::right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: $savepoint (_.var "lux_pm_cursor_savepoint"))
(def: $cursor (_.var "lux_pm_cursor"))
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 b650c7e8d..7de7310d6 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
@@ -139,7 +139,7 @@
(def: lux_procs
Bundle
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "is" (binary lux//is))
(install "try" (unary lux//try))
(install "if" (trinary lux//if))
@@ -171,7 +171,7 @@
(def: bit_procs
Bundle
(<| (prefix "bit")
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "and" (binary bit//and))
(install "or" (binary bit//or))
(install "xor" (binary bit//xor))
@@ -243,7 +243,7 @@
(def: int_procs
Bundle
(<| (prefix "int")
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "+" (binary int//add))
(install "-" (binary int//sub))
(install "*" (binary int//mul))
@@ -261,7 +261,7 @@
(def: frac_procs
Bundle
(<| (prefix "frac")
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "+" (binary frac//add))
(install "-" (binary frac//sub))
(install "*" (binary frac//mul))
@@ -296,7 +296,7 @@
(def: text_procs
Bundle
(<| (prefix "text")
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "=" (binary text//=))
(install "<" (binary text//<))
(install "concat" (binary text//concat))
@@ -320,7 +320,7 @@
(def: io_procs
Bundle
(<| (prefix "io")
- (|> (dict.new text.Hash<Text>)
+ (|> (dict.empty text.Hash<Text>)
(install "log" (unary (|>> r.print ..void)))
(install "error" (unary r.stop))
(install "exit" (unary io//exit))
@@ -332,9 +332,9 @@
Bundle
(<| (prefix "lux")
(|> lux_procs
- (dict.merge bit_procs)
- (dict.merge int_procs)
- (dict.merge frac_procs)
- (dict.merge text_procs)
- (dict.merge io_procs)
+ (dict.merged bit_procs)
+ (dict.merged int_procs)
+ (dict.merged frac_procs)
+ (dict.merged text_procs)
+ (dict.merged io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
index cb0f5e48d..f97ae27e0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
@@ -47,7 +47,7 @@
## (def: lua_procs
## @.Bundle
-## (|> (dict.new text.Hash<Text>)
+## (|> (dict.empty text.Hash<Text>)
## (@.install "nil" (@.nullary lua//nil))
## (@.install "table" (@.nullary lua//table))
## (@.install "global" lua//global)
@@ -76,7 +76,7 @@
## (def: table_procs
## @.Bundle
## (<| (@.prefix "table")
-## (|> (dict.new text.Hash<Text>)
+## (|> (dict.empty text.Hash<Text>)
## (@.install "call" table//call)
## (@.install "get" (@.binary table//get))
## (@.install "set" (@.trinary table//set)))))
@@ -84,7 +84,7 @@
(def: #export procedures
@.Bundle
(<| (@.prefix "lua")
- (dict.new text.Hash<Text>)
+ (dict.empty text.Hash<Text>)
## (|> lua_procs
- ## (dict.merge table_procs))
+ ## (dict.merged table_procs))
))
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 69df6f104..d1bbfae39 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
@@ -99,7 +99,7 @@
[#.Right //runtime.tuple//right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: @savepoint (_.local "lux_pm_savepoint"))
(def: @cursor (_.local "lux_pm_cursor"))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
index ed5370a68..d021df198 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
@@ -38,7 +38,7 @@
(list\map (function (_ [register value])
(_.set (list (//case.register (n.+ offset register)))
value)))
- list.reverse
+ list.reversed
(list\fold _.then body)))
(def: symbol
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 79d8950ce..25da6b501 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
@@ -73,7 +73,7 @@
[#.Right //runtime.tuple//right]))]
(method source)))
valueO
- (list.reverse pathP)))))
+ (list.reversed pathP)))))
(def: @savepoint (_.var "lux_pm_cursor_savepoint"))
(def: @cursor (_.var "lux_pm_cursor"))
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 a3a598808..28cf31cc1 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
@@ -216,8 +216,8 @@
Bundle
(<| (bundle.prefix "lux")
(|> bundle::lux
- (dict.merge bundle::i64)
- (dict.merge bundle::f64)
- (dict.merge bundle::text)
- (dict.merge bundle::io)
+ (dict.merged bundle::i64)
+ (dict.merged bundle::f64)
+ (dict.merged bundle::text)
+ (dict.merged bundle::io)
)))
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 dc22dc355..f6f4d746c 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
@@ -87,7 +87,7 @@
(when> [(new> (not end?') [])] [(///\map ..clean_up)])
nextC))))
thenC
- (list.reverse (list.enumeration tuple))))
+ (list.reversed (list.enumeration tuple))))
))
(def: (path archive synthesize pattern bodyA)
@@ -322,8 +322,8 @@
(def: empty
Storage
- {#bindings (set.new n.hash)
- #dependencies (set.new ///reference/variable.hash)})
+ {#bindings (set.empty n.hash)
+ #dependencies (set.empty ///reference/variable.hash)})
## TODO: Use this to declare all local variables at the beginning of
## script functions.
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 80d3eb556..ab798a01b 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
@@ -172,7 +172,7 @@
(def: initial
Redundancy
- (dictionary.new n.hash))
+ (dictionary.empty n.hash))
(def: redundant! true)
(def: necessary! false)
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 a54350ccf..d6c43e896 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -103,7 +103,7 @@
(def: #export no_aliases
Aliases
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
(def: #export prelude
.prelude_module)
@@ -230,7 +230,7 @@
(#.Left [source' error])
(if (is? <close> error)
(#.Right [source'
- [where (<tag> (list.reverse stack))]])
+ [where (<tag> (list.reversed stack))]])
(#.Left [source' error])))))]
## Form and tuple syntax is mostly the same, differing only in the
@@ -253,7 +253,7 @@
(#.Left [source' error])
(if (is? ..close_record error)
(#.Right [source'
- [where (#.Record (list.reverse stack))]])
+ [where (#.Record (list.reversed stack))]])
(#.Left [source' error])))))
(template: (!guarantee_no_new_lines where offset source_code content body)
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 8559afe35..d5a1e53a4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
@@ -44,7 +44,7 @@
(def: #export fresh_resolver
Resolver
- (dictionary.new variable.hash))
+ (dictionary.empty variable.hash))
(def: #export init
State
@@ -307,10 +307,10 @@
(format "(@ " (%.nat register) ")")
(#Alt left right)
- (format "(| " (%path' %then left) " " (%path' %then right) ")")
+ (format "(Variant " (%path' %then left) " " (%path' %then right) ")")
(#Seq left right)
- (format "(& " (%path' %then left) " " (%path' %then right) ")")
+ (format "(Tuple " (%path' %then left) " " (%path' %then right) ")")
(#Then then)
(|> (%then then)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index a5a8826a0..a45c7ad59 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -85,7 +85,7 @@
(def: #export empty
Archive
(:abstraction {#next 0
- #resolver (dictionary.new text.hash)}))
+ #resolver (dictionary.empty text.hash)}))
(def: #export (id module archive)
(-> Module Archive (Try ID))
@@ -189,7 +189,7 @@
(list\map (function (_ [module [id _]])
[module id]))))
- (def: #export (merge additions archive)
+ (def: #export (merged additions archive)
(-> Archive Archive Archive)
(let [[+next +resolver] (:representation additions)]
(|> archive
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 c7f699f87..7feeac2a0 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -44,7 +44,7 @@
(def: #export empty
Registry
(:abstraction {#artifacts row.empty
- #resolver (dictionary.new text.hash)}))
+ #resolver (dictionary.empty text.hash)}))
(def: #export artifacts
(-> Registry (Row Artifact))
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 c51151b68..4d9af7859 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
@@ -27,14 +27,14 @@
(def: fresh
Ancestry
- (set.new text.hash))
+ (set.empty text.hash))
(type: #export Graph
(Dictionary Module Ancestry))
(def: empty
Graph
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
(def: #export modules
(-> Graph (List Module))
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 7290b74a5..c5ebc6bad 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -205,10 +205,10 @@
(def: empty_bundles
Bundles
- [(dictionary.new text.hash)
- (dictionary.new text.hash)
- (dictionary.new text.hash)
- (dictionary.new text.hash)])
+ [(dictionary.empty text.hash)
+ (dictionary.empty text.hash)
+ (dictionary.empty text.hash)
+ (dictionary.empty text.hash)])
(def: (loaded_document extension host module_id expected actual document)
(All [expression directive]
@@ -218,7 +218,7 @@
[[definitions bundles] (: (Try [Definitions Bundles Output])
(loop [input (row.to_list expected)
definitions (: Definitions
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
bundles ..empty_bundles
output (: Output row.empty)]
(let [[analysers synthesizers generators directives] bundles]
@@ -452,10 +452,10 @@
analysis_state
(list\fold (function (_ [_ [+analysers +synthesizers +generators +directives]]
[analysers synthesizers generators directives])
- [(dictionary.merge +analysers analysers)
- (dictionary.merge +synthesizers synthesizers)
- (dictionary.merge +generators generators)
- (dictionary.merge +directives directives)])
+ [(dictionary.merged +analysers analysers)
+ (dictionary.merged +synthesizers synthesizers)
+ (dictionary.merged +generators generators)
+ (dictionary.merged +directives directives)])
..empty_bundles
loaded_caches)])))))
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 aae528bda..8903ab503 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
@@ -165,5 +165,5 @@
(try.with async.monad))
(..enumerate_context fs)
(: Enumeration
- (dictionary.new text.hash))
+ (dictionary.empty text.hash))
contexts))
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 b1735f389..3ebdae788 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -256,8 +256,8 @@
[entries duplicates sink] (|> host_dependencies
dictionary.values
(monad.fold ! ..write_host_dependency
- [(set.new text.hash)
- (set.new text.hash)
+ [(set.empty text.hash)
+ (set.empty text.hash)
sink]))
#let [_ (do_to sink
(java/io/Flushable::flush)