From 3525998c8fa9768dfeb333c553ccd71f38ac5311 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 20 Oct 2022 15:11:05 -0400 Subject: Migrating default extensions to the new format [Part 3] --- stdlib/source/library/lux/data/text.lux | 24 +- stdlib/source/library/lux/ffi.jvm.lux | 328 +++++++++--------- stdlib/source/library/lux/ffi/export.jvm.lux | 7 +- stdlib/source/library/lux/math/number/frac.lux | 10 +- .../language/lux/phase/extension/analysis/jvm.lux | 314 ++++++++--------- .../lux/phase/extension/declaration/jvm.lux | 9 +- .../lux/phase/extension/generation/jvm/host.lux | 384 ++++++++++----------- .../library/lux/meta/target/jvm/constant.lux | 5 +- .../source/library/lux/meta/target/jvm/loader.lux | 2 +- stdlib/source/library/lux/world/net/http.lux | 6 +- .../source/library/lux/world/net/http/version.lux | 42 ++- stdlib/source/library/lux/world/time/instant.lux | 4 +- stdlib/source/test/lux/ffi.jvm.lux | 4 +- stdlib/source/test/lux/meta/target/jvm.lux | 361 ++++++++++--------- stdlib/source/test/lux/world/net.lux | 4 +- stdlib/source/test/lux/world/net/http/version.lux | 48 +++ stdlib/source/unsafe/lux/data/collection/array.lux | 22 +- 17 files changed, 791 insertions(+), 783 deletions(-) create mode 100644 stdlib/source/test/lux/world/net/http/version.lux (limited to 'stdlib/source') diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index e1ac2856b..2df34e163 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -229,10 +229,10 @@ (as (Primitive "java.lang.CharSequence") replacement))) @.jvm (as Text - ("jvm member invoke virtual" [] "java.lang.String" "replace" [] - (as (Primitive "java.lang.String") template) - ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") pattern)] - ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") replacement)])) + (.jvm_member_invoke_virtual# [] "java.lang.String" "replace" [] + (as (Primitive "java.lang.String") template) + ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") pattern)] + ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") replacement)])) @.js ... TODO: Remove this when Nashorn is no longer being used. (..if_nashorn @@ -283,7 +283,7 @@ (Hash Text) (implementation (def equivalence ..equivalence) - + (def (hash input) (for @.old (|> input @@ -295,9 +295,9 @@ @.jvm (|> input (as (Primitive "java.lang.Object")) - ("jvm member invoke virtual" [] "java.lang.Object" "hashCode" []) - "jvm conversion int-to-long" - "jvm object cast" + (.jvm_member_invoke_virtual# [] "java.lang.Object" "hashCode" []) + .jvm_conversion_int_to_long# + .jvm_object_cast# (is (Primitive "java.lang.Long")) (as Nat)) ... Platform-independent default. @@ -361,8 +361,8 @@ (as (Primitive "java.lang.String") value))) @.jvm (as Text - ("jvm member invoke virtual" [] "java.lang.String" "toLowerCase" [] - (as (Primitive "java.lang.String") value))) + (.jvm_member_invoke_virtual# [] "java.lang.String" "toLowerCase" [] + (as (Primitive "java.lang.String") value))) @.js (as Text ("js object do" "toLowerCase" value [])) @@ -384,8 +384,8 @@ (as (Primitive "java.lang.String") value))) @.jvm (as Text - ("jvm member invoke virtual" [] "java.lang.String" "toUpperCase" [] - (as (Primitive "java.lang.String") value))) + (.jvm_member_invoke_virtual# [] "java.lang.String" "toUpperCase" [] + (as (Primitive "java.lang.String") value))) @.js (as Text ("js object do" "toUpperCase" value [])) diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index c585c45c7..0f704a0cb 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -92,16 +92,14 @@ (def (get_static_field class field) (-> Text Text Code) - (` ("jvm member get static" - (, (code.text class)) - (, (code.text field))))) + (` (.jvm_member_get_static# (, (code.text class)) + (, (code.text field))))) (def (get_virtual_field class field object) (-> Text Text Code Code) - (` ("jvm member get virtual" - (, (code.text class)) - (, (code.text field)) - (, object)))) + (` (.jvm_member_get_virtual# (, (code.text class)) + (, (code.text field)) + (, object)))) (def boxes (Dictionary (Type Value) Text) @@ -121,7 +119,7 @@ (let [unboxed (..reflection unboxed)] (` (|> (, raw) (.is (.Primitive (, (code.text
))))
-              "jvm object cast"
+              .jvm_object_cast#
               (.is (.Primitive (, (code.text ))))))))]
 
   [unbox boxed unboxed]
@@ -133,40 +131,40 @@
      (template ( value)
        [(|> value
             (.is )
-            "jvm object cast"
+            .jvm_object_cast#
             
-            "jvm object cast"
+            .jvm_object_cast#
             (.is ))]))]
 
