aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
authorEduardo Julian2022-06-26 18:37:05 -0400
committerEduardo Julian2022-06-26 18:37:05 -0400
commit9f6505491e8a5c8a159ce094fe0af6f4fef0c5cf (patch)
treed497c163e477406a388460eedea80fdd6ee9748a /stdlib/source/test
parent3053fd79bc6ae42415298ee056a268dc2c9b690c (diff)
Re-named "format/lux/data/binary.Writer" to "Format".
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/aedifex/command/deploy.lux2
-rw-r--r--stdlib/source/test/lux/data/binary.lux4
-rw-r--r--stdlib/source/test/lux/data/format/tar.lux18
-rw-r--r--stdlib/source/test/lux/extension.lux2
-rw-r--r--stdlib/source/test/lux/target/jvm.lux402
-rw-r--r--stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux4
-rw-r--r--stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux4
-rw-r--r--stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux4
-rw-r--r--stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux4
-rw-r--r--stdlib/source/test/lux/tool/compiler/meta/import.lux12
10 files changed, 228 insertions, 228 deletions
diff --git a/stdlib/source/test/aedifex/command/deploy.lux b/stdlib/source/test/aedifex/command/deploy.lux
index 38aa5aebc..a38f12ad0 100644
--- a/stdlib/source/test/aedifex/command/deploy.lux
+++ b/stdlib/source/test/aedifex/command/deploy.lux
@@ -90,7 +90,7 @@
(the ///.#sources)
set.list
(export.library fs)
- (at ! each (format.result tar.writer)))
+ (at ! each (format.result tar.format)))
actual_pom (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.pom))
actual_library (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.lux_library))
diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux
index 4ae5fc849..1389e4620 100644
--- a/stdlib/source/test/lux/data/binary.lux
+++ b/stdlib/source/test/lux/data/binary.lux
@@ -86,7 +86,7 @@
(Equivalence Location)
(implementation
(def (= [expected_module expected_line expected_column]
- [sample_module sample_line sample_column])
+ [sample_module sample_line sample_column])
(and (text#= expected_module sample_module)
(n.= expected_line sample_line)
(n.= expected_column sample_column)))))
@@ -413,7 +413,7 @@
(def \\format
Test
(<| (_.covering \\format._)
- (_.for [\\format.Mutation \\format.Specification \\format.Writer])
+ (_.for [\\format.Mutation \\format.Specification \\format.Format])
(all _.and
(_.for [\\format.monoid]
($monoid.spec ..equivalence \\format.monoid ..random_specification))
diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux
index 5cf8a6d35..349149b22 100644
--- a/stdlib/source/test/lux/data/format/tar.lux
+++ b/stdlib/source/test/lux/data/format/tar.lux
@@ -171,7 +171,7 @@
(|> (do try.monad
[expected_path (/.path expected_path)
tar (|> (sequence.sequence {<tag> expected_path})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {<tag> actual_path}))
@@ -200,7 +200,7 @@
/.#group [/.#name /.anonymous
/.#id /.no_id]]
expected_content]})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]}))
@@ -258,7 +258,7 @@
/.#group [/.#name /.anonymous
/.#id /.no_id]]
content]})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {/.#Normal [_ _ actual_mode _ _]}))
@@ -281,7 +281,7 @@
/.#group [/.#name /.anonymous
/.#id /.no_id]]
content]})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {/.#Normal [_ _ actual_mode _ _]}))
@@ -348,7 +348,7 @@
/.#group [/.#name /.anonymous
/.#id /.no_id]]
content]})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {/.#Normal [_ _ _ actual_ownership _]}))
@@ -372,7 +372,7 @@
/.#group [/.#name /.anonymous
/.#id /.no_id]]
content]})
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser))]
(in (case (sequence.list tar)
(pattern (list {/.#Normal [_ _ _ actual_ownership _]}))
@@ -397,14 +397,14 @@
(do random.monad
[_ (in [])]
(all _.and
- (_.coverage [/.writer /.parser]
+ (_.coverage [/.format /.parser]
(|> sequence.empty
- (\\format.result /.writer)
+ (\\format.result /.format)
(<b>.result /.parser)
(at try.monad each sequence.empty?)
(try.else false)))
(_.coverage [/.invalid_end_of_archive]
- (let [dump (\\format.result /.writer sequence.empty)]
+ (let [dump (\\format.result /.format sequence.empty)]
(case (<b>.result /.parser (binary#composite dump dump))
{try.#Success _}
false
diff --git a/stdlib/source/test/lux/extension.lux b/stdlib/source/test/lux/extension.lux
index e23bd23ea..58b5cd3fd 100644
--- a/stdlib/source/test/lux/extension.lux
+++ b/stdlib/source/test/lux/extension.lux
@@ -158,7 +158,7 @@
(for @.jvm (let [$class (jvm/runtime.class_name [module_id artifact_id])]
(<| [$class]
(try.else (binary.empty 0))
- (try#each (binaryF.result class.writer))
+ (try#each (binaryF.result class.format))
(class.class version.v6_0 class.public
(name.internal $class)
{.#None}
diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux
index c282c2250..fd972f3e0 100644
--- a/stdlib/source/test/lux/target/jvm.lux
+++ b/stdlib/source/test/lux/target/jvm.lux
@@ -125,20 +125,20 @@
method_name (random.upper_case 10)]
(in (case (do try.monad
[class (/class.class /version.v6_0 /class.public
- (/name.internal class_name)
- {.#None}
- (/name.internal "java.lang.Object")
- (list)
- (list)
- (list (/method.method ..method_modifier
- method_name
- #0 (/type.method [(list) (list) ..$Object (list)])
- (list)
- {.#Some (do /.monad
- [_ bytecode]
- /.areturn)}))
- (sequence.sequence))
- .let [bytecode (binary.result /class.writer class)
+ (/name.internal class_name)
+ {.#None}
+ (/name.internal "java.lang.Object")
+ (list)
+ (list)
+ (list (/method.method ..method_modifier
+ method_name
+ #0 (/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 []))]
_ (/loader.define class_name bytecode loader)
class (io.run! (/loader.load class_name loader))
@@ -872,44 +872,44 @@
constructor::type (/type.method [(list) (list /type.long) /type.void (list)])
static_method "static_method"
bytecode (|> (/class.class /version.v6_0 /class.public
- (/name.internal class_name)
- {.#None}
- (/name.internal "java.lang.Object")
- (list)
- (list (/field.field /field.static class_field #0 /type.long (sequence.sequence))
- (/field.field /field.public object_field #0 /type.long (sequence.sequence)))
- (list (/method.method /method.private
- constructor
- #0 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
- #0 (/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))
+ (/name.internal class_name)
+ {.#None}
+ (/name.internal "java.lang.Object")
+ (list)
+ (list (/field.field /field.static class_field #0 /type.long (sequence.sequence))
+ (/field.field /field.public object_field #0 /type.long (sequence.sequence)))
+ (list (/method.method /method.private
+ constructor
+ #0 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
+ #0 (/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.writer))
+ (binary.result /class.format))
loader (/loader.memory (/loader.new_library []))]]
(_.property "PUTSTATIC & PUTFIELD & GETFIELD & GETSTATIC"
(case (do try.monad
@@ -974,67 +974,67 @@
(write_and_read size constructor value literal [*store *load *wrap] test))))))]
(all _.and
(_.context "boolean"
- (array (/.newarray /instruction.t_boolean) $Boolean::random $Boolean::literal [/.bastore /.baload $Boolean::wrap]
- (function (_ expected) (|>> (as Bit) (bit#= (as Bit expected))))))
+ (array (/.newarray /instruction.t_boolean) $Boolean::random $Boolean::literal [/.bastore /.baload $Boolean::wrap]
+ (function (_ expected) (|>> (as Bit) (bit#= (as Bit expected))))))
(_.context "byte"
- (array (/.newarray /instruction.t_byte) $Byte::random $Byte::literal [/.bastore /.baload $Byte::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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)))))))))
+ (array (/.newarray /instruction.t_byte) $Byte::random $Byte::literal [/.bastore /.baload $Byte::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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)))))))))
(_.context "short"
- (array (/.newarray /instruction.t_short) $Short::random $Short::literal [/.sastore /.saload $Short::wrap]
- (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)))))))))
+ (array (/.newarray /instruction.t_short) $Short::random $Short::literal [/.sastore /.saload $Short::wrap]
+ (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)))))))))
(_.context "int"
- (array (/.newarray /instruction.t_int) $Integer::random $Integer::literal [/.iastore /.iaload $Integer::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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))))))))
+ (array (/.newarray /instruction.t_int) $Integer::random $Integer::literal [/.iastore /.iaload $Integer::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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))))))))
(_.context "long"
- (array (/.newarray /instruction.t_long) $Long::random $Long::literal [/.lastore /.laload $Long::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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))))))))
+ (array (/.newarray /instruction.t_long) $Long::random $Long::literal [/.lastore /.laload $Long::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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))))))))
(_.context "float"
- (array (/.newarray /instruction.t_float) ..valid_float $Float::literal [/.fastore /.faload $Float::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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))))))))
+ (array (/.newarray /instruction.t_float) ..valid_float $Float::literal [/.fastore /.faload $Float::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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))))))))
(_.context "double"
- (array (/.newarray /instruction.t_double) ..valid_double $Double::literal [/.dastore /.daload $Double::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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))))))))
+ (array (/.newarray /instruction.t_double) ..valid_double $Double::literal [/.dastore /.daload $Double::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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))))))))
(_.context "char"
- (array (/.newarray /instruction.t_char) $Character::random $Character::literal [/.castore /.caload $Character::wrap]
- (function (_ expected)
- (for @.old
- (|>> (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))))))))
+ (array (/.newarray /instruction.t_char) $Character::random $Character::literal [/.castore /.caload $Character::wrap]
+ (function (_ expected)
+ (for @.old
+ (|>> (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))))))))
(_.context "object"
- (array (/.anewarray ..$String) $String::random $String::literal [/.aastore /.aaload /.nop]
- (function (_ expected) (|>> (as Text) (text#= (as Text expected))))))
+ (array (/.anewarray ..$String) $String::random $String::literal [/.aastore /.aaload /.nop]
+ (function (_ expected) (|>> (as Text) (text#= (as Text expected))))))
(<| (_.context "multi")
(do [! random.monad]
[.let [size (at ! each (|>> (n.% 5) (n.+ 1))
@@ -1351,34 +1351,34 @@
.let [$Self (/type.class class_name (list))]]
(in (case (do try.monad
[class (/class.class /version.v6_0 /class.public
- (/name.internal class_name)
- {.#None}
- (/name.internal "java.lang.Object")
- (list)
- (list)
- (list (/method.method ..method_modifier
- primitive_method_name
- #0 primitive_method_type
- (list)
- {.#Some (do /.monad
- [_ ((the #literal primitive) expected)]
- return)})
- (/method.method ..method_modifier
- object_method_name
- #0 (/type.method [(list) (list) (the #boxed primitive) (list)])
- (list)
- {.#Some (do /.monad
- [_ (/.invokestatic $Self primitive_method_name primitive_method_type)
- _ (case substitute
- {.#None}
- (in [])
-
- {.#Some substitute}
- (substitute expected))
- _ (the #wrap primitive)]
- /.areturn)}))
- (sequence.sequence))
- .let [bytecode (binary.result /class.writer class)
+ (/name.internal class_name)
+ {.#None}
+ (/name.internal "java.lang.Object")
+ (list)
+ (list)
+ (list (/method.method ..method_modifier
+ primitive_method_name
+ #0 primitive_method_type
+ (list)
+ {.#Some (do /.monad
+ [_ ((the #literal primitive) expected)]
+ return)})
+ (/method.method ..method_modifier
+ object_method_name
+ #0 (/type.method [(list) (list) (the #boxed primitive) (list)])
+ (list)
+ {.#Some (do /.monad
+ [_ (/.invokestatic $Self primitive_method_name primitive_method_type)
+ _ (case 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 []))]
_ (/loader.define class_name bytecode loader)
class (io.run! (/loader.load class_name loader))
@@ -1651,85 +1651,85 @@
/.lreturn)})))
interface_bytecode (|> (/class.class /version.v6_0 (all /modifier#composite /class.public /class.abstract /class.interface)
- (/name.internal interface_class)
- {.#None}
- (/name.internal "java.lang.Object")
- (list)
- (list)
- (list (/method.method (all /modifier#composite /method.public /method.abstract)
- interface_method #0 method::type (list) {.#None}))
- (sequence.sequence))
+ (/name.internal interface_class)
+ {.#None}
+ (/name.internal "java.lang.Object")
+ (list)
+ (list)
+ (list (/method.method (all /modifier#composite /method.public /method.abstract)
+ interface_method #0 method::type (list) {.#None}))
+ (sequence.sequence))
try.trusted
- (binary.result /class.writer))
+ (binary.result /class.format))
abstract_bytecode (|> (/class.class /version.v6_0 (all /modifier#composite /class.public /class.abstract)
- (/name.internal abstract_class)
- {.#None}
- (/name.internal "java.lang.Object")
- (list)
- (list)
- (list (/method.method /method.public
- "<init>"
- #0 constructor::type
- (list)
- {.#Some (do /.monad
- [_ /.aload_0
- _ (/.invokespecial ..$Object "<init>" constructor::type)]
- /.return)})
- (method inherited_method part0)
- (method overriden_method fake_part2)
- (/method.method (all /modifier#composite /method.public /method.abstract)
- abstract_method #0 method::type (list) {.#None}))
- (sequence.sequence))
+ (/name.internal abstract_class)
+ {.#None}
+ (/name.internal "java.lang.Object")
+ (list)
+ (list)
+ (list (/method.method /method.public
+ "<init>"
+ #0 constructor::type
+ (list)
+ {.#Some (do /.monad
+ [_ /.aload_0
+ _ (/.invokespecial ..$Object "<init>" constructor::type)]
+ /.return)})
+ (method inherited_method part0)
+ (method overriden_method fake_part2)
+ (/method.method (all /modifier#composite /method.public /method.abstract)
+ abstract_method #0 method::type (list) {.#None}))
+ (sequence.sequence))
try.trusted
- (binary.result /class.writer))
+ (binary.result /class.format))
invoke (is (-> (Type Class) Text (Bytecode Any))
(function (_ class method)
(do /.monad
[_ /.aload_0]
(/.invokevirtual class method method::type))))
concrete_bytecode (|> (/class.class /version.v6_0 /class.public
- (/name.internal concrete_class)
- {.#None}
- (/name.internal abstract_class)
- (list (/name.internal interface_class))
- (list)
- (list (/method.method /method.public
- "<init>"
- #0 constructor::type
- (list)
- {.#Some (do /.monad
- [_ /.aload_0
- _ (/.invokespecial $Abstract "<init>" constructor::type)]
- /.return)})
- (method virtual_method part1)
- (method overriden_method part2)
- (method abstract_method part3)
- (method interface_method part4)
- (/method.method (all /modifier#composite
- /method.public
- /method.static)
- static_method
- #0 (/type.method [(list) (list) ..$Long (list)])
- (list)
- {.#Some (do /.monad
- [_ (/.new $Concrete)
- _ /.dup
- _ (/.invokespecial $Concrete "<init>" 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))
+ (/name.internal concrete_class)
+ {.#None}
+ (/name.internal abstract_class)
+ (list (/name.internal interface_class))
+ (list)
+ (list (/method.method /method.public
+ "<init>"
+ #0 constructor::type
+ (list)
+ {.#Some (do /.monad
+ [_ /.aload_0
+ _ (/.invokespecial $Abstract "<init>" constructor::type)]
+ /.return)})
+ (method virtual_method part1)
+ (method overriden_method part2)
+ (method abstract_method part3)
+ (method interface_method part4)
+ (/method.method (all /modifier#composite
+ /method.public
+ /method.static)
+ static_method
+ #0 (/type.method [(list) (list) ..$Long (list)])
+ (list)
+ {.#Some (do /.monad
+ [_ (/.new $Concrete)
+ _ /.dup
+ _ (/.invokespecial $Concrete "<init>" 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.writer))
+ (binary.result /class.format))
loader (/loader.memory (/loader.new_library []))]]
(_.property "Class & interface inheritance"
(case (do try.monad
diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux
index 1357295a1..fd3103d21 100644
--- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux
+++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux
@@ -49,9 +49,9 @@
(_.for [/.Module]
(_.coverage [/.runtime]
(text#= "" /.runtime)))
- (_.coverage [/.writer /.parser]
+ (_.coverage [/.format /.parser]
(|> expected
- (binary.result /.writer)
+ (binary.result /.format)
(<binary>.result /.parser)
(try#each (|>> (at /.equivalence = (has /.#state {.#Cached} expected))))
(try.else false)))
diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux
index 4637d7f39..b1ab4c5ec 100644
--- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux
+++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux
@@ -79,10 +79,10 @@
{try.#Failure error}
(exception.match? /.invalid_signature error)))))
- (_.coverage [/.writer /.parser]
+ (_.coverage [/.format /.parser]
(|> expected
(/.document key/0)
- (binaryF.result (/.writer binaryF.nat))
+ (binaryF.result (/.format binaryF.nat))
(<binary>.result (/.parser key/0 <binary>.nat))
(pipe.case
{try.#Success it}
diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux
index 2a1732cb8..53d3abd61 100644
--- a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux
+++ b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux
@@ -158,12 +158,12 @@
[/.directive /.directives text.equivalence (|>>)]
[/.custom /.customs text.equivalence (|>>)]
))))
- (_.coverage [/.writer /.parser]
+ (_.coverage [/.format /.parser]
(and (~~ (with_template [<new> <expected>' <name>]
[(let [<expected> <expected>'
[@expected before] (<new> <expected> mandatory? expected_dependencies /.empty)]
(|> before
- (binary.result /.writer)
+ (binary.result /.format)
(<binary>.result /.parser)
(try#each (|>> (/.id (<name> <expected>))
(maybe#each (same? @expected))
diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux
index 683ed09b4..2d75deca0 100644
--- a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux
+++ b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux
@@ -46,9 +46,9 @@
(text#= (/.description left) (/.description right)))))
(do random.monad
[expected ..random]
- (_.coverage [/.writer /.parser]
+ (_.coverage [/.format /.parser]
(|> expected
- (binaryF.result /.writer)
+ (binaryF.result /.format)
(<binary>.result /.parser)
(try#each (at /.equivalence = expected))
(try.else false))))
diff --git a/stdlib/source/test/lux/tool/compiler/meta/import.lux b/stdlib/source/test/lux/tool/compiler/meta/import.lux
index 6c98680d0..fc2e79616 100644
--- a/stdlib/source/test/lux/tool/compiler/meta/import.lux
+++ b/stdlib/source/test/lux/tool/compiler/meta/import.lux
@@ -66,35 +66,35 @@
content/1 (tar.content content/1)]
(in (|> (sequence.sequence {tar.#Normal [file/0 now export.mode export.ownership content/0]}
{tar.#Normal [file/1 now export.mode export.ownership content/1]})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
library_content/0 (|> (do try.monad
[file/0 (tar.path file/0)
content/0 (tar.content content/0)]
(in (|> (sequence.sequence {tar.#Normal [file/0 now export.mode export.ownership content/0]})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
library_content/1 (|> (do try.monad
[file/1 (tar.path file/1)
content/1 (tar.content content/1)]
(in (|> (sequence.sequence {tar.#Normal [file/1 now export.mode export.ownership content/1]})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
library_content/-0 (|> (do try.monad
[file/0 (tar.path file/0)
content/0 (tar.content content/0)]
(in (|> (sequence.sequence {tar.#Contiguous [file/0 now export.mode export.ownership content/0]})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
library_content/-1 (|> (do try.monad
[file/0 (tar.path file/0)]
(in (|> (sequence.sequence {tar.#Symbolic_Link file/0})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
library_content/-2 (|> (do try.monad
[file/0 (tar.path file/0)]
(in (|> (sequence.sequence {tar.#Directory file/0})
- (\\format.result tar.writer))))
+ (\\format.result tar.format))))
(try.else (binary.empty 0)))
imported? (is (-> /.Import Bit)
(function (_ it)