-  [byte_to_long    "jvm conversion byte-to-long"    ..Byte      ..Long]
+  [byte_to_long    .jvm_conversion_byte_to_long#    ..Byte      ..Long]
 
-  [short_to_long   "jvm conversion short-to-long"   ..Short     ..Long]
+  [short_to_long   .jvm_conversion_short_to_long#   ..Short     ..Long]
   
-  [double_to_int   "jvm conversion double-to-int"   ..Double    ..Integer]
-  [double_to_long  "jvm conversion double-to-long"  ..Double    ..Long]
-  [double_to_float "jvm conversion double-to-float" ..Double    ..Float]
+  [double_to_int   .jvm_conversion_double_to_int#   ..Double    ..Integer]
+  [double_to_long  .jvm_conversion_double_to_long#  ..Double    ..Long]
+  [double_to_float .jvm_conversion_double_to_float# ..Double    ..Float]
 
-  [float_to_int    "jvm conversion float-to-int"    ..Float     ..Integer]
-  [float_to_long   "jvm conversion float-to-long"   ..Float     ..Long]
-  [float_to_double "jvm conversion float-to-double" ..Float     ..Double]
+  [float_to_int    .jvm_conversion_float_to_int#    ..Float     ..Integer]
+  [float_to_long   .jvm_conversion_float_to_long#   ..Float     ..Long]
+  [float_to_double .jvm_conversion_float_to_double# ..Float     ..Double]
   
-  [int_to_byte     "jvm conversion int-to-byte"     ..Integer   ..Byte]
-  [int_to_short    "jvm conversion int-to-short"    ..Integer   ..Short]
-  [int_to_long     "jvm conversion int-to-long"     ..Integer   ..Long]
-  [int_to_float    "jvm conversion int-to-float"    ..Integer   ..Float]
-  [int_to_double   "jvm conversion int-to-double"   ..Integer   ..Double]
-  [int_to_char     "jvm conversion int-to-char"     ..Integer   ..Character]
-
-  [long_to_byte    "jvm conversion long-to-byte"    ..Long      ..Byte]
-  [long_to_short   "jvm conversion long-to-short"   ..Long      ..Short]
-  [long_to_int     "jvm conversion long-to-int"     ..Long      ..Integer]
-  [long_to_float   "jvm conversion long-to-float"   ..Long      ..Float]
-  [long_to_double  "jvm conversion long-to-double"  ..Long      ..Double]
-
-  [char_to_byte    "jvm conversion char-to-byte"    ..Character ..Byte]
-  [char_to_short   "jvm conversion char-to-short"   ..Character ..Short]
-  [char_to_int     "jvm conversion char-to-int"     ..Character ..Integer]
-  [char_to_long    "jvm conversion char-to-long"    ..Character ..Long]
+  [int_to_byte     .jvm_conversion_int_to_byte#     ..Integer   ..Byte]
+  [int_to_short    .jvm_conversion_int_to_short#    ..Integer   ..Short]
+  [int_to_long     .jvm_conversion_int_to_long#     ..Integer   ..Long]
+  [int_to_float    .jvm_conversion_int_to_float#    ..Integer   ..Float]
+  [int_to_double   .jvm_conversion_int_to_double#   ..Integer   ..Double]
+  [int_to_char     .jvm_conversion_int_to_char#     ..Integer   ..Character]
+
+  [long_to_byte    .jvm_conversion_long_to_byte#    ..Long      ..Byte]
+  [long_to_short   .jvm_conversion_long_to_short#   ..Long      ..Short]
+  [long_to_int     .jvm_conversion_long_to_int#     ..Long      ..Integer]
+  [long_to_float   .jvm_conversion_long_to_float#   ..Long      ..Float]
+  [long_to_double  .jvm_conversion_long_to_double#  ..Long      ..Double]
+
+  [char_to_byte    .jvm_conversion_char_to_byte#    ..Character ..Byte]
+  [char_to_short   .jvm_conversion_char_to_short#   ..Character ..Short]
+  [char_to_int     .jvm_conversion_char_to_int#     ..Character ..Integer]
+  [char_to_long    .jvm_conversion_char_to_long#    ..Character ..Long]
   )
 
 (with_template [   <0> <1>]
@@ -1043,16 +1041,15 @@
        .let [expected_arguments (list.size (the #method_inputs method))
              actual_arguments (list.size inputs)]]
       (if (n.= expected_arguments actual_arguments)
-        (in (list (` ("jvm member invoke special"
-                      [(,* (list#each (|>> ..signature code.text) super_vars))]
-                      (, (code.text super_name))
-                      (, (code.text (the #member_name member)))
-                      [(,* (list#each (|>> ..signature code.text) (the #method_tvars method)))]
-                      ("jvm object cast" (, self))
-                      (,* (|> inputs
-                              (list#each (|>> , "jvm object cast" `))
-                              (list.zipped_2 (the #method_inputs method))
-                              (list#each ..decorate_input)))))))
+        (in (list (` (.jvm_member_invoke_special# [(,* (list#each (|>> ..signature code.text) super_vars))]
+                                                  (, (code.text super_name))
+                                                  (, (code.text (the #member_name member)))
+                                                  [(,* (list#each (|>> ..signature code.text) (the #method_tvars method)))]
+                                                  (.jvm_object_cast# (, self))
+                                                  (,* (|> inputs
+                                                          (list#each (|>> , .jvm_object_cast# `))
+                                                          (list.zipped_2 (the #method_inputs method))
+                                                          (list#each ..decorate_input)))))))
         (meta.failure (exception.error ..insufficient_parameters [expected_arguments actual_arguments]))))))
 
 (.type Get|Set
@@ -1131,15 +1128,13 @@
         {.#Some [member {#VariableField _ static? :field:}]}
         (when [static? this]
           [.true {.#None}]
-          (in (list (` ("jvm member get static"
-                        (, (code.text class_name))
-                        (, (code.text (the #member_name member)))))))
+          (in (list (` (.jvm_member_get_static# (, (code.text class_name))
+                                                (, (code.text (the #member_name member)))))))
           
           [.false {.#Some this}]
-          (in (list (` ("jvm member get virtual"
-                        (, (code.text class_name))
-                        (, (code.text (the #member_name member)))
-                        (, this)))))
+          (in (list (` (.jvm_member_get_virtual# (, (code.text class_name))
+                                                 (, (code.text (the #member_name member)))
+                                                 (, this)))))
 
           _
           (meta.failure (exception.error ..cannot_get_field [class_name field])))
@@ -1166,17 +1161,15 @@
           _
           (when [static? this]
             [.true {.#None}]
-            (in (list (` ("jvm member put static"
-                          (, (code.text class_name))
-                          (, (code.text (the #member_name member)))
-                          (, value)))))
+            (in (list (` (.jvm_member_put_static# (, (code.text class_name))
+                                                  (, (code.text (the #member_name member)))
+                                                  (, value)))))
             
             [.false {.#Some this}]
-            (in (list (` ("jvm member put virtual"
-                          (, (code.text class_name))
-                          (, (code.text (the #member_name member)))
-                          (, value)
-                          (, this)))))
+            (in (list (` (.jvm_member_put_virtual# (, (code.text class_name))
+                                                   (, (code.text (the #member_name member)))
+                                                   (, value)
+                                                   (, this)))))
 
             _
             (meta.failure (exception.error ..cannot_set_field [class_name field]))))
@@ -1216,16 +1209,15 @@
         (let [expected_arguments (list.size (the #method_inputs method))
               actual_arguments (list.size inputs)]
           (if (n.= expected_arguments actual_arguments)
-            (in (list (` ("jvm member invoke virtual"
-                          [(,* (list#each (|>> ..signature code.text) class_vars))]
-                          (, (code.text class_name))
-                          (, (code.text (the #member_name member)))
-                          [(,* (list#each (|>> ..signature code.text) (the #method_tvars method)))]
-                          ("jvm object cast" (, self))
-                          (,* (|> inputs
-                                  (list#each (|>> , "jvm object cast" `))
-                                  (list.zipped_2 (the #method_inputs method))
-                                  (list#each ..decorate_input)))))))
+            (in (list (` (.jvm_member_invoke_virtual# [(,* (list#each (|>> ..signature code.text) class_vars))]
+                                                      (, (code.text class_name))
+                                                      (, (code.text (the #member_name member)))
+                                                      [(,* (list#each (|>> ..signature code.text) (the #method_tvars method)))]
+                                                      (.jvm_object_cast# (, self))
+                                                      (,* (|> inputs
+                                                              (list#each (|>> , .jvm_object_cast# `))
+                                                              (list.zipped_2 (the #method_inputs method))
+                                                              (list#each ..decorate_input)))))))
             (meta.failure (exception.error ..insufficient_parameters [expected_arguments actual_arguments]))))
 
         _
@@ -1369,14 +1361,13 @@
               methods (<>.some (..method_def^ class_vars))])
     (do meta.monad
       [methods (monad.each ! (method_def$ full_class_name class_vars super fields methods) methods)]
-      (in (list (` ("jvm class"
-                    (, (declaration$ (jvm.declaration full_class_name class_vars)))
-                    (, (class$ super))
-                    [(,* (list#each class$ interfaces))]
-                    (, (inheritance_modifier$ im))
-                    [(,* (list#each annotation$ annotations))]
-                    [(,* (list#each field_decl$ fields))]
-                    [(,* methods)])))))))
+      (in (list (` (.jvm_class# (, (declaration$ (jvm.declaration full_class_name class_vars)))
+                                (, (class$ super))
+                                [(,* (list#each class$ interfaces))]
+                                (, (inheritance_modifier$ im))
+                                [(,* (list#each annotation$ annotations))]
+                                [(,* (list#each field_decl$ fields))]
+                                [(,* methods)])))))))
 
 (def .public interface
   (syntax (_ [.let [! <>.monad]
@@ -1385,11 +1376,10 @@
                               (.tuple (<>.some (class^ class_vars))))
               annotations ..annotations^
               members (<>.some (..method_decl^ class_vars))])
-    (in (list (` ("jvm class interface"
-                  (, (declaration$ (jvm.declaration full_class_name class_vars)))
-                  [(,* (list#each class$ supers))]
-                  [(,* (list#each annotation$ annotations))]
-                  (,* (list#each method_decl$ members))))))))
+    (in (list (` (.jvm_class_interface# (, (declaration$ (jvm.declaration full_class_name class_vars)))
+                                        [(,* (list#each class$ supers))]
+                                        [(,* (list#each annotation$ annotations))]
+                                        (,* (list#each method_decl$ members))))))))
 
 (def .public object
   (syntax (_ [class_vars ..vars^
@@ -1401,26 +1391,25 @@
               methods (<>.some ..overriden_method_def^)])
     (do [! meta.monad]
       [methods (monad.each ! (method_def$ "" (list) super (list) methods) methods)]
-      (in (list (` ("jvm class anonymous"
-                    [(,* (list#each var$ class_vars))]
-                    (, (class$ super))
-                    [(,* (list#each class$ interfaces))]
-                    [(,* (list#each constructor_arg$ constructor_args))]
-                    [(,* methods)])))))))
+      (in (list (` (.jvm_class_anonymous# [(,* (list#each var$ class_vars))]
+                                          (, (class$ super))
+                                          [(,* (list#each class$ interfaces))]
+                                          [(,* (list#each constructor_arg$ constructor_args))]
+                                          [(,* methods)])))))))
 
 (def .public null
   (syntax (_ [])
-    (in (list (` ("jvm object null"))))))
+    (in (list (` (.jvm_object_null#))))))
 
 (def .public (null? obj)
   (-> (.Primitive "java.lang.Object") Bit)
-  ("jvm object null?" obj))
+  (.jvm_object_null?# obj))
 
 (def .public ???
   (syntax (_ [expr .any])
     (with_symbols [g!temp]
       (in (list (` (let [(, g!temp) (, expr)]
-                     (if (not ("jvm object null?" (, g!temp)))
+                     (if (not (.jvm_object_null?# (, g!temp)))
                        {.#Some (, g!temp)}
                        {.#None}))))))))
 
@@ -1432,7 +1421,7 @@
                      (, g!value)
 
                      {.#None}
-                     ("jvm object null"))))))))
+                     (.jvm_object_null#))))))))
 
 (def .public as
   (syntax (_ [class (..type^ (list))
@@ -1441,7 +1430,7 @@
       (let [class_name (..reflection class)
             class_type (` (.Primitive (, (code.text class_name))))
             check_type (` (.Maybe (, class_type)))
-            check_code (` (if ("jvm object instance?" (, (code.text class_name)) (, g!unchecked))
+            check_code (` (if (.jvm_object_instance?# (, (code.text class_name)) (, g!unchecked))
                             {.#Some (.as (, class_type)
                                          (, g!unchecked))}
                             {.#None}))]
@@ -1460,7 +1449,7 @@
 (def .public synchronized
   (syntax (_ [lock .any
               body .any])
-    (in (list (` ("jvm object synchronized" (, lock) (, body)))))))
+    (in (list (` (.jvm_object_synchronized# (, lock) (, body)))))))
 
 (def .public to
   (syntax (_ [obj .any
@@ -1584,7 +1573,7 @@
                                                  ... else
                                                  [unboxed
                                                   (if 
-                                                    (` ("jvm object cast" (, raw)))
+                                                    (` (.jvm_object_cast# (, raw)))
                                                     raw)
                                                   (list)]))))
            unboxed/boxed (when (dictionary.value unboxed ..boxes)
@@ -1683,13 +1672,12 @@
         [.let [classT (jvm.class full_name (list))
                def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
                jvm_interop (|> [classT
-                                (` ("jvm member invoke constructor"
-                                    [(,* (list#each ..var$ class_tvars))]
-                                    (, (code.text full_name))
-                                    [(,* (list#each ..var$ (the #import_member_tvars commons)))]
-                                    (,* (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs)
-                                            (list.zipped_2 input_jvm_types)
-                                            (list#each ..decorate_input)))))]
+                                (` (.jvm_member_invoke_constructor# [(,* (list#each ..var$ class_tvars))]
+                                                                    (, (code.text full_name))
+                                                                    [(,* (list#each ..var$ (the #import_member_tvars commons)))]
+                                                                    (,* (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs)
+                                                                            (list.zipped_2 input_jvm_types)
+                                                                            (list#each ..decorate_input)))))]
                                (with_automatic_output_conversion (the #import_member_mode commons))
                                (with_return_maybe member true classT)
                                (with_return_try member)
@@ -1704,25 +1692,25 @@
           [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
                  (open "[0]") commons
                  (open "[0]") method
-                 [jvm_op object_ast] (.is [Text (List Code)]
+                 [jvm_op object_ast] (.is [Code (List Code)]
                                           (when #import_member_kind
                                             {#StaticIMK}
-                                            ["jvm member invoke static"
+                                            [(` .jvm_member_invoke_static#)
                                              (list)]
 
                                             {#VirtualIMK}
                                             (when kind
                                               {#Class}
-                                              ["jvm member invoke virtual"
+                                              [(` .jvm_member_invoke_virtual#)
                                                (list g!obj)]
                                               
                                               {#Interface}
-                                              ["jvm member invoke interface"
+                                              [(` .jvm_member_invoke_interface#)
                                                (list g!obj)]
                                               )))
                  method_return (the #import_method_return method)
                  callC (.is Code
-                            (` ((, (code.text jvm_op))
+                            (` ((, jvm_op)
                                 [(,* (list#each ..var$ class_tvars))]
                                 (, (code.text full_name))
                                 (, (code.text #import_method_name))
@@ -1776,7 +1764,7 @@
                     setter_value (if _#import_field_maybe?
                                    (` (!!! (, setter_value)))
                                    setter_value)
-                    setter_command (if _#import_field_static? "jvm member put static" "jvm member put virtual")
+                    setter_command (if _#import_field_static? (` .jvm_member_put_static#) (` .jvm_member_put_virtual#))
                     g!obj+ (.is (List Code)
                                 (if _#import_field_static?
                                   (list)
@@ -1794,7 +1782,7 @@
                                   (` {.#Left [(, g!value)]})
                                   (` {.#Left [(, g!value) (, g!obj)]}))
                                 (if _#import_field_setter?
-                                  (` ((,' in) (.list (.` (io.io ((, (code.text setter_command))
+                                  (` ((,' in) (.list (.` (io.io ((, setter_command)
                                                                  (, (code.text full_name))
                                                                  (, (code.text _#import_field_name))
                                                                  (, setter_value)
@@ -1821,8 +1809,8 @@
 
 (def interface?
   (All (_ a) (-> (.Primitive "java.lang.Class" [a]) Bit))
-  (|>> ("jvm member invoke virtual" [] "java.lang.Class" "isInterface" [])
-       "jvm object cast"
+  (|>> (.jvm_member_invoke_virtual# [] "java.lang.Class" "isInterface" [])
+       .jvm_object_cast#
        (.is ..Boolean)
        (.as Bit)))
 
@@ -1830,7 +1818,7 @@
   (-> External (Try (.Primitive "java.lang.Class" [Any])))
   (|>> (.as (.Primitive "java.lang.String"))
        ["Ljava/lang/String;"]
-       ("jvm member invoke static" [] "java.lang.Class" "forName" [])
+       (.jvm_member_invoke_static# [] "java.lang.Class" "forName" [])
        try))
 
 (def (class_kind declaration)
@@ -1863,24 +1851,24 @@
     (let [g!size (` (|> (, size)
                         (.is .Nat)
                         (.as (.Primitive (, (code.text box.long))))
-                        "jvm object cast"
-                        "jvm conversion long-to-int"))]
+                        .jvm_object_cast#
+                        .jvm_conversion_long_to_int#))]
       (`` (cond (,, (with_template [ ]
                       [(at jvm.equivalence =  type)
                        (in (list (` ( (, g!size)))))]
 
-                      [jvm.boolean "jvm array new boolean"]
-                      [jvm.byte    "jvm array new byte"]
-                      [jvm.short   "jvm array new short"]
-                      [jvm.int     "jvm array new int"]
-                      [jvm.long    "jvm array new long"]
-                      [jvm.float   "jvm array new float"]
-                      [jvm.double  "jvm array new double"]
-                      [jvm.char    "jvm array new char"]))
+                      [jvm.boolean .jvm_array_new_boolean#]
+                      [jvm.byte    .jvm_array_new_byte#]
+                      [jvm.short   .jvm_array_new_short#]
+                      [jvm.int     .jvm_array_new_int#]
+                      [jvm.long    .jvm_array_new_long#]
+                      [jvm.float   .jvm_array_new_float#]
+                      [jvm.double  .jvm_array_new_double#]
+                      [jvm.char    .jvm_array_new_char#]))
                 ... else
                 (in (list (` (.as (array.Array (, (value_type {#ManualPrM} type)))
                                   (.is (, (value_type {#ManualPrM} (jvm.array type)))
-                                       ("jvm array new object" (, g!size))))))))))))
+                                       (.jvm_array_new_object# (, g!size))))))))))))
 
 (exception.def .public (cannot_convert_to_jvm_type type)
   (Exception .Type)
@@ -1994,26 +1982,26 @@
         [array_type (meta.type array_name)
          context meta.type_context
          array_jvm_type (lux_type->jvm_type context array_type)
-         .let [g!extension (code.text (`` (cond (,, (with_template [ ]
-                                                      [(at jvm.equivalence =
-                                                           (jvm.array )
-                                                           array_jvm_type)
-                                                       ]
-
-                                                      [jvm.boolean "jvm array length boolean"]
-                                                      [jvm.byte "jvm array length byte"]
-                                                      [jvm.short "jvm array length short"]
-                                                      [jvm.int "jvm array length int"]
-                                                      [jvm.long "jvm array length long"]
-                                                      [jvm.float "jvm array length float"]
-                                                      [jvm.double "jvm array length double"]
-                                                      [jvm.char "jvm array length char"]))
-                                                
-                                                ... else
-                                                "jvm array length object")))]]
+         .let [g!extension (`` (cond (,, (with_template [ ]
+                                           [(at jvm.equivalence =
+                                                (jvm.array )
+                                                array_jvm_type)
+                                            (` )]
+
+                                           [jvm.boolean .jvm_array_length_boolean#]
+                                           [jvm.byte .jvm_array_length_byte#]
+                                           [jvm.short .jvm_array_length_short#]
+                                           [jvm.int .jvm_array_length_int#]
+                                           [jvm.long .jvm_array_length_long#]
+                                           [jvm.float .jvm_array_length_float#]
+                                           [jvm.double .jvm_array_length_double#]
+                                           [jvm.char .jvm_array_length_char#]))
+                                     
+                                     ... else
+                                     (` .jvm_array_length_object#)))]]
         (in (list (` (.|> ((, g!extension) (, array))
-                          "jvm conversion int-to-long"
-                          "jvm object cast"
+                          .jvm_conversion_int_to_long#
+                          .jvm_object_cast#
                           (.is (.Primitive (, (code.text box.long))))
                           (.as .Nat))))))
 
@@ -2034,27 +2022,27 @@
          .let [g!idx (` (.|> (, idx)
                              (.is .Nat)
                              (.as (.Primitive (, (code.text box.long))))
-                             "jvm object cast"
-                             "jvm conversion long-to-int"))]]
+                             .jvm_object_cast#
+                             .jvm_conversion_long_to_int#))]]
         (`` (cond (,, (with_template [  ]
                         [(at jvm.equivalence =
                              (jvm.array )
                              array_jvm_type)
                          (in (list (` (.|> ( (, g!idx) (, array))
-                                           "jvm object cast"
+                                           .jvm_object_cast#
                                            (.is (.Primitive (, (code.text ))))))))]
 
-                        [jvm.boolean "jvm array read boolean" box.boolean]
-                        [jvm.byte "jvm array read byte" box.byte]
-                        [jvm.short "jvm array read short" box.short]
-                        [jvm.int "jvm array read int" box.int]
-                        [jvm.long "jvm array read long" box.long]
-                        [jvm.float "jvm array read float" box.float]
-                        [jvm.double "jvm array read double" box.double]
-                        [jvm.char "jvm array read char" box.char]))
+                        [jvm.boolean .jvm_array_read_boolean# box.boolean]
+                        [jvm.byte .jvm_array_read_byte# box.byte]
+                        [jvm.short .jvm_array_read_short# box.short]
+                        [jvm.int .jvm_array_read_int# box.int]
+                        [jvm.long .jvm_array_read_long# box.long]
+                        [jvm.float .jvm_array_read_float# box.float]
+                        [jvm.double .jvm_array_read_double# box.double]
+                        [jvm.char .jvm_array_read_char# box.char]))
                   
                   ... else
-                  (in (list (` ("jvm array read object" (, g!idx) (, array))))))))
+                  (in (list (` (.jvm_array_read_object# (, g!idx) (, array))))))))
 
       _
       (with_symbols [g!array]
@@ -2074,28 +2062,28 @@
          .let [g!idx (` (.|> (, idx)
                              (.is .Nat)
                              (.as (.Primitive (, (code.text box.long))))
-                             "jvm object cast"
-                             "jvm conversion long-to-int"))]]
+                             .jvm_object_cast#
+                             .jvm_conversion_long_to_int#))]]
         (`` (cond (,, (with_template [  ]
                         [(at jvm.equivalence =
                              (jvm.array )
                              array_jvm_type)
                          (let [g!value (` (.|> (, value)
                                                (.as (.Primitive (, (code.text ))))
-                                               "jvm object cast"))]
+                                               .jvm_object_cast#))]
                            (in (list (` ( (, g!idx) (, g!value) (, array))))))]
 
-                        [jvm.boolean "jvm array write boolean" box.boolean]
-                        [jvm.byte "jvm array write byte" box.byte]
-                        [jvm.short "jvm array write short" box.short]
-                        [jvm.int "jvm array write int" box.int]
-                        [jvm.long "jvm array write long" box.long]
-                        [jvm.float "jvm array write float" box.float]
-                        [jvm.double "jvm array write double" box.double]
-                        [jvm.char "jvm array write char" box.char]))
+                        [jvm.boolean .jvm_array_write_boolean# box.boolean]
+                        [jvm.byte .jvm_array_write_byte# box.byte]
+                        [jvm.short .jvm_array_write_short# box.short]
+                        [jvm.int .jvm_array_write_int# box.int]
+                        [jvm.long .jvm_array_write_long# box.long]
+                        [jvm.float .jvm_array_write_float# box.float]
+                        [jvm.double .jvm_array_write_double# box.double]
+                        [jvm.char .jvm_array_write_char# box.char]))
                   
                   ... else
-                  (in (list (` ("jvm array write object" (, g!idx) (, value) (, array))))))))
+                  (in (list (` (.jvm_array_write_object# (, g!idx) (, value) (, array))))))))
 
       _
       (with_symbols [g!array]
@@ -2104,7 +2092,7 @@
 
 (def .public class_for
   (syntax (_ [type (..type^ (list))])
-    (in (list (` ("jvm object class" (, (code.text (..reflection type)))))))))
+    (in (list (` (.jvm_object_class# (, (code.text (..reflection type)))))))))
 
 (def .public type
   (syntax (_ [type (..type^ (list))])
@@ -2123,7 +2111,7 @@
            (parser.class? type)]
       (^.or [{.#Some _} _] [_ {.#Some _}])
       (in (list (` (.is (, (..value_type {#ManualPrM} type))
-                        ("jvm object cast" (, object))))))
+                        (.jvm_object_cast# (, object))))))
 
       _
       (meta.failure (exception.error ..cannot_cast_to_non_object [type])))))
diff --git a/stdlib/source/library/lux/ffi/export.jvm.lux b/stdlib/source/library/lux/ffi/export.jvm.lux
index af5ab079a..50f87df09 100644
--- a/stdlib/source/library/lux/ffi/export.jvm.lux
+++ b/stdlib/source/library/lux/ffi/export.jvm.lux
@@ -100,9 +100,8 @@
                      ("public" "strict" "static" [] ((,' ) [])
                       (,' void)
                       [(,* (list#each (.function (_ [name type term])
-                                        (` ("jvm member put static"
-                                            (, (code.text api))
-                                            (, (code.text name))
-                                            ("jvm object cast" (, term)))))
+                                        (` (.jvm_member_put_static# (, (code.text api))
+                                                                    (, (code.text name))
+                                                                    (.jvm_object_cast# (, term)))))
                                       initialization))])
                      )))))))
diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux
index 80eacae5d..a25106d63 100644
--- a/stdlib/source/library/lux/math/number/frac.lux
+++ b/stdlib/source/library/lux/math/number/frac.lux
@@ -66,12 +66,12 @@
               (template (_ value)
                 [(|> value
                      (as (Primitive "java.lang.Double"))
-                     "jvm object cast")]))
+                     .jvm_object_cast#)]))
             
             (def !frac
               (template (_ value)
                 [(|> value
-                     "jvm object cast"
+                     .jvm_object_cast#
                      (is (Primitive "java.lang.Double"))
                      (as Frac))]))
             
@@ -80,7 +80,7 @@
                  (-> Frac Frac)
                  (|>> !double
                       ["D"]
-                      ("jvm member invoke static" [] "java.lang.Math"  [])
+                      (.jvm_member_invoke_static# [] "java.lang.Math"  [])
                       !frac))]
 
               [cos    "cos"]
@@ -103,8 +103,8 @@
             
             (def .public (pow param subject)
               (-> Frac Frac Frac)
-              (|> ("jvm member invoke static" [] "java.lang.Math" "pow" []
-                   ["D" (!double subject)] ["D" (!double param)])
+              (|> (.jvm_member_invoke_static# [] "java.lang.Math" "pow" []
+                                              ["D" (!double subject)] ["D" (!double param)])
                   !frac)))
 
      @.js
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
index d9c81c517..4b118d972 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -298,84 +298,79 @@
   [unknown_type_var]
   )
 
-(def bundle::conversion
-  Bundle
-  (<| (///bundle.prefix "conversion")
-      (|> ///bundle.empty
-          (///bundle.install "double-to-float" (//lux.unary ..double ..float))
-          (///bundle.install "double-to-int" (//lux.unary ..double ..int))
-          (///bundle.install "double-to-long" (//lux.unary ..double ..long))
-          (///bundle.install "float-to-double" (//lux.unary ..float ..double))
-          (///bundle.install "float-to-int" (//lux.unary ..float ..int))
-          (///bundle.install "float-to-long" (//lux.unary ..float ..long))
-          (///bundle.install "int-to-byte" (//lux.unary ..int ..byte))
-          (///bundle.install "int-to-char" (//lux.unary ..int ..char))
-          (///bundle.install "int-to-double" (//lux.unary ..int ..double))
-          (///bundle.install "int-to-float" (//lux.unary ..int ..float))
-          (///bundle.install "int-to-long" (//lux.unary ..int ..long))
-          (///bundle.install "int-to-short" (//lux.unary ..int ..short))
-          (///bundle.install "long-to-double" (//lux.unary ..long ..double))
-          (///bundle.install "long-to-float" (//lux.unary ..long ..float))
-          (///bundle.install "long-to-int" (//lux.unary ..long ..int))
-          (///bundle.install "long-to-short" (//lux.unary ..long ..short))
-          (///bundle.install "long-to-byte" (//lux.unary ..long ..byte))
-          (///bundle.install "char-to-byte" (//lux.unary ..char ..byte))
-          (///bundle.install "char-to-short" (//lux.unary ..char ..short))
-          (///bundle.install "char-to-int" (//lux.unary ..char ..int))
-          (///bundle.install "char-to-long" (//lux.unary ..char ..long))
-          (///bundle.install "byte-to-long" (//lux.unary ..byte ..long))
-          (///bundle.install "short-to-long" (//lux.unary ..short ..long))
-          )))
+(def with_conversion_extensions
+  (-> Bundle Bundle)
+  (|>> (///bundle.install "jvm_conversion_double_to_float#" (//lux.unary ..double ..float))
+       (///bundle.install "jvm_conversion_double_to_int#" (//lux.unary ..double ..int))
+       (///bundle.install "jvm_conversion_double_to_long#" (//lux.unary ..double ..long))
+       (///bundle.install "jvm_conversion_float_to_double#" (//lux.unary ..float ..double))
+       (///bundle.install "jvm_conversion_float_to_int#" (//lux.unary ..float ..int))
+       (///bundle.install "jvm_conversion_float_to_long#" (//lux.unary ..float ..long))
+       (///bundle.install "jvm_conversion_int_to_byte#" (//lux.unary ..int ..byte))
+       (///bundle.install "jvm_conversion_int_to_char#" (//lux.unary ..int ..char))
+       (///bundle.install "jvm_conversion_int_to_double#" (//lux.unary ..int ..double))
+       (///bundle.install "jvm_conversion_int_to_float#" (//lux.unary ..int ..float))
+       (///bundle.install "jvm_conversion_int_to_long#" (//lux.unary ..int ..long))
+       (///bundle.install "jvm_conversion_int_to_short#" (//lux.unary ..int ..short))
+       (///bundle.install "jvm_conversion_long_to_double#" (//lux.unary ..long ..double))
+       (///bundle.install "jvm_conversion_long_to_float#" (//lux.unary ..long ..float))
+       (///bundle.install "jvm_conversion_long_to_int#" (//lux.unary ..long ..int))
+       (///bundle.install "jvm_conversion_long_to_short#" (//lux.unary ..long ..short))
+       (///bundle.install "jvm_conversion_long_to_byte#" (//lux.unary ..long ..byte))
+       (///bundle.install "jvm_conversion_char_to_byte#" (//lux.unary ..char ..byte))
+       (///bundle.install "jvm_conversion_char_to_short#" (//lux.unary ..char ..short))
+       (///bundle.install "jvm_conversion_char_to_int#" (//lux.unary ..char ..int))
+       (///bundle.install "jvm_conversion_char_to_long#" (//lux.unary ..char ..long))
+       (///bundle.install "jvm_conversion_byte_to_long#" (//lux.unary ..byte ..long))
+       (///bundle.install "jvm_conversion_short_to_long#" (//lux.unary ..short ..long))
+       ))
 
 (with_template [  ]
   [(def 
-     Bundle
-     (<| (///bundle.prefix (reflection.reflection ))
-         (|> ///bundle.empty
-             (///bundle.install "+" (//lux.binary   ))
-             (///bundle.install "-" (//lux.binary   ))
-             (///bundle.install "*" (//lux.binary   ))
-             (///bundle.install "/" (//lux.binary   ))
-             (///bundle.install "%" (//lux.binary   ))
-             (///bundle.install "=" (//lux.binary   Bit))
-             (///bundle.install "<" (//lux.binary   Bit))
-             (///bundle.install "and" (//lux.binary   ))
-             (///bundle.install "or" (//lux.binary   ))
-             (///bundle.install "xor" (//lux.binary   ))
-             (///bundle.install "shl" (//lux.binary ..int  ))
-             (///bundle.install "shr" (//lux.binary ..int  ))
-             (///bundle.install "ushr" (//lux.binary ..int  ))
-             )))]
-
-  [bundle::int  reflection.int  ..int]
-  [bundle::long reflection.long ..long]
+     (-> Bundle Bundle)
+     (let [type (reflection.reflection )]
+       (|>> (///bundle.install (%.format "jvm_" type "_" "+" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "-" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "*" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "/" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "%" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "=" "#") (//lux.binary   Bit))
+            (///bundle.install (%.format "jvm_" type "_" "<" "#") (//lux.binary   Bit))
+            (///bundle.install (%.format "jvm_" type "_" "and" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "or" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "xor" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "shl" "#") (//lux.binary ..int  ))
+            (///bundle.install (%.format "jvm_" type "_" "shr" "#") (//lux.binary ..int  ))
+            (///bundle.install (%.format "jvm_" type "_" "ushr" "#") (//lux.binary ..int  ))
+            )))]
+
+  [with_int_extensions  reflection.int  ..int]
+  [with_long_extensions reflection.long ..long]
   )
 
 (with_template [  ]
   [(def 
-     Bundle
-     (<| (///bundle.prefix (reflection.reflection ))
-         (|> ///bundle.empty
-             (///bundle.install "+" (//lux.binary   ))
-             (///bundle.install "-" (//lux.binary   ))
-             (///bundle.install "*" (//lux.binary   ))
-             (///bundle.install "/" (//lux.binary   ))
-             (///bundle.install "%" (//lux.binary   ))
-             (///bundle.install "=" (//lux.binary   Bit))
-             (///bundle.install "<" (//lux.binary   Bit))
-             )))]
-
-  [bundle::float  reflection.float  ..float]
-  [bundle::double reflection.double ..double]
+     (-> Bundle Bundle)
+     (let [type (reflection.reflection )]
+       (|>> (///bundle.install (%.format "jvm_" type "_" "+" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "-" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "*" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "/" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "%" "#") (//lux.binary   ))
+            (///bundle.install (%.format "jvm_" type "_" "=" "#") (//lux.binary   Bit))
+            (///bundle.install (%.format "jvm_" type "_" "<" "#") (//lux.binary   Bit))
+            )))]
+
+  [with_float_extensions  reflection.float  ..float]
+  [with_double_extensions reflection.double ..double]
   )
 
-(def bundle::char
-  Bundle
-  (<| (///bundle.prefix (reflection.reflection reflection.char))
-      (|> ///bundle.empty
-          (///bundle.install "=" (//lux.binary ..char ..char Bit))
-          (///bundle.install "<" (//lux.binary ..char ..char Bit))
-          )))
+(def with_char_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.char)]
+    (|>> (///bundle.install (%.format "jvm_" type "_" "=" "#") (//lux.binary ..char ..char Bit))
+         (///bundle.install (%.format "jvm_" type "_" "<" "#") (//lux.binary ..char ..char Bit))
+         )))
 
 (def .public boxes
   (Dictionary External [External (Type Primitive)])
@@ -791,55 +786,48 @@
       _
       (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)]))))
 
-(def bundle::array
-  Bundle
-  (<| (///bundle.prefix "array")
-      (|> ///bundle.empty
-          (dictionary.composite (<| (///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.composite (<| (///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.composite (<| (///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.composite (<| (///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 with_array_extensions
+  (-> Bundle Bundle)
+  (|>> (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.boolean) "#") (primitive_array_length_handler jvm.boolean))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.byte) "#") (primitive_array_length_handler jvm.byte))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.short) "#") (primitive_array_length_handler jvm.short))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.int) "#") (primitive_array_length_handler jvm.int))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.long) "#") (primitive_array_length_handler jvm.long))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.float) "#") (primitive_array_length_handler jvm.float))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.double) "#") (primitive_array_length_handler jvm.double))
+       (///bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.char) "#") (primitive_array_length_handler jvm.char))
+       (///bundle.install (%.format "jvm_" "array_" "length_" "object" "#") array::length::object)
+
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.boolean) "#") (new_primitive_array_handler jvm.boolean))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.byte) "#") (new_primitive_array_handler jvm.byte))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.short) "#") (new_primitive_array_handler jvm.short))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.int) "#") (new_primitive_array_handler jvm.int))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.long) "#") (new_primitive_array_handler jvm.long))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.float) "#") (new_primitive_array_handler jvm.float))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.double) "#") (new_primitive_array_handler jvm.double))
+       (///bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.char) "#") (new_primitive_array_handler jvm.char))
+       (///bundle.install (%.format "jvm_" "array_" "new_" "object" "#") array::new::object)
+
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.boolean) "#") (read_primitive_array_handler ..boolean jvm.boolean))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.byte) "#") (read_primitive_array_handler ..byte jvm.byte))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.short) "#") (read_primitive_array_handler ..short jvm.short))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.int) "#") (read_primitive_array_handler ..int jvm.int))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.long) "#") (read_primitive_array_handler ..long jvm.long))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.float) "#") (read_primitive_array_handler ..float jvm.float))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.double) "#") (read_primitive_array_handler ..double jvm.double))
+       (///bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.char) "#") (read_primitive_array_handler ..char jvm.char))
+       (///bundle.install (%.format "jvm_" "array_" "read_" "object" "#") array::read::object)
+
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.boolean) "#") (write_primitive_array_handler ..boolean jvm.boolean))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.byte) "#") (write_primitive_array_handler ..byte jvm.byte))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.short) "#") (write_primitive_array_handler ..short jvm.short))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.int) "#") (write_primitive_array_handler ..int jvm.int))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.long) "#") (write_primitive_array_handler ..long jvm.long))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.float) "#") (write_primitive_array_handler ..float jvm.float))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.double) "#") (write_primitive_array_handler ..double jvm.double))
+       (///bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.char) "#") (write_primitive_array_handler ..char jvm.char))
+       (///bundle.install (%.format "jvm_" "array_" "write_" "object" "#") array::write::object)
+       ))
 
 (def object::null
   Handler
@@ -1041,18 +1029,16 @@
       _
       (/////analysis.except ///.invalid_syntax [extension_name %.code args]))))
 
-(def (bundle::object class_loader)
-  (-> java/lang/ClassLoader Bundle)
-  (<| (///bundle.prefix "object")
-      (|> ///bundle.empty
-          (///bundle.install "null" object::null)
-          (///bundle.install "null?" object::null?)
-          (///bundle.install "synchronized" object::synchronized)
-          (///bundle.install "throw" (object::throw class_loader))
-          (///bundle.install "class" (object::class class_loader))
-          (///bundle.install "instance?" (object::instance? class_loader))
-          (///bundle.install "cast" (object::cast class_loader))
-          )))
+(def (with_object_extensions class_loader)
+  (-> java/lang/ClassLoader (-> Bundle Bundle))
+  (|>> (///bundle.install (%.format "jvm_" "object_" "null" "#") object::null)
+       (///bundle.install (%.format "jvm_" "object_" "null?" "#") object::null?)
+       (///bundle.install (%.format "jvm_" "object_" "synchronized" "#") object::synchronized)
+       (///bundle.install (%.format "jvm_" "object_" "throw" "#") (object::throw class_loader))
+       (///bundle.install (%.format "jvm_" "object_" "class" "#") (object::class class_loader))
+       (///bundle.install (%.format "jvm_" "object_" "instance?" "#") (object::instance? class_loader))
+       (///bundle.install (%.format "jvm_" "object_" "cast" "#") (object::cast class_loader))
+       ))
 
 (def (get::static class_loader)
   (-> java/lang/ClassLoader Handler)
@@ -1636,27 +1622,20 @@
                                       (list.partial (/////analysis.text (..signature (jvm.class class (list))))
                                                     (decorate_inputs argsT argsA))})))]))
 
-(def (bundle::member class_loader)
-  (-> java/lang/ClassLoader Bundle)
-  (<| (///bundle.prefix "member")
-      (|> ///bundle.empty
-          (dictionary.composite (<| (///bundle.prefix "get")
-                                    (|> ///bundle.empty
-                                        (///bundle.install "static" (get::static class_loader))
-                                        (///bundle.install "virtual" (get::virtual class_loader)))))
-          (dictionary.composite (<| (///bundle.prefix "put")
-                                    (|> ///bundle.empty
-                                        (///bundle.install "static" (put::static class_loader))
-                                        (///bundle.install "virtual" (put::virtual class_loader)))))
-          (dictionary.composite (<| (///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))
-                                        )))
-          )))
+(def (with_member_extensions class_loader)
+  (-> java/lang/ClassLoader (-> Bundle Bundle))
+  (|>> (///bundle.install "jvm_member_get_static#" (get::static class_loader))
+       (///bundle.install "jvm_member_get_virtual#" (get::virtual class_loader))
+       
+       (///bundle.install "jvm_member_put_static#" (put::static class_loader))
+       (///bundle.install "jvm_member_put_virtual#" (put::virtual class_loader))
+       
+       (///bundle.install "jvm_member_invoke_static#" (invoke::static class_loader))
+       (///bundle.install "jvm_member_invoke_virtual#" (invoke::virtual class_loader))
+       (///bundle.install "jvm_member_invoke_special#" (invoke::special class_loader))
+       (///bundle.install "jvm_member_invoke_interface#" (invoke::interface class_loader))
+       (///bundle.install "jvm_member_invoke_constructor#" (invoke::constructor class_loader))
+       ))
 
 (.type .public (Annotation_Parameter a)
   [Text a])
@@ -2734,25 +2713,20 @@
                                             (/////analysis.tuple (list#each typed_analysis constructor_argsA+))
                                             (/////analysis.tuple methodsA))})))]))
 
-(def (bundle::class class_loader host)
-  (-> java/lang/ClassLoader runtime.Host Bundle)
-  (<| (///bundle.prefix "class")
-      (|> ///bundle.empty
-          (///bundle.install "anonymous" (class::anonymous class_loader host))
-          )))
+(def (with_class_extensions class_loader host)
+  (-> java/lang/ClassLoader runtime.Host (-> Bundle Bundle))
+  (///bundle.install (%.format "jvm_" "class_" "anonymous" "#") (class::anonymous class_loader host)))
 
 (def .public (bundle class_loader host)
   (-> java/lang/ClassLoader runtime.Host Bundle)
-  (<| (///bundle.prefix "jvm")
-      (|> ///bundle.empty
-          (dictionary.composite bundle::conversion)
-          (dictionary.composite bundle::int)
-          (dictionary.composite bundle::long)
-          (dictionary.composite bundle::float)
-          (dictionary.composite bundle::double)
-          (dictionary.composite bundle::char)
-          (dictionary.composite bundle::array)
-          (dictionary.composite (bundle::object class_loader))
-          (dictionary.composite (bundle::member class_loader))
-          (dictionary.composite (bundle::class class_loader host))
-          )))
+  (<| with_conversion_extensions
+      with_int_extensions
+      with_long_extensions
+      with_float_extensions
+      with_double_extensions
+      with_char_extensions
+      with_array_extensions
+      (with_object_extensions class_loader)
+      (with_member_extensions class_loader)
+      (with_class_extensions class_loader host)
+      ///bundle.empty))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
index 02f45f8e9..f32eabad5 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
@@ -970,8 +970,7 @@
 
 (def .public (bundle class_loader extender)
   (-> java/lang/ClassLoader Extender (Bundle Anchor (Bytecode Any) Definition))
-  (<| (bundle.prefix "jvm")
-      (|> bundle.empty
-          (dictionary.has "class" jvm::class)
-          (dictionary.has "class interface" ..jvm::class::interface)
-          )))
+  (|> bundle.empty
+      (dictionary.has (%.format "jvm_" "class" "#") jvm::class)
+      (dictionary.has (%.format "jvm_" "class_" "interface" "#") ..jvm::class::interface)
+      ))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/generation/jvm/host.lux
index f74e4c823..18981ce1c 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/generation/jvm/host.lux
@@ -134,41 +134,39 @@
   [_.i2l conversion::short_to_long]
   )
 
-(def bundle::conversion
-  Bundle
-  (<| (/////bundle.prefix "conversion")
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "double-to-float|generation" (unary conversion::double_to_float))
-          (/////bundle.install "double-to-int|generation" (unary conversion::double_to_int))
-          (/////bundle.install "double-to-long|generation" (unary conversion::double_to_long))
-          
-          (/////bundle.install "float-to-double|generation" (unary conversion::float_to_double))
-          (/////bundle.install "float-to-int|generation" (unary conversion::float_to_int))
-          (/////bundle.install "float-to-long|generation" (unary conversion::float_to_long))
-          
-          (/////bundle.install "int-to-byte|generation" (unary conversion::int_to_byte))
-          (/////bundle.install "int-to-char|generation" (unary conversion::int_to_char))
-          (/////bundle.install "int-to-double|generation" (unary conversion::int_to_double))
-          (/////bundle.install "int-to-float|generation" (unary conversion::int_to_float))
-          (/////bundle.install "int-to-long|generation" (unary conversion::int_to_long))
-          (/////bundle.install "int-to-short|generation" (unary conversion::int_to_short))
-          
-          (/////bundle.install "long-to-double|generation" (unary conversion::long_to_double))
-          (/////bundle.install "long-to-float|generation" (unary conversion::long_to_float))
-          (/////bundle.install "long-to-int|generation" (unary conversion::long_to_int))
-          (/////bundle.install "long-to-short|generation" (unary conversion::long_to_short))
-          (/////bundle.install "long-to-byte|generation" (unary conversion::long_to_byte))
-          (/////bundle.install "long-to-char|generation" (unary conversion::long_to_char))
-          
-          (/////bundle.install "char-to-byte|generation" (unary conversion::char_to_byte))
-          (/////bundle.install "char-to-short|generation" (unary conversion::char_to_short))
-          (/////bundle.install "char-to-int|generation" (unary conversion::char_to_int))
-          (/////bundle.install "char-to-long|generation" (unary conversion::char_to_long))
-          
-          (/////bundle.install "byte-to-long|generation" (unary conversion::byte_to_long))
-          
-          (/////bundle.install "short-to-long|generation" (unary conversion::short_to_long))
-          )))
+(def with_conversion_extensions
+  (-> Bundle Bundle)
+  (|>> (/////bundle.install (%.format "jvm_" "conversion_" "double_to_float" "#" "|generation") (unary conversion::double_to_float))
+       (/////bundle.install (%.format "jvm_" "conversion_" "double_to_int" "#" "|generation") (unary conversion::double_to_int))
+       (/////bundle.install (%.format "jvm_" "conversion_" "double_to_long" "#" "|generation") (unary conversion::double_to_long))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "float_to_double" "#" "|generation") (unary conversion::float_to_double))
+       (/////bundle.install (%.format "jvm_" "conversion_" "float_to_int" "#" "|generation") (unary conversion::float_to_int))
+       (/////bundle.install (%.format "jvm_" "conversion_" "float_to_long" "#" "|generation") (unary conversion::float_to_long))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_byte" "#" "|generation") (unary conversion::int_to_byte))
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_char" "#" "|generation") (unary conversion::int_to_char))
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_double" "#" "|generation") (unary conversion::int_to_double))
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_float" "#" "|generation") (unary conversion::int_to_float))
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_long" "#" "|generation") (unary conversion::int_to_long))
+       (/////bundle.install (%.format "jvm_" "conversion_" "int_to_short" "#" "|generation") (unary conversion::int_to_short))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_double" "#" "|generation") (unary conversion::long_to_double))
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_float" "#" "|generation") (unary conversion::long_to_float))
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_int" "#" "|generation") (unary conversion::long_to_int))
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_short" "#" "|generation") (unary conversion::long_to_short))
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_byte" "#" "|generation") (unary conversion::long_to_byte))
+       (/////bundle.install (%.format "jvm_" "conversion_" "long_to_char" "#" "|generation") (unary conversion::long_to_char))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "char_to_byte" "#" "|generation") (unary conversion::char_to_byte))
+       (/////bundle.install (%.format "jvm_" "conversion_" "char_to_short" "#" "|generation") (unary conversion::char_to_short))
+       (/////bundle.install (%.format "jvm_" "conversion_" "char_to_int" "#" "|generation") (unary conversion::char_to_int))
+       (/////bundle.install (%.format "jvm_" "conversion_" "char_to_long" "#" "|generation") (unary conversion::char_to_long))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "byte_to_long" "#" "|generation") (unary conversion::byte_to_long))
+       
+       (/////bundle.install (%.format "jvm_" "conversion_" "short_to_long" "#" "|generation") (unary conversion::short_to_long))
+       ))
 
 (with_template [ ]
   [(def ( [parameter! subject!])
@@ -270,77 +268,72 @@
   [double::< _.dcmpg -1]
   )
 
-(def bundle::int
-  Bundle
-  (<| (/////bundle.prefix (reflection.reflection reflection.int))
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "+|generation" (binary int::+))
-          (/////bundle.install "-|generation" (binary int::-))
-          (/////bundle.install "*|generation" (binary int::*))
-          (/////bundle.install "/|generation" (binary int::/))
-          (/////bundle.install "%|generation" (binary int::%))
-          (/////bundle.install "=|generation" (binary int::=))
-          (/////bundle.install "<|generation" (binary int::<))
-          (/////bundle.install "and|generation" (binary int::and))
-          (/////bundle.install "or|generation" (binary int::or))
-          (/////bundle.install "xor|generation" (binary int::xor))
-          (/////bundle.install "shl|generation" (binary int::shl))
-          (/////bundle.install "shr|generation" (binary int::shr))
-          (/////bundle.install "ushr|generation" (binary int::ushr))
-          )))
-
-(def bundle::long
-  Bundle
-  (<| (/////bundle.prefix (reflection.reflection reflection.long))
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "+|generation" (binary long::+))
-          (/////bundle.install "-|generation" (binary long::-))
-          (/////bundle.install "*|generation" (binary long::*))
-          (/////bundle.install "/|generation" (binary long::/))
-          (/////bundle.install "%|generation" (binary long::%))
-          (/////bundle.install "=|generation" (binary long::=))
-          (/////bundle.install "<|generation" (binary long::<))
-          (/////bundle.install "and|generation" (binary long::and))
-          (/////bundle.install "or|generation" (binary long::or))
-          (/////bundle.install "xor|generation" (binary long::xor))
-          (/////bundle.install "shl|generation" (binary long::shl))
-          (/////bundle.install "shr|generation" (binary long::shr))
-          (/////bundle.install "ushr|generation" (binary long::ushr))
-          )))
-
-(def bundle::float
-  Bundle
-  (<| (/////bundle.prefix (reflection.reflection reflection.float))
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "+|generation" (binary float::+))
-          (/////bundle.install "-|generation" (binary float::-))
-          (/////bundle.install "*|generation" (binary float::*))
-          (/////bundle.install "/|generation" (binary float::/))
-          (/////bundle.install "%|generation" (binary float::%))
-          (/////bundle.install "=|generation" (binary float::=))
-          (/////bundle.install "<|generation" (binary float::<))
-          )))
-
-(def bundle::double
-  Bundle
-  (<| (/////bundle.prefix (reflection.reflection reflection.double))
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "+|generation" (binary double::+))
-          (/////bundle.install "-|generation" (binary double::-))
-          (/////bundle.install "*|generation" (binary double::*))
-          (/////bundle.install "/|generation" (binary double::/))
-          (/////bundle.install "%|generation" (binary double::%))
-          (/////bundle.install "=|generation" (binary double::=))
-          (/////bundle.install "<|generation" (binary double::<))
-          )))
-
-(def bundle::char
-  Bundle
-  (<| (/////bundle.prefix (reflection.reflection reflection.char))
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install "=|generation" (binary char::=))
-          (/////bundle.install "<|generation" (binary char::<))
-          )))
+(def with_int_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.int)]
+    (|>> (/////bundle.install (%.format "jvm_" type "_" "+" "#" "|generation") (binary int::+))
+         (/////bundle.install (%.format "jvm_" type "_" "-" "#" "|generation") (binary int::-))
+         (/////bundle.install (%.format "jvm_" type "_" "*" "#" "|generation") (binary int::*))
+         (/////bundle.install (%.format "jvm_" type "_" "/" "#" "|generation") (binary int::/))
+         (/////bundle.install (%.format "jvm_" type "_" "%" "#" "|generation") (binary int::%))
+         (/////bundle.install (%.format "jvm_" type "_" "=" "#" "|generation") (binary int::=))
+         (/////bundle.install (%.format "jvm_" type "_" "<" "#" "|generation") (binary int::<))
+         (/////bundle.install (%.format "jvm_" type "_" "and" "#" "|generation") (binary int::and))
+         (/////bundle.install (%.format "jvm_" type "_" "or" "#" "|generation") (binary int::or))
+         (/////bundle.install (%.format "jvm_" type "_" "xor" "#" "|generation") (binary int::xor))
+         (/////bundle.install (%.format "jvm_" type "_" "shl" "#" "|generation") (binary int::shl))
+         (/////bundle.install (%.format "jvm_" type "_" "shr" "#" "|generation") (binary int::shr))
+         (/////bundle.install (%.format "jvm_" type "_" "ushr" "#" "|generation") (binary int::ushr))
+         )))
+
+(def with_long_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.long)]
+    (|>> (/////bundle.install (%.format "jvm_" type "_" "+" "#" "|generation") (binary long::+))
+         (/////bundle.install (%.format "jvm_" type "_" "-" "#" "|generation") (binary long::-))
+         (/////bundle.install (%.format "jvm_" type "_" "*" "#" "|generation") (binary long::*))
+         (/////bundle.install (%.format "jvm_" type "_" "/" "#" "|generation") (binary long::/))
+         (/////bundle.install (%.format "jvm_" type "_" "%" "#" "|generation") (binary long::%))
+         (/////bundle.install (%.format "jvm_" type "_" "=" "#" "|generation") (binary long::=))
+         (/////bundle.install (%.format "jvm_" type "_" "<" "#" "|generation") (binary long::<))
+         (/////bundle.install (%.format "jvm_" type "_" "and" "#" "|generation") (binary long::and))
+         (/////bundle.install (%.format "jvm_" type "_" "or" "#" "|generation") (binary long::or))
+         (/////bundle.install (%.format "jvm_" type "_" "xor" "#" "|generation") (binary long::xor))
+         (/////bundle.install (%.format "jvm_" type "_" "shl" "#" "|generation") (binary long::shl))
+         (/////bundle.install (%.format "jvm_" type "_" "shr" "#" "|generation") (binary long::shr))
+         (/////bundle.install (%.format "jvm_" type "_" "ushr" "#" "|generation") (binary long::ushr))
+         )))
+
+(def with_float_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.float)]
+    (|>> (/////bundle.install (%.format "jvm_" type "_" "+" "#" "|generation") (binary float::+))
+         (/////bundle.install (%.format "jvm_" type "_" "-" "#" "|generation") (binary float::-))
+         (/////bundle.install (%.format "jvm_" type "_" "*" "#" "|generation") (binary float::*))
+         (/////bundle.install (%.format "jvm_" type "_" "/" "#" "|generation") (binary float::/))
+         (/////bundle.install (%.format "jvm_" type "_" "%" "#" "|generation") (binary float::%))
+         (/////bundle.install (%.format "jvm_" type "_" "=" "#" "|generation") (binary float::=))
+         (/////bundle.install (%.format "jvm_" type "_" "<" "#" "|generation") (binary float::<))
+         )))
+
+(def with_double_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.float)]
+    (|>> (/////bundle.install (%.format "jvm_" type "_" "+" "#" "|generation") (binary double::+))
+         (/////bundle.install (%.format "jvm_" type "_" "-" "#" "|generation") (binary double::-))
+         (/////bundle.install (%.format "jvm_" type "_" "*" "#" "|generation") (binary double::*))
+         (/////bundle.install (%.format "jvm_" type "_" "/" "#" "|generation") (binary double::/))
+         (/////bundle.install (%.format "jvm_" type "_" "%" "#" "|generation") (binary double::%))
+         (/////bundle.install (%.format "jvm_" type "_" "=" "#" "|generation") (binary double::=))
+         (/////bundle.install (%.format "jvm_" type "_" "<" "#" "|generation") (binary double::<))
+         )))
+
+(def with_char_extensions
+  (-> Bundle Bundle)
+  (let [type (reflection.reflection reflection.char)]
+    (|>> (/////bundle.install (%.format "jvm_" type "_" "=" "#" "|generation") (binary char::=))
+         (/////bundle.install (%.format "jvm_" type "_" "<" "#" "|generation") (binary char::<))
+         )))
 
 (with_template [  ]
   [(def .public 
@@ -493,55 +486,48 @@
                  valueG
                  _.aastore))))]))
 
-(def bundle::array
-  Bundle
-  (<| (/////bundle.prefix "array")
-      (|> /////bundle.empty
-          (dictionary.composite (<| (/////bundle.prefix "length")
-                                    (|> /////bundle.empty
-                                        (/////bundle.install (%.format (reflection.reflection reflection.boolean) "|generation") (primitive_array_length_handler type.boolean))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.byte) "|generation") (primitive_array_length_handler type.byte))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.short) "|generation") (primitive_array_length_handler type.short))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.int) "|generation") (primitive_array_length_handler type.int))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.long) "|generation") (primitive_array_length_handler type.long))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.float) "|generation") (primitive_array_length_handler type.float))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.double) "|generation") (primitive_array_length_handler type.double))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.char) "|generation") (primitive_array_length_handler type.char))
-                                        (/////bundle.install (%.format "object" "|generation") array::length::object))))
-          (dictionary.composite (<| (/////bundle.prefix "new")
-                                    (|> /////bundle.empty
-                                        (/////bundle.install (%.format (reflection.reflection reflection.boolean) "|generation") (new_primitive_array_handler __.t_boolean))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.byte) "|generation") (new_primitive_array_handler __.t_byte))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.short) "|generation") (new_primitive_array_handler __.t_short))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.int) "|generation") (new_primitive_array_handler __.t_int))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.long) "|generation") (new_primitive_array_handler __.t_long))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.float) "|generation") (new_primitive_array_handler __.t_float))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.double) "|generation") (new_primitive_array_handler __.t_double))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.char) "|generation") (new_primitive_array_handler __.t_char))
-                                        (/////bundle.install (%.format "object" "|generation") array::new::object))))
-          (dictionary.composite (<| (/////bundle.prefix "read")
-                                    (|> /////bundle.empty
-                                        (/////bundle.install (%.format (reflection.reflection reflection.boolean) "|generation") (read_primitive_array_handler type.boolean _.baload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.byte) "|generation") (read_primitive_array_handler type.byte _.baload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.short) "|generation") (read_primitive_array_handler type.short _.saload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.int) "|generation") (read_primitive_array_handler type.int _.iaload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.long) "|generation") (read_primitive_array_handler type.long _.laload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.float) "|generation") (read_primitive_array_handler type.float _.faload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.double) "|generation") (read_primitive_array_handler type.double _.daload))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.char) "|generation") (read_primitive_array_handler type.char _.caload))
-                                        (/////bundle.install (%.format "object" "|generation") array::read::object))))
-          (dictionary.composite (<| (/////bundle.prefix "write")
-                                    (|> /////bundle.empty
-                                        (/////bundle.install (%.format (reflection.reflection reflection.boolean) "|generation") (write_primitive_array_handler type.boolean _.bastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.byte) "|generation") (write_primitive_array_handler type.byte _.bastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.short) "|generation") (write_primitive_array_handler type.short _.sastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.int) "|generation") (write_primitive_array_handler type.int _.iastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.long) "|generation") (write_primitive_array_handler type.long _.lastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.float) "|generation") (write_primitive_array_handler type.float _.fastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.double) "|generation") (write_primitive_array_handler type.double _.dastore))
-                                        (/////bundle.install (%.format (reflection.reflection reflection.char) "|generation") (write_primitive_array_handler type.char _.castore))
-                                        (/////bundle.install (%.format "object" "|generation") array::write::object))))
-          )))
+(def with_array_extensions
+  (-> Bundle Bundle)
+  (|>> (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.boolean) "#" "|generation") (primitive_array_length_handler type.boolean))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.byte) "#" "|generation") (primitive_array_length_handler type.byte))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.short) "#" "|generation") (primitive_array_length_handler type.short))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.int) "#" "|generation") (primitive_array_length_handler type.int))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.long) "#" "|generation") (primitive_array_length_handler type.long))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.float) "#" "|generation") (primitive_array_length_handler type.float))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.double) "#" "|generation") (primitive_array_length_handler type.double))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" (reflection.reflection reflection.char) "#" "|generation") (primitive_array_length_handler type.char))
+       (/////bundle.install (%.format "jvm_" "array_" "length_" "object" "#" "|generation") array::length::object)
+
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.boolean) "#" "|generation") (new_primitive_array_handler __.t_boolean))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.byte) "#" "|generation") (new_primitive_array_handler __.t_byte))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.short) "#" "|generation") (new_primitive_array_handler __.t_short))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.int) "#" "|generation") (new_primitive_array_handler __.t_int))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.long) "#" "|generation") (new_primitive_array_handler __.t_long))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.float) "#" "|generation") (new_primitive_array_handler __.t_float))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.double) "#" "|generation") (new_primitive_array_handler __.t_double))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" (reflection.reflection reflection.char) "#" "|generation") (new_primitive_array_handler __.t_char))
+       (/////bundle.install (%.format "jvm_" "array_" "new_" "object" "#" "|generation") array::new::object)
+
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.boolean) "#" "|generation") (read_primitive_array_handler type.boolean _.baload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.byte) "#" "|generation") (read_primitive_array_handler type.byte _.baload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.short) "#" "|generation") (read_primitive_array_handler type.short _.saload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.int) "#" "|generation") (read_primitive_array_handler type.int _.iaload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.long) "#" "|generation") (read_primitive_array_handler type.long _.laload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.float) "#" "|generation") (read_primitive_array_handler type.float _.faload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.double) "#" "|generation") (read_primitive_array_handler type.double _.daload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" (reflection.reflection reflection.char) "#" "|generation") (read_primitive_array_handler type.char _.caload))
+       (/////bundle.install (%.format "jvm_" "array_" "read_" "object" "#" "|generation") array::read::object)
+
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.boolean) "#" "|generation") (write_primitive_array_handler type.boolean _.bastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.byte) "#" "|generation") (write_primitive_array_handler type.byte _.bastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.short) "#" "|generation") (write_primitive_array_handler type.short _.sastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.int) "#" "|generation") (write_primitive_array_handler type.int _.iastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.long) "#" "|generation") (write_primitive_array_handler type.long _.lastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.float) "#" "|generation") (write_primitive_array_handler type.float _.fastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.double) "#" "|generation") (write_primitive_array_handler type.double _.dastore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" (reflection.reflection reflection.char) "#" "|generation") (write_primitive_array_handler type.char _.castore))
+       (/////bundle.install (%.format "jvm_" "array_" "write_" "object" "#" "|generation") array::write::object)
+       ))
 
 (def (object::null _)
   (Nullary (Bytecode Any))
@@ -639,18 +625,16 @@
                       ... else
                       valueG)))))]))
 
-(def bundle::object
-  Bundle
-  (<| (/////bundle.prefix "object")
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install (%.format "null" "|generation") (nullary object::null))
-          (/////bundle.install (%.format "null?" "|generation") (unary object::null?))
-          (/////bundle.install (%.format "synchronized" "|generation") (binary object::synchronized))
-          (/////bundle.install (%.format "throw" "|generation") (unary object::throw))
-          (/////bundle.install (%.format "class" "|generation") object::class)
-          (/////bundle.install (%.format "instance?" "|generation") object::instance?)
-          (/////bundle.install (%.format "cast" "|generation") object::cast)
-          )))
+(def with_object_extensions
+  (-> Bundle Bundle)
+  (|>> (/////bundle.install (%.format "jvm_" "object_" "null" "#" "|generation") (nullary object::null))
+       (/////bundle.install (%.format "jvm_" "object_" "null?" "#" "|generation") (unary object::null?))
+       (/////bundle.install (%.format "jvm_" "object_" "synchronized" "#" "|generation") (binary object::synchronized))
+       (/////bundle.install (%.format "jvm_" "object_" "throw" "#" "|generation") (unary object::throw))
+       (/////bundle.install (%.format "jvm_" "object_" "class" "#" "|generation") object::class)
+       (/////bundle.install (%.format "jvm_" "object_" "instance?" "#" "|generation") object::instance?)
+       (/////bundle.install (%.format "jvm_" "object_" "cast" "#" "|generation") object::cast)
+       ))
 
 (def get::static
   Handler
@@ -792,26 +776,20 @@
                  (monad.each _.monad product.right inputsTG)
                  (_.invokespecial class "" (type.method [(list) (list#each product.left inputsTG) type.void (list)]))))))]))
 
-(def bundle::member
-  Bundle
-  (<| (/////bundle.prefix "member")
-      (|> (is Bundle /////bundle.empty)
-          (dictionary.composite (<| (/////bundle.prefix "get")
-                                    (|> (is Bundle /////bundle.empty)
-                                        (/////bundle.install (%.format "static" "|generation") get::static)
-                                        (/////bundle.install (%.format "virtual" "|generation") get::virtual))))
-          (dictionary.composite (<| (/////bundle.prefix "put")
-                                    (|> (is Bundle /////bundle.empty)
-                                        (/////bundle.install (%.format "static" "|generation") put::static)
-                                        (/////bundle.install (%.format "virtual" "|generation") put::virtual))))
-          (dictionary.composite (<| (/////bundle.prefix "invoke")
-                                    (|> (is Bundle /////bundle.empty)
-                                        (/////bundle.install (%.format "static" "|generation") invoke::static)
-                                        (/////bundle.install (%.format "virtual" "|generation") invoke::virtual)
-                                        (/////bundle.install (%.format "special" "|generation") invoke::special)
-                                        (/////bundle.install (%.format "interface" "|generation") invoke::interface)
-                                        (/////bundle.install (%.format "constructor" "|generation") invoke::constructor))))
-          )))
+(def with_member_extensions
+  (-> Bundle Bundle)
+  (|>> (/////bundle.install (%.format "jvm_" "member_" "get_" "static" "#" "|generation") get::static)
+       (/////bundle.install (%.format "jvm_" "member_" "get_" "virtual" "#" "|generation") get::virtual)
+       
+       (/////bundle.install (%.format "jvm_" "member_" "put_" "static" "#" "|generation") put::static)
+       (/////bundle.install (%.format "jvm_" "member_" "put_" "virtual" "#" "|generation") put::virtual)
+       
+       (/////bundle.install (%.format "jvm_" "member_" "invoke_" "static" "#" "|generation") invoke::static)
+       (/////bundle.install (%.format "jvm_" "member_" "invoke_" "virtual" "#" "|generation") invoke::virtual)
+       (/////bundle.install (%.format "jvm_" "member_" "invoke_" "special" "#" "|generation") invoke::special)
+       (/////bundle.install (%.format "jvm_" "member_" "invoke_" "interface" "#" "|generation") invoke::interface)
+       (/////bundle.install (%.format "jvm_" "member_" "invoke_" "constructor" "#" "|generation") invoke::constructor)
+       ))
 
 (def annotation_parameter
   (Parser (/.Annotation_Parameter Synthesis))
@@ -1370,24 +1348,20 @@
          _ (//////generation.save! artifact_id {.#None} artifact)]
         (anonymous_instance generate archive class total_environment inputsTI)))]))
 
-(def bundle::class
-  Bundle
-  (<| (/////bundle.prefix "class")
-      (|> (is Bundle /////bundle.empty)
-          (/////bundle.install (%.format "anonymous" "|generation") class::anonymous)
-          )))
+(def with_class_extensions
+  (-> Bundle Bundle)
+  (/////bundle.install (%.format "jvm_" "class_" "anonymous" "#" "|generation") class::anonymous))
 
 (def .public bundle
   Bundle
-  (<| (/////bundle.prefix "jvm")
-      (|> ..bundle::conversion
-          (dictionary.composite ..bundle::int)
-          (dictionary.composite ..bundle::long)
-          (dictionary.composite ..bundle::float)
-          (dictionary.composite ..bundle::double)
-          (dictionary.composite ..bundle::char)
-          (dictionary.composite ..bundle::array)
-          (dictionary.composite ..bundle::object)
-          (dictionary.composite ..bundle::member)
-          (dictionary.composite ..bundle::class)
-          )))
+  (<| with_conversion_extensions
+      with_int_extensions
+      with_long_extensions
+      with_float_extensions
+      with_double_extensions
+      with_char_extensions
+      with_array_extensions
+      with_object_extensions
+      with_member_extensions
+      with_class_extensions
+      /////bundle.empty))
diff --git a/stdlib/source/library/lux/meta/target/jvm/constant.lux b/stdlib/source/library/lux/meta/target/jvm/constant.lux
index 7c23d49c7..3b77b382a 100644
--- a/stdlib/source/library/lux/meta/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/constant.lux
@@ -75,9 +75,8 @@
           ("jvm feq" parameter subject)
           
           @.jvm
-          ("jvm float ="
-           ("jvm object cast" parameter)
-           ("jvm object cast" subject))))))
+          (.jvm_float_=# (.jvm_object_cast# parameter)
+                         (.jvm_object_cast# subject))))))
 
 (import java/lang/Double
   "[1]::[0]"
diff --git a/stdlib/source/library/lux/meta/target/jvm/loader.lux b/stdlib/source/library/lux/meta/target/jvm/loader.lux
index 3f2c4dd39..5e9b5fa0c 100644
--- a/stdlib/source/library/lux/meta/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/loader.lux
@@ -110,7 +110,7 @@
                                 (<|)
                                 
                                 @.jvm
-                                "jvm object cast")]
+                                .jvm_object_cast#)]
     (<| 
         (object [] java/lang/ClassLoader []
           []
diff --git a/stdlib/source/library/lux/world/net/http.lux b/stdlib/source/library/lux/world/net/http.lux
index b90c770f5..15044efec 100644
--- a/stdlib/source/library/lux/world/net/http.lux
+++ b/stdlib/source/library/lux/world/net/http.lux
@@ -7,15 +7,14 @@
      [frp (.only Channel)]]]
    [data
     [binary (.only Binary)]]]]
+ [/
+  [version (.only Version)]]
  [// (.only Address)
   [uri (.only URI)]
   [//
    ["[0]" environment
     ["[1]" \\parser (.only Environment)]]]])
 
-(type .public Version
-  Text)
-
 (type .public Method
   (Variant
    {#Post}
@@ -44,6 +43,7 @@
 (type .public (Body !)
   (-> (Maybe Nat) (! (Try [Nat Binary]))))
 
+... https://en.wikipedia.org/wiki/List_of_URI_schemes
 (type .public Scheme
   (Variant
    {#HTTP}
diff --git a/stdlib/source/library/lux/world/net/http/version.lux b/stdlib/source/library/lux/world/net/http/version.lux
index aeaba736b..1bd888b31 100644
--- a/stdlib/source/library/lux/world/net/http/version.lux
+++ b/stdlib/source/library/lux/world/net/http/version.lux
@@ -1,13 +1,39 @@
 (.require
  [library
-  [lux (.except)]]
- [// (.only Version)])
+  [lux (.except)
+   [abstract
+    [equivalence (.only Equivalence)]
+    [hash (.only Hash)]]
+   [data
+    ["[0]" text (.use "[1]#[0]" hash)]]
+   [meta
+    [type
+     ["[0]" primitive (.only primitive)]]]]])
 
-(with_template [ ]
-  [(def .public  Version )]
+(primitive .public Version
+  Text
 
-  [v0_9 "0.9"]
-  [v1_0 "1.0"]
-  [v1_1 "1.1"]
-  [v2_0 "2.0"]
+  (def .public equivalence
+    (Equivalence Version)
+    (implementation
+     (def (= reference it)
+       (text#= (primitive.representation reference)
+               (primitive.representation it)))))
+
+  (def .public hash
+    (Hash Version)
+    (implementation
+     (def equivalence ..equivalence)
+     (def hash (|>> primitive.representation text#hash))))
+
+  (with_template [ ]
+    [(def .public 
+       Version
+       (primitive.abstraction ))]
+
+    [v0_9 "0.9"]
+    [v1_0 "1.0"]
+    [v1_1 "1.1"]
+    [v2_0 "2.0"]
+    )
   )
diff --git a/stdlib/source/library/lux/world/time/instant.lux b/stdlib/source/library/lux/world/time/instant.lux
index a9fbc61e2..e5fd7fd34 100644
--- a/stdlib/source/library/lux/world/time/instant.lux
+++ b/stdlib/source/library/lux/world/time/instant.lux
@@ -159,8 +159,8 @@
 (def .public now
   (IO Instant)
   (io (..of_millis (for @.old ("jvm invokestatic:java.lang.System:currentTimeMillis:")
-                        @.jvm (|> ("jvm member invoke static" [] "java.lang.System" "currentTimeMillis" [])
-                                  ("jvm object cast")
+                        @.jvm (|> (.jvm_member_invoke_static# [] "java.lang.System" "currentTimeMillis" [])
+                                  .jvm_object_cast#
                                   (is (Primitive "java.lang.Long"))
                                   (as Int))
                         @.js (let [date ("js object new" ("js constant" "Date") [])]
diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux
index d7d05321d..c50dfc7e8 100644
--- a/stdlib/source/test/lux/ffi.jvm.lux
+++ b/stdlib/source/test/lux/ffi.jvm.lux
@@ -210,9 +210,9 @@
                    [(_.coverage [ ]
                       (|> 
                           (is )
-                          "jvm object cast"
+                          .jvm_object_cast#
                           (is )
-                          "jvm object cast"
+                          .jvm_object_cast#
                           (is )
                           ( )))
                     (_.coverage [ ]
diff --git a/stdlib/source/test/lux/meta/target/jvm.lux b/stdlib/source/test/lux/meta/target/jvm.lux
index b7c487680..6330dcbe2 100644
--- a/stdlib/source/test/lux/meta/target/jvm.lux
+++ b/stdlib/source/test/lux/meta/target/jvm.lux
@@ -133,12 +133,12 @@
                          (list)
                          (list)
                          (list (/method.method ..method_modifier
-                                               method_name
-                                               false (/type.method [(list) (list) ..$Object (list)])
-                                               (list)
-                                               {.#Some (do /.monad
-                                                         [_ bytecode]
-                                                         /.areturn)}))
+                                 method_name
+                                 false (/type.method [(list) (list) ..$Object (list)])
+                                 (list)
+                                 {.#Some (do /.monad
+                                           [_ bytecode]
+                                           /.areturn)}))
                          (sequence.sequence))
                  .let [bytecode (binary.result /class.format class)
                        loader (/loader.memory (/loader.new_library []))]
@@ -331,7 +331,7 @@
                             (|>> (as )  ("jvm leq" expected))
                             
                             @.jvm
-                            (|>> (as )  "jvm object cast" ("jvm long =" ("jvm object cast" (as java/lang/Long expected))))))
+                            (|>> (as )  .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (as java/lang/Long expected))))))
            (do /.monad
              [_ ( (|> expected .int  try.trusted))]
              ))))]
@@ -349,9 +349,9 @@
                    ( subject parameter)
                    
                    @.jvm
-                   ("jvm object cast"
-                    ( ("jvm object cast" parameter)
-                                     ("jvm object cast" subject))))))]))]
+                   (.jvm_object_cast#
+                    ( (.jvm_object_cast# parameter)
+                                     (.jvm_object_cast# subject))))))]))]
 
   [int/2 java/lang/Integer]
   [long/2 java/lang/Long]
@@ -367,9 +367,9 @@
                 ( subject parameter)
                 
                 @.jvm
-                ("jvm object cast"
-                 ( ("jvm object cast" parameter)
-                                  ("jvm object cast" subject))))))]))
+                (.jvm_object_cast#
+                 ( (.jvm_object_cast# parameter)
+                                  (.jvm_object_cast# subject))))))]))
 
 (def int
   Test
@@ -379,7 +379,7 @@
                                        (|>> (as java/lang/Integer) ("jvm ieq" expected))
                                        
                                        @.jvm
-                                       (|>> (as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" expected)))))
+                                       (|>> (as java/lang/Integer) .jvm_object_cast# (.jvm_int_=# (.jvm_object_cast# expected)))))
                       (do /.monad
                         [_ bytecode]
                         ..$Integer::wrap))))
@@ -426,23 +426,23 @@
                                  [expected ..$Integer::random]
                                  (int expected (..$Integer::literal expected)))))
         arithmetic (all _.and
-                        (_.lifted "IADD" (binary (int/2 "jvm iadd" "jvm int +") /.iadd))
-                        (_.lifted "ISUB" (binary (int/2 "jvm isub" "jvm int -") /.isub))
-                        (_.lifted "IMUL" (binary (int/2 "jvm imul" "jvm int *") /.imul))
-                        (_.lifted "IDIV" (binary (int/2 "jvm idiv" "jvm int /") /.idiv))
-                        (_.lifted "IREM" (binary (int/2 "jvm irem" "jvm int %") /.irem))
+                        (_.lifted "IADD" (binary (int/2 "jvm iadd" .jvm_int_+#) /.iadd))
+                        (_.lifted "ISUB" (binary (int/2 "jvm isub" .jvm_int_-#) /.isub))
+                        (_.lifted "IMUL" (binary (int/2 "jvm imul" .jvm_int_*#) /.imul))
+                        (_.lifted "IDIV" (binary (int/2 "jvm idiv" .jvm_int_/#) /.idiv))
+                        (_.lifted "IREM" (binary (int/2 "jvm irem" .jvm_int_%#) /.irem))
                         (_.lifted "INEG" (unary (function (_ value)
-                                                  ((int/2 "jvm isub" "jvm int -")
+                                                  ((int/2 "jvm isub" .jvm_int_-#)
                                                    value
                                                    (ffi.long_to_int (as java/lang/Long +0))))
                                                 /.ineg)))
         bitwise (all _.and
-                     (_.lifted "IAND" (binary (int/2 "jvm iand" "jvm int and") /.iand))
-                     (_.lifted "IOR" (binary (int/2 "jvm ior" "jvm int or") /.ior))
-                     (_.lifted "IXOR" (binary (int/2 "jvm ixor" "jvm int xor") /.ixor))
-                     (_.lifted "ISHL" (shift (int/2 "jvm ishl" "jvm int shl") /.ishl))
-                     (_.lifted "ISHR" (shift (int/2 "jvm ishr" "jvm int shr") /.ishr))
-                     (_.lifted "IUSHR" (shift (int/2 "jvm iushr" "jvm int ushr") /.iushr)))]
+                     (_.lifted "IAND" (binary (int/2 "jvm iand" .jvm_int_and#) /.iand))
+                     (_.lifted "IOR" (binary (int/2 "jvm ior" .jvm_int_or#) /.ior))
+                     (_.lifted "IXOR" (binary (int/2 "jvm ixor" .jvm_int_xor#) /.ixor))
+                     (_.lifted "ISHL" (shift (int/2 "jvm ishl" .jvm_int_shl#) /.ishl))
+                     (_.lifted "ISHR" (shift (int/2 "jvm ishr" .jvm_int_shr#) /.ishr))
+                     (_.lifted "IUSHR" (shift (int/2 "jvm iushr" .jvm_int_ushr#) /.iushr)))]
     (all _.and
          (<| (_.context "literal")
              literal)
@@ -460,7 +460,7 @@
                                         (|>> (as Int) (i.= expected))
                                         
                                         @.jvm
-                                        (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected)))))
+                                        (|>> (as java/lang/Long) .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# expected)))))
                        (do /.monad
                          [_ bytecode]
                          ..$Long::wrap))))
@@ -500,23 +500,23 @@
                                  [expected ..$Long::random]
                                  (long expected (..$Long::literal expected)))))
         arithmetic (all _.and
-                        (_.lifted "LADD" (binary (long/2 "jvm ladd" "jvm long +") /.ladd))
-                        (_.lifted "LSUB" (binary (long/2 "jvm lsub" "jvm long -") /.lsub))
-                        (_.lifted "LMUL" (binary (long/2 "jvm lmul" "jvm long *") /.lmul))
-                        (_.lifted "LDIV" (binary (long/2 "jvm ldiv" "jvm long /") /.ldiv))
-                        (_.lifted "LREM" (binary (long/2 "jvm lrem" "jvm long %") /.lrem))
+                        (_.lifted "LADD" (binary (long/2 "jvm ladd" .jvm_long_+#) /.ladd))
+                        (_.lifted "LSUB" (binary (long/2 "jvm lsub" .jvm_long_-#) /.lsub))
+                        (_.lifted "LMUL" (binary (long/2 "jvm lmul" .jvm_long_*#) /.lmul))
+                        (_.lifted "LDIV" (binary (long/2 "jvm ldiv" .jvm_long_/#) /.ldiv))
+                        (_.lifted "LREM" (binary (long/2 "jvm lrem" .jvm_long_%#) /.lrem))
                         (_.lifted "LNEG" (unary (function (_ value)
-                                                  ((long/2 "jvm lsub" "jvm long -")
+                                                  ((long/2 "jvm lsub" .jvm_long_-#)
                                                    value
                                                    (as java/lang/Long +0)))
                                                 /.lneg)))
         bitwise (all _.and
-                     (_.lifted "LAND" (binary (long/2 "jvm land" "jvm long and") /.land))
-                     (_.lifted "LOR" (binary (long/2 "jvm lor" "jvm long or") /.lor))
-                     (_.lifted "LXOR" (binary (long/2 "jvm lxor" "jvm long xor") /.lxor))
-                     (_.lifted "LSHL" (shift (int+long/2 "jvm lshl" "jvm long shl") /.lshl))
-                     (_.lifted "LSHR" (shift (int+long/2 "jvm lshr" "jvm long shr") /.lshr))
-                     (_.lifted "LUSHR" (shift (int+long/2 "jvm lushr" "jvm long ushr") /.lushr)))
+                     (_.lifted "LAND" (binary (long/2 "jvm land" .jvm_long_and#) /.land))
+                     (_.lifted "LOR" (binary (long/2 "jvm lor" .jvm_long_or#) /.lor))
+                     (_.lifted "LXOR" (binary (long/2 "jvm lxor" .jvm_long_xor#) /.lxor))
+                     (_.lifted "LSHL" (shift (int+long/2 "jvm lshl" .jvm_long_shl#) /.lshl))
+                     (_.lifted "LSHR" (shift (int+long/2 "jvm lshr" .jvm_long_shr#) /.lshr))
+                     (_.lifted "LUSHR" (shift (int+long/2 "jvm lushr" .jvm_long_ushr#) /.lushr)))
         comparison (_.lifted "LCMP"
                              (do random.monad
                                [reference ..$Long::random
@@ -533,7 +533,7 @@
                                                     (|>> (as Int) (i.= expected))
                                                     
                                                     @.jvm
-                                                    (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected)))))
+                                                    (|>> (as java/lang/Long) .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# expected)))))
                                    (do /.monad
                                      [_ (..$Long::literal subject)
                                       _ (..$Long::literal reference)
@@ -563,7 +563,7 @@
                                          
                                          @.jvm
                                          (function (_ actual)
-                                           (or (|> actual (as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" expected)))
+                                           (or (|> actual (as java/lang/Float) .jvm_object_cast# (.jvm_float_=# (.jvm_object_cast# expected)))
                                                (and (f.not_a_number? (as Frac (ffi.float_to_double expected)))
                                                     (f.not_a_number? (as Frac (ffi.float_to_double (as java/lang/Float actual)))))))))
                         (do /.monad
@@ -600,13 +600,13 @@
                                  [expected ..$Float::random]
                                  (float expected (..$Float::literal expected)))))
         arithmetic (all _.and
-                        (_.lifted "FADD" (binary (float/2 "jvm fadd" "jvm float +") /.fadd))
-                        (_.lifted "FSUB" (binary (float/2 "jvm fsub" "jvm float -") /.fsub))
-                        (_.lifted "FMUL" (binary (float/2 "jvm fmul" "jvm float *") /.fmul))
-                        (_.lifted "FDIV" (binary (float/2 "jvm fdiv" "jvm float /") /.fdiv))
-                        (_.lifted "FREM" (binary (float/2 "jvm frem" "jvm float %") /.frem))
+                        (_.lifted "FADD" (binary (float/2 "jvm fadd" .jvm_float_+#) /.fadd))
+                        (_.lifted "FSUB" (binary (float/2 "jvm fsub" .jvm_float_-#) /.fsub))
+                        (_.lifted "FMUL" (binary (float/2 "jvm fmul" .jvm_float_*#) /.fmul))
+                        (_.lifted "FDIV" (binary (float/2 "jvm fdiv" .jvm_float_/#) /.fdiv))
+                        (_.lifted "FREM" (binary (float/2 "jvm frem" .jvm_float_%#) /.frem))
                         (_.lifted "FNEG" (unary (function (_ value)
-                                                  ((float/2 "jvm fsub" "jvm float -")
+                                                  ((float/2 "jvm fsub" .jvm_float_-#)
                                                    value
                                                    (ffi.double_to_float (as java/lang/Double +0.0))))
                                                 /.fneg)))
@@ -621,7 +621,7 @@
                                                     ("jvm feq" reference subject)
                                                     
                                                     @.jvm
-                                                    ("jvm float =" ("jvm object cast" reference) ("jvm object cast" subject)))
+                                                    (.jvm_float_=# (.jvm_object_cast# reference) (.jvm_object_cast# subject)))
                                              +0
                                              (if (standard reference subject)
                                                +1
@@ -639,7 +639,7 @@
                                        ("jvm fgt" subject reference)
                                        
                                        @.jvm
-                                       ("jvm float <" ("jvm object cast" subject) ("jvm object cast" reference)))))
+                                       (.jvm_float_<# (.jvm_object_cast# subject) (.jvm_object_cast# reference)))))
         comparison (all _.and
                         (_.lifted "FCMPL" (comparison /.fcmpl comparison_standard))
                         (_.lifted "FCMPG" (comparison /.fcmpg comparison_standard)))]
@@ -664,7 +664,7 @@
                                           
                                           @.jvm
                                           (function (_ actual)
-                                            (or (|> actual (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected)))
+                                            (or (|> actual (as java/lang/Double) .jvm_object_cast# (.jvm_double_=# (.jvm_object_cast# expected)))
                                                 (and (f.not_a_number? (as Frac expected))
                                                      (f.not_a_number? (as Frac actual)))))))
                          (do /.monad
@@ -696,13 +696,13 @@
                                  [expected ..$Double::random]
                                  (double expected (..$Double::literal expected)))))
         arithmetic (all _.and
-                        (_.lifted "DADD" (binary (double/2 "jvm dadd" "jvm double +") /.dadd))
-                        (_.lifted "DSUB" (binary (double/2 "jvm dsub" "jvm double -") /.dsub))
-                        (_.lifted "DMUL" (binary (double/2 "jvm dmul" "jvm double *") /.dmul))
-                        (_.lifted "DDIV" (binary (double/2 "jvm ddiv" "jvm double /") /.ddiv))
-                        (_.lifted "DREM" (binary (double/2 "jvm drem" "jvm double %") /.drem))
+                        (_.lifted "DADD" (binary (double/2 "jvm dadd" .jvm_double_+#) /.dadd))
+                        (_.lifted "DSUB" (binary (double/2 "jvm dsub" .jvm_double_-#) /.dsub))
+                        (_.lifted "DMUL" (binary (double/2 "jvm dmul" .jvm_double_*#) /.dmul))
+                        (_.lifted "DDIV" (binary (double/2 "jvm ddiv" .jvm_double_/#) /.ddiv))
+                        (_.lifted "DREM" (binary (double/2 "jvm drem" .jvm_double_%#) /.drem))
                         (_.lifted "DNEG" (unary (function (_ value)
-                                                  ((double/2 "jvm dsub" "jvm double -")
+                                                  ((double/2 "jvm dsub" .jvm_double_-#)
                                                    value
                                                    (as java/lang/Double +0.0)))
                                                 /.dneg)))
@@ -715,7 +715,7 @@
                                                     ("jvm deq" reference subject)
                                                     
                                                     @.jvm
-                                                    ("jvm double =" ("jvm object cast" reference) ("jvm object cast" subject)))
+                                                    (.jvm_double_=# (.jvm_object_cast# reference) (.jvm_object_cast# subject)))
                                              +0
                                              (if (standard reference subject)
                                                +1
@@ -734,7 +734,7 @@
                                        ("jvm dgt" subject reference)
                                        
                                        @.jvm
-                                       ("jvm double <" ("jvm object cast" subject) ("jvm object cast" reference)))))
+                                       (.jvm_double_<# (.jvm_object_cast# subject) (.jvm_object_cast# reference)))))
         comparison (all _.and
                         (_.lifted "DCMPL" (comparison /.dcmpl comparison_standard))
                         (_.lifted "DCMPG" (comparison /.dcmpg comparison_standard)))]
@@ -816,7 +816,7 @@
                             (|>> (as java/lang/Double) ("jvm deq" expected))
                             
                             @.jvm
-                            (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected)))))
+                            (|>> (as java/lang/Double) .jvm_object_cast# (.jvm_double_=# (.jvm_object_cast# expected)))))
            (do /.monad
              [_ (/.double expected)]
              (/.invokestatic ..$Double "valueOf" (/type.method [(list) (list /type.double) ..$Double (list)]))))
@@ -837,7 +837,7 @@
                             (|>> (as java/lang/Double) ("jvm deq" expected))
                             
                             @.jvm
-                            (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected)))))
+                            (|>> (as java/lang/Double) .jvm_object_cast# (.jvm_double_=# (.jvm_object_cast# expected)))))
            (do /.monad
              [_ (/.new ..$Double)
               _ /.dup
@@ -865,8 +865,8 @@
                              ("jvm ladd" part0 part1)
                              
                              @.jvm
-                             ("jvm object cast"
-                              ("jvm long +" ("jvm object cast" part0) ("jvm object cast" part1)))))
+                             (.jvm_object_cast#
+                              (.jvm_long_+# (.jvm_object_cast# part0) (.jvm_object_cast# part1)))))
            $Self (/type.class class_name (list))
            class_field "class_field"
            object_field "object_field"
@@ -881,34 +881,34 @@
                           (list (/field.field /field.static class_field false /type.long (sequence.sequence))
                                 (/field.field /field.public object_field false /type.long (sequence.sequence)))
                           (list (/method.method /method.private
-                                                constructor
-                                                false constructor::type
-                                                (list)
-                                                {.#Some (do /.monad
-                                                          [_ /.aload_0
-                                                           _ (/.invokespecial ..$Object constructor (/type.method [(list) (list) /type.void (list)]))
-                                                           _ (..$Long::literal part0)
-                                                           _ (/.putstatic $Self class_field /type.long)
-                                                           _ /.aload_0
-                                                           _ /.lload_1
-                                                           _ (/.putfield $Self object_field /type.long)]
-                                                          /.return)})
+                                  constructor
+                                  false constructor::type
+                                  (list)
+                                  {.#Some (do /.monad
+                                            [_ /.aload_0
+                                             _ (/.invokespecial ..$Object constructor (/type.method [(list) (list) /type.void (list)]))
+                                             _ (..$Long::literal part0)
+                                             _ (/.putstatic $Self class_field /type.long)
+                                             _ /.aload_0
+                                             _ /.lload_1
+                                             _ (/.putfield $Self object_field /type.long)]
+                                            /.return)})
                                 (/method.method (all /modifier#composite
                                                      /method.public
                                                      /method.static)
-                                                static_method
-                                                false (/type.method [(list) (list) ..$Long (list)])
-                                                (list)
-                                                {.#Some (do /.monad
-                                                          [_ (/.new $Self)
-                                                           _ /.dup
-                                                           _ (..$Long::literal part1)
-                                                           _ (/.invokespecial $Self constructor constructor::type)
-                                                           _ (/.getfield $Self object_field /type.long)
-                                                           _ (/.getstatic $Self class_field /type.long)
-                                                           _ /.ladd
-                                                           _ ..$Long::wrap]
-                                                          /.areturn)}))
+                                  static_method
+                                  false (/type.method [(list) (list) ..$Long (list)])
+                                  (list)
+                                  {.#Some (do /.monad
+                                            [_ (/.new $Self)
+                                             _ /.dup
+                                             _ (..$Long::literal part1)
+                                             _ (/.invokespecial $Self constructor constructor::type)
+                                             _ (/.getfield $Self object_field /type.long)
+                                             _ (/.getstatic $Self class_field /type.long)
+                                             _ /.ladd
+                                             _ ..$Long::wrap]
+                                            /.areturn)}))
                           (sequence.sequence))
                         try.trusted
                         (binary.result /class.format))
@@ -985,7 +985,7 @@
                          (|>> (as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected)))
                          
                          @.jvm
-                         (|>> (as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (as java/lang/Byte expected)))))))))
+                         (|>> (as java/lang/Byte) ffi.byte_to_long .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (ffi.byte_to_long (as java/lang/Byte expected)))))))))
          (_.context "short"
            (array (/.newarray /instruction.t_short) $Short::random $Short::literal [/.sastore /.saload $Short::wrap]
                   (function (_ expected)
@@ -993,7 +993,7 @@
                          (|>> (as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected)))
                          
                          @.jvm
-                         (|>> (as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (as java/lang/Short expected)))))))))
+                         (|>> (as java/lang/Short) ffi.short_to_long .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (ffi.short_to_long (as java/lang/Short expected)))))))))
          (_.context "int"
            (array (/.newarray /instruction.t_int) $Integer::random $Integer::literal [/.iastore /.iaload $Integer::wrap]
                   (function (_ expected)
@@ -1001,7 +1001,7 @@
                          (|>> (as java/lang/Integer) ("jvm ieq" (as java/lang/Integer expected)))
                          
                          @.jvm
-                         (|>> (as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" (as java/lang/Integer expected))))))))
+                         (|>> (as java/lang/Integer) .jvm_object_cast# (.jvm_int_=# (.jvm_object_cast# (as java/lang/Integer expected))))))))
          (_.context "long"
            (array (/.newarray /instruction.t_long) $Long::random $Long::literal [/.lastore /.laload $Long::wrap]
                   (function (_ expected)
@@ -1009,7 +1009,7 @@
                          (|>> (as java/lang/Long) ("jvm leq" expected))
                          
                          @.jvm
-                         (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" (as java/lang/Long expected))))))))
+                         (|>> (as java/lang/Long) .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (as java/lang/Long expected))))))))
          (_.context "float"
            (array (/.newarray /instruction.t_float) ..valid_float $Float::literal [/.fastore /.faload $Float::wrap]
                   (function (_ expected)
@@ -1017,7 +1017,7 @@
                          (|>> (as java/lang/Float) ("jvm feq" expected))
                          
                          @.jvm
-                         (|>> (as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" (as java/lang/Float expected))))))))
+                         (|>> (as java/lang/Float) .jvm_object_cast# (.jvm_float_=# (.jvm_object_cast# (as java/lang/Float expected))))))))
          (_.context "double"
            (array (/.newarray /instruction.t_double) ..valid_double $Double::literal [/.dastore /.daload $Double::wrap]
                   (function (_ expected)
@@ -1025,7 +1025,7 @@
                          (|>> (as java/lang/Double) ("jvm deq" expected))
                          
                          @.jvm
-                         (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" (as java/lang/Double expected))))))))
+                         (|>> (as java/lang/Double) .jvm_object_cast# (.jvm_double_=# (.jvm_object_cast# (as java/lang/Double expected))))))))
          (_.context "char"
            (array (/.newarray /instruction.t_char) $Character::random $Character::literal [/.castore /.caload $Character::wrap]
                   (function (_ expected)
@@ -1033,7 +1033,7 @@
                          (|>> (as java/lang/Character) ("jvm ceq" expected))
                          
                          @.jvm
-                         (|>> (as java/lang/Character) "jvm object cast" ("jvm char =" ("jvm object cast" (as java/lang/Character expected))))))))
+                         (|>> (as java/lang/Character) .jvm_object_cast# (.jvm_char_=# (.jvm_object_cast# (as java/lang/Character expected))))))))
          (_.context "object"
            (array (/.anewarray ..$String) $String::random $String::literal [/.aastore /.aaload /.nop]
                   (function (_ expected) (|>> (as Text) (text#= (as Text expected))))))
@@ -1068,7 +1068,7 @@
                 (|>> (as ) ( expected))
                 
                 @.jvm
-                (|>> (as ) "jvm object cast" ( ("jvm object cast" (as  expected)))))))]))
+                (|>> (as ) .jvm_object_cast# ( (.jvm_object_cast# (as  expected)))))))]))
 
 (def conversion
   Test
@@ -1083,10 +1083,10 @@
                                          [_ ((the #literal from) input)
                                           _ instruction]
                                          (the #wrap to))))))
-        int::= (!::= java/lang/Integer "jvm ieq" "jvm int =")
-        long::= (!::= java/lang/Long "jvm leq" "jvm long =")
-        float::= (!::= java/lang/Float "jvm feq" "jvm float =")
-        double::= (!::= java/lang/Double "jvm deq" "jvm double =")]
+        int::= (!::= java/lang/Integer "jvm ieq" .jvm_int_=#)
+        long::= (!::= java/lang/Long "jvm leq" .jvm_long_=#)
+        float::= (!::= java/lang/Float "jvm feq" .jvm_float_=#)
+        double::= (!::= java/lang/Double "jvm deq" .jvm_double_=#)]
     (all _.and
          (<| (_.context "int")
              (all _.and
@@ -1099,16 +1099,16 @@
                                                      (|>> (as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected)))
                                                      
                                                      @.jvm
-                                                     (|>> (as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (as java/lang/Byte expected)))))))))
+                                                     (|>> (as java/lang/Byte) ffi.byte_to_long .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (ffi.byte_to_long (as java/lang/Byte expected)))))))))
                   (_.lifted "I2C" (conversion ..$Integer::primitive ..$Character::primitive /.i2c (|>> ffi.int_to_char)
-                                              (!::= java/lang/Character "jvm ceq" "jvm char =")))
+                                              (!::= java/lang/Character "jvm ceq" .jvm_char_=#)))
                   (_.lifted "I2S" (conversion ..$Integer::primitive ..$Short::primitive /.i2s (|>> ffi.int_to_short)
                                               (function (_ expected)
                                                 (for @.old
                                                      (|>> (as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected)))
                                                      
                                                      @.jvm
-                                                     (|>> (as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (as java/lang/Short expected)))))))))))
+                                                     (|>> (as java/lang/Short) ffi.short_to_long .jvm_object_cast# (.jvm_long_=# (.jvm_object_cast# (ffi.short_to_long (as java/lang/Short expected)))))))))))
          (<| (_.context "long")
              (all _.and
                   (_.lifted "L2I" (conversion ..$Long::primitive ..$Integer::primitive /.l2i (|>> ffi.long_to_int) int::=))
@@ -1162,7 +1162,7 @@
                                      *wrap)))))]
     (all _.and
          (<| (_.context "int")
-             (let [test (!::= java/lang/Integer "jvm ieq" "jvm int =")]
+             (let [test (!::= java/lang/Integer "jvm ieq" .jvm_int_=#)]
                (all _.and
                     (_.lifted "ISTORE_0/ILOAD_0"
                               (store_and_load ..$Integer::random ..$Integer::literal ..$Integer::wrap [(function.constant /.istore_0) (function.constant /.iload_0)] test))
@@ -1186,10 +1186,9 @@
                                                           (.int (/unsigned.value increment)))
                                                          
                                                          @.jvm
-                                                         ("jvm object cast"
-                                                          ("jvm long +"
-                                                           ("jvm object cast" (ffi.byte_to_long base))
-                                                           ("jvm object cast" (as java/lang/Long (/unsigned.value increment)))))))]]
+                                                         (.jvm_object_cast#
+                                                          (.jvm_long_+# (.jvm_object_cast# (ffi.byte_to_long base))
+                                                                        (.jvm_object_cast# (as java/lang/Long (/unsigned.value increment)))))))]]
                                 (..bytecode (|>> (as Int) (i.= (as Int expected)))
                                             (do /.monad
                                               [_ (..$Byte::literal base)
@@ -1199,7 +1198,7 @@
                                                _ /.i2l]
                                               ..$Long::wrap)))))))
          (<| (_.context "long")
-             (let [test (!::= java/lang/Long "jvm leq" "jvm long =")]
+             (let [test (!::= java/lang/Long "jvm leq" .jvm_long_=#)]
                (all _.and
                     (_.lifted "LSTORE_0/LLOAD_0"
                               (store_and_load ..$Long::random ..$Long::literal ..$Long::wrap [(function.constant /.lstore_0) (function.constant /.lload_0)] test))
@@ -1212,7 +1211,7 @@
                     (_.lifted "LSTORE/LLOAD"
                               (store_and_load ..$Long::random ..$Long::literal ..$Long::wrap [/.lstore /.lload] test)))))
          (<| (_.context "float")
-             (let [test (!::= java/lang/Float "jvm feq" "jvm float =")]
+             (let [test (!::= java/lang/Float "jvm feq" .jvm_float_=#)]
                (all _.and
                     (_.lifted "FSTORE_0/FLOAD_0"
                               (store_and_load ..valid_float ..$Float::literal ..$Float::wrap [(function.constant /.fstore_0) (function.constant /.fload_0)] test))
@@ -1225,7 +1224,7 @@
                     (_.lifted "FSTORE/FLOAD"
                               (store_and_load ..valid_float ..$Float::literal ..$Float::wrap [/.fstore /.fload] test)))))
          (<| (_.context "double")
-             (let [test (!::= java/lang/Double "jvm deq" "jvm double =")]
+             (let [test (!::= java/lang/Double "jvm deq" .jvm_double_=#)]
                (all _.and
                     (_.lifted "DSTORE_0/DLOAD_0"
                               (store_and_load ..valid_double ..$Double::literal ..$Double::wrap [(function.constant /.dstore_0) (function.constant /.dload_0)] test))
@@ -1359,26 +1358,26 @@
                                                       (list)
                                                       (list)
                                                       (list (/method.method ..method_modifier
-                                                                            primitive_method_name
-                                                                            false primitive_method_type
-                                                                            (list)
-                                                                            {.#Some (do /.monad
-                                                                                      [_ ((the #literal primitive) expected)]
-                                                                                      return)})
+                                                              primitive_method_name
+                                                              false primitive_method_type
+                                                              (list)
+                                                              {.#Some (do /.monad
+                                                                        [_ ((the #literal primitive) expected)]
+                                                                        return)})
                                                             (/method.method ..method_modifier
-                                                                            object_method_name
-                                                                            false (/type.method [(list) (list) (the #boxed primitive) (list)])
-                                                                            (list)
-                                                                            {.#Some (do /.monad
-                                                                                      [_ (/.invokestatic $Self primitive_method_name primitive_method_type)
-                                                                                       _ (when substitute
-                                                                                           {.#None}
-                                                                                           (in [])
-
-                                                                                           {.#Some substitute}
-                                                                                           (substitute expected))
-                                                                                       _ (the #wrap primitive)]
-                                                                                      /.areturn)}))
+                                                              object_method_name
+                                                              false (/type.method [(list) (list) (the #boxed primitive) (list)])
+                                                              (list)
+                                                              {.#Some (do /.monad
+                                                                        [_ (/.invokestatic $Self primitive_method_name primitive_method_type)
+                                                                         _ (when substitute
+                                                                             {.#None}
+                                                                             (in [])
+
+                                                                             {.#Some substitute}
+                                                                             (substitute expected))
+                                                                         _ (the #wrap primitive)]
+                                                                        /.areturn)}))
                                                       (sequence.sequence))
                                               .let [bytecode (binary.result /class.format class)
                                                     loader (/loader.memory (/loader.new_library []))]
@@ -1393,10 +1392,10 @@
                                        false)
                                      ))))]
     (all _.and
-         (_.lifted "IRETURN" (primitive_return ..$Integer::primitive /.ireturn {.#None} (!::= java/lang/Integer "jvm ieq" "jvm int =")))
-         (_.lifted "LRETURN" (primitive_return ..$Long::primitive /.lreturn {.#None} (!::= java/lang/Long "jvm leq" "jvm long =")))
-         (_.lifted "FRETURN" (primitive_return ..$Float::primitive /.freturn {.#None} (!::= java/lang/Float "jvm feq" "jvm float =")))
-         (_.lifted "DRETURN" (primitive_return ..$Double::primitive /.dreturn {.#None} (!::= java/lang/Double "jvm deq" "jvm double =")))
+         (_.lifted "IRETURN" (primitive_return ..$Integer::primitive /.ireturn {.#None} (!::= java/lang/Integer "jvm ieq" .jvm_int_=#)))
+         (_.lifted "LRETURN" (primitive_return ..$Long::primitive /.lreturn {.#None} (!::= java/lang/Long "jvm leq" .jvm_long_=#)))
+         (_.lifted "FRETURN" (primitive_return ..$Float::primitive /.freturn {.#None} (!::= java/lang/Float "jvm feq" .jvm_float_=#)))
+         (_.lifted "DRETURN" (primitive_return ..$Double::primitive /.dreturn {.#None} (!::= java/lang/Double "jvm deq" .jvm_double_=#)))
          (_.lifted "ARETURN" (primitive_return ..$String::primitive /.areturn {.#None} (function (_ expected actual) (text#= (as Text expected) (as Text actual)))))
          (_.lifted "RETURN" (primitive_return (is (Primitive java/lang/String)
                                                   [#unboxed /type.void
@@ -1416,7 +1415,7 @@
      dummy ..$Long::random
      .let [if! (is (-> (-> Label (Bytecode Any)) (Bytecode Any) (Random Bit))
                    (function (_ instruction prelude)
-                     (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected))
+                     (<| (..bytecode ((!::= java/lang/Long "jvm leq" .jvm_long_=#) expected))
                          (do /.monad
                            [@then /.new_label
                             @end /.new_label
@@ -1440,12 +1439,12 @@
                           (_.lifted "IFNONNULL" (if! /.ifnonnull (/.string ""))))]
      reference ..$Integer::random
      subject (|> ..$Integer::random
-                 (random.only (|>> ((!::= java/lang/Integer "jvm ieq" "jvm int =") reference) not)))
+                 (random.only (|>> ((!::= java/lang/Integer "jvm ieq" .jvm_int_=#) reference) not)))
      .let [[lesser greater] (if (for @.old
                                      ("jvm ilt" reference subject)
                                      
                                      @.jvm
-                                     ("jvm int <" ("jvm object cast" subject) ("jvm object cast" reference)))
+                                     (.jvm_int_<# (.jvm_object_cast# subject) (.jvm_object_cast# reference)))
                               [reference subject]
                               [subject reference])
            int_comparison (all _.and
@@ -1478,7 +1477,7 @@
      dummy ..$Long::random
      .let [jump (is (-> (-> Label (Bytecode Any)) (Random Bit))
                     (function (_ goto)
-                      (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected))
+                      (<| (..bytecode ((!::= java/lang/Long "jvm leq" .jvm_long_=#) expected))
                           (do /.monad
                             [@skipped /.new_label
                              @value /.new_label
@@ -1505,7 +1504,7 @@
               minimum (at ! each (|>> (n.% 100) .int /signed.s4 try.trusted)
                           random.nat)
               afterwards (at ! each (n.% 10) random.nat)])
-           (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected))
+           (..bytecode ((!::= java/lang/Long "jvm leq" .jvm_long_=#) expected))
            (do /.monad
              [@right /.new_label
               @wrong /.new_label
@@ -1531,7 +1530,7 @@
               .let [choice (maybe.trusted (list.item choice options))]
               expected ..$Long::random
               dummy ..$Long::random])
-           (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected))
+           (..bytecode ((!::= java/lang/Long "jvm leq" .jvm_long_=#) expected))
            (do /.monad
              [@right /.new_label
               @wrong /.new_label
@@ -1557,7 +1556,7 @@
      dummy ..$Long::random
      exception ..$String::random]
     (<| (_.lifted "ATHROW")
-        (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected))
+        (..bytecode ((!::= java/lang/Long "jvm leq" .jvm_long_=#) expected))
         (do /.monad
           [.let [$Exception (/type.class "java.lang.Exception" (list))]
            @skipped /.new_label
@@ -1645,12 +1644,12 @@
            method (is (-> Text java/lang/Long (Resource Method))
                       (function (_ name value)
                         (/method.method /method.public
-                                        name
-                                        false method::type
-                                        (list)
-                                        {.#Some (do /.monad
-                                                  [_ (..$Long::literal value)]
-                                                  /.lreturn)})))
+                          name
+                          false method::type
+                          (list)
+                          {.#Some (do /.monad
+                                    [_ (..$Long::literal value)]
+                                    /.lreturn)})))
 
            interface_bytecode (|> (/class.class /version.v6_0 (all /modifier#composite /class.public /class.abstract /class.interface)
                                     (/name.internal interface_class)
@@ -1659,7 +1658,7 @@
                                     (list)
                                     (list)
                                     (list (/method.method (all /modifier#composite /method.public /method.abstract)
-                                                          interface_method false method::type (list) {.#None}))
+                                            interface_method false method::type (list) {.#None}))
                                     (sequence.sequence))
                                   try.trusted
                                   (binary.result /class.format))
@@ -1670,17 +1669,17 @@
                                    (list)
                                    (list)
                                    (list (/method.method /method.public
-                                                         ""
-                                                         false constructor::type
-                                                         (list)
-                                                         {.#Some (do /.monad
-                                                                   [_ /.aload_0
-                                                                    _ (/.invokespecial ..$Object "" constructor::type)]
-                                                                   /.return)})
+                                           ""
+                                           false constructor::type
+                                           (list)
+                                           {.#Some (do /.monad
+                                                     [_ /.aload_0
+                                                      _ (/.invokespecial ..$Object "" constructor::type)]
+                                                     /.return)})
                                          (method inherited_method part0)
                                          (method overriden_method fake_part2)
                                          (/method.method (all /modifier#composite /method.public /method.abstract)
-                                                         abstract_method false method::type (list) {.#None}))
+                                           abstract_method false method::type (list) {.#None}))
                                    (sequence.sequence))
                                  try.trusted
                                  (binary.result /class.format))
@@ -1696,13 +1695,13 @@
                                    (list (/name.internal interface_class))
                                    (list)
                                    (list (/method.method /method.public
-                                                         ""
-                                                         false constructor::type
-                                                         (list)
-                                                         {.#Some (do /.monad
-                                                                   [_ /.aload_0
-                                                                    _ (/.invokespecial $Abstract "" constructor::type)]
-                                                                   /.return)})
+                                           ""
+                                           false constructor::type
+                                           (list)
+                                           {.#Some (do /.monad
+                                                     [_ /.aload_0
+                                                      _ (/.invokespecial $Abstract "" constructor::type)]
+                                                     /.return)})
                                          (method virtual_method part1)
                                          (method overriden_method part2)
                                          (method abstract_method part3)
@@ -1710,25 +1709,25 @@
                                          (/method.method (all /modifier#composite
                                                               /method.public
                                                               /method.static)
-                                                         static_method
-                                                         false (/type.method [(list) (list) ..$Long (list)])
-                                                         (list)
-                                                         {.#Some (do /.monad
-                                                                   [_ (/.new $Concrete)
-                                                                    _ /.dup
-                                                                    _ (/.invokespecial $Concrete "" constructor::type)
-                                                                    _ /.astore_0
-                                                                    _ (invoke $Abstract inherited_method)
-                                                                    _ (invoke $Concrete virtual_method)
-                                                                    _ /.ladd
-                                                                    _ (invoke $Abstract overriden_method)
-                                                                    _ /.ladd
-                                                                    _ /.aload_0 _ (/.invokeinterface $Interface interface_method method::type)
-                                                                    _ /.ladd
-                                                                    _ (invoke $Abstract abstract_method)
-                                                                    _ /.ladd
-                                                                    _ ..$Long::wrap]
-                                                                   /.areturn)}))
+                                           static_method
+                                           false (/type.method [(list) (list) ..$Long (list)])
+                                           (list)
+                                           {.#Some (do /.monad
+                                                     [_ (/.new $Concrete)
+                                                      _ /.dup
+                                                      _ (/.invokespecial $Concrete "" constructor::type)
+                                                      _ /.astore_0
+                                                      _ (invoke $Abstract inherited_method)
+                                                      _ (invoke $Concrete virtual_method)
+                                                      _ /.ladd
+                                                      _ (invoke $Abstract overriden_method)
+                                                      _ /.ladd
+                                                      _ /.aload_0 _ (/.invokeinterface $Interface interface_method method::type)
+                                                      _ /.ladd
+                                                      _ (invoke $Abstract abstract_method)
+                                                      _ /.ladd
+                                                      _ ..$Long::wrap]
+                                                     /.areturn)}))
                                    (sequence.sequence))
                                  try.trusted
                                  (binary.result /class.format))
diff --git a/stdlib/source/test/lux/world/net.lux b/stdlib/source/test/lux/world/net.lux
index a6d74f5c6..29427d6c3 100644
--- a/stdlib/source/test/lux/world/net.lux
+++ b/stdlib/source/test/lux/world/net.lux
@@ -12,7 +12,8 @@
  ["[0]" /
   ["[1][0]" http
    ["[1]/[0]" client]
-   ["[1]/[0]" status]]])
+   ["[1]/[0]" status]
+   ["[1]/[0]" version]]])
 
 (def .public test
   Test
@@ -31,4 +32,5 @@
 
            /http/client.test
            /http/status.test
+           /http/version.test
            )))
diff --git a/stdlib/source/test/lux/world/net/http/version.lux b/stdlib/source/test/lux/world/net/http/version.lux
new file mode 100644
index 000000000..f005e944b
--- /dev/null
+++ b/stdlib/source/test/lux/world/net/http/version.lux
@@ -0,0 +1,48 @@
+(.require
+ [library
+  [lux (.except)
+   [abstract
+    [monad (.only do)]
+    [\\specification
+     ["$[0]" equivalence]
+     ["$[0]" hash]]]
+   [data
+    [collection
+     ["[0]" list]
+     ["[0]" set]]]
+   [math
+    ["[0]" random (.only Random) (.use "[1]#[0]" monad)]
+    [number
+     ["n" nat]]]
+   [test
+    ["_" property (.only Test)]]]]
+ [\\library
+  ["[0]" /]])
+
+(def .public random
+  (Random /.Version)
+  (all random.or
+       (random#in /.v0_9)
+       (random#in /.v1_0)
+       (random#in /.v1_1)
+       (random#in /.v2_0)
+       ))
+
+(def .public test
+  Test
+  (<| (_.covering /._)
+      (do [! random.monad]
+        [])
+      (_.for [/.Version])
+      (all _.and
+           (_.for [/.equivalence]
+                  ($equivalence.spec /.equivalence ..random))
+           (_.for [/.hash]
+                  ($hash.spec /.hash ..random))
+
+           (_.coverage [/.v0_9 /.v1_0 /.v1_1 /.v2_0]
+             (let [options (list /.v0_9 /.v1_0 /.v1_1 /.v2_0)
+                   uniques (set.empty /.hash options)]
+               (n.= (list.size options)
+                    (set.size uniques))))
+           )))
diff --git a/stdlib/source/unsafe/lux/data/collection/array.lux b/stdlib/source/unsafe/lux/data/collection/array.lux
index 6f85f60bb..c8c98508c 100644
--- a/stdlib/source/unsafe/lux/data/collection/array.lux
+++ b/stdlib/source/unsafe/lux/data/collection/array.lux
@@ -28,8 +28,8 @@
                (template (jvm_int value)
                  [(.|> value
                        (.as )
-                       "jvm object cast"
-                       "jvm conversion long-to-int")]))
+                       .jvm_object_cast#
+                       .jvm_conversion_long_to_int#)]))
        (these))
   
   (`` (def .public empty
@@ -42,7 +42,7 @@
 
                           (,, (.static @.jvm))
                           (|> (,, (..jvm_int size))
-                              "jvm array new object"
+                              .jvm_array_new_object#
                               (.is (..Array )))
 
                           (,, (.static @.js)) ("js array new" size)
@@ -62,9 +62,9 @@
 
                          (,, (.static @.jvm))
                          (.|> array
-                              "jvm array length object"
-                              "jvm conversion int-to-long"
-                              "jvm object cast"
+                              .jvm_array_length_object#
+                              .jvm_conversion_int_to_long#
+                              .jvm_object_cast#
                               (.is )
                               (.as .Nat))
 
@@ -92,8 +92,8 @@
 
                              (,, (.static @.jvm))
                              (.|> array
-                                  ("jvm array read object" (,, (jvm_int index)))
-                                  "jvm object null?")
+                                  (.jvm_array_read_object# (,, (jvm_int index)))
+                                  .jvm_object_null?#)
 
                              (,, (.static @.js)) (,, (lacks?' "js array read" "js object undefined?" index array))
                              (,, (.static @.python)) (,, (lacks?' "python array read" "python object none?" index array))
@@ -118,7 +118,7 @@
                           ("jvm aaload" array index)
 
                           (,, (.static @.jvm))
-                          ("jvm array read object" (,, (jvm_int index)) array)
+                          (.jvm_array_read_object# (,, (jvm_int index)) array)
 
                           (,, (.static @.js)) ("js array read" index array)
                           (,, (.static @.python)) ("python array read" index array)
@@ -138,7 +138,7 @@
 
                          (,, (.static @.jvm))
                          (.|> array
-                              ("jvm array write object" (,, (jvm_int index)) value)
+                              (.jvm_array_write_object# (,, (jvm_int index)) value)
                               .as_expected)
 
                          (,, (.static @.js)) ("js array write" index (.as_expected value) array)
@@ -160,7 +160,7 @@
                              (..has! index (.as_expected ("jvm object null")) array)
                              
                              (,, (.static @.jvm))
-                             (..has! index (.as_expected (is  ("jvm object null"))) array)
+                             (..has! index (.as_expected (is  (.jvm_object_null#))) array)
 
                              (,, (.static @.js)) ("js array delete" index array)
                              (,, (.static @.python)) ("python array delete" index array)
-- 
cgit v1.2.3