From fbc9f6f9186254263255f03a9378216adfbeaa0e Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 20 Jun 2019 23:14:40 -0400 Subject: Re-structured encoding-related modules a bit. --- stdlib/source/lux/target/jvm/attribute.lux | 19 +++---- stdlib/source/lux/target/jvm/attribute/code.lux | 23 +++++---- .../lux/target/jvm/attribute/code/exception.lux | 13 ++--- .../source/lux/target/jvm/attribute/code/label.lux | 7 +-- .../source/lux/target/jvm/attribute/constant.lux | 5 +- stdlib/source/lux/target/jvm/class.lux | 11 ++-- stdlib/source/lux/target/jvm/constant.lux | 5 +- stdlib/source/lux/target/jvm/constant/pool.lux | 9 ++-- stdlib/source/lux/target/jvm/constant/tag.lux | 12 +++-- stdlib/source/lux/target/jvm/descriptor.lux | 3 +- stdlib/source/lux/target/jvm/encoding.lux | 59 ---------------------- stdlib/source/lux/target/jvm/encoding/name.lux | 32 ++++++++++++ stdlib/source/lux/target/jvm/encoding/unsigned.lux | 59 ++++++++++++++++++++++ stdlib/source/lux/target/jvm/field.lux | 1 - stdlib/source/lux/target/jvm/index.lux | 7 +-- stdlib/source/lux/target/jvm/magic.lux | 7 +-- stdlib/source/lux/target/jvm/method.lux | 1 - stdlib/source/lux/target/jvm/modifier.lux | 15 +++--- stdlib/source/lux/target/jvm/name.lux | 32 ------------ stdlib/source/lux/target/jvm/version.lux | 7 +-- stdlib/source/test/lux/target/jvm.lux | 3 +- 21 files changed, 172 insertions(+), 158 deletions(-) delete mode 100644 stdlib/source/lux/target/jvm/encoding.lux create mode 100644 stdlib/source/lux/target/jvm/encoding/name.lux create mode 100644 stdlib/source/lux/target/jvm/encoding/unsigned.lux delete mode 100644 stdlib/source/lux/target/jvm/name.lux (limited to 'stdlib/source') diff --git a/stdlib/source/lux/target/jvm/attribute.lux b/stdlib/source/lux/target/jvm/attribute.lux index e2db85282..82ca49111 100644 --- a/stdlib/source/lux/target/jvm/attribute.lux +++ b/stdlib/source/lux/target/jvm/attribute.lux @@ -15,8 +15,9 @@ [world ["." binary (#+ Binary)]]] ["." // #_ - ["#." encoding (#+ U2 U4)] ["#." index (#+ Index)] + [encoding + ["#." unsigned (#+ U2 U4)]] ["#." constant (#+ UTF8 Class Value) ["#/." pool (#+ Pool)]]] ["." / #_ @@ -34,7 +35,7 @@ (Equivalence (Info about)))) ($_ equivalence.product //index.equivalence - //encoding.equivalence + //unsigned.equivalence Equivalence)) (def: (info-writer writer) @@ -43,7 +44,7 @@ (Writer (Info about)))) (function (_ [name length info]) (let [[nameS nameT] ((get@ #binaryF.writer //index.format) name) - [lengthS lengthT] ((get@ #binaryF.writer //encoding.u4-format) length) + [lengthS lengthT] ((get@ #binaryF.writer //unsigned.u4-format) length) [infoS infoT] (writer info)] [($_ n/+ nameS lengthS infoS) (|>> nameT lengthT infoT)]))) @@ -68,9 +69,9 @@ (def: fixed-attribute-length ($_ n/+ ## u2 attribute_name_index; - //encoding.u2-bytes + //unsigned.u2-bytes ## u4 attribute_length; - //encoding.u4-bytes + //unsigned.u4-bytes )) (def: (length attribute) @@ -78,7 +79,7 @@ (case attribute (^template [] ( [name length info]) - (|> length //encoding.nat .nat (n/+ fixed-attribute-length))) + (|> length //unsigned.nat .nat (n/+ fixed-attribute-length))) ([#Constant] [#Code]))) (def: constant-name "ConstantValue") @@ -86,7 +87,7 @@ (def: (constant' @name index) (-> (Index UTF8) Constant Attribute) (#Constant {#name @name - #length (//encoding.u4 /constant.length) + #length (//unsigned.u4 /constant.length) #info index})) (def: #export (constant index) @@ -101,7 +102,7 @@ (-> (Index UTF8) Code Attribute) (#Code {#name @name ## https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3 - #length (//encoding.u4 + #length (//unsigned.u4 (/code.length ..length specification)) #info specification})) @@ -128,7 +129,7 @@ (function (_ reader) (do <>.monad [@name (get@ #binaryF.reader //index.format) - length (get@ #binaryF.reader //encoding.u4-format)] + length (get@ #binaryF.reader //unsigned.u4-format)] (cond (_@= ?@constant (#error.Success @name)) (:: @ map (..constant' @name) (get@ #binaryF.reader /constant.format)) diff --git a/stdlib/source/lux/target/jvm/attribute/code.lux b/stdlib/source/lux/target/jvm/attribute/code.lux index d30bfa806..c466fa838 100644 --- a/stdlib/source/lux/target/jvm/attribute/code.lux +++ b/stdlib/source/lux/target/jvm/attribute/code.lux @@ -13,7 +13,8 @@ [world ["." binary (#+ Binary)]]] ["." /// #_ - ["#." encoding (#+ U2)]] + [encoding + ["#." unsigned (#+ U2)]]] ["." / #_ ["#." exception (#+ Exception)]]) @@ -28,22 +29,22 @@ (All [Attribute] (-> (-> Attribute Nat) (Code Attribute) Nat)) ($_ n/+ ## u2 max_stack; - ///encoding.u2-bytes + ///unsigned.u2-bytes ## u2 max_locals; - ///encoding.u2-bytes + ///unsigned.u2-bytes ## u4 code_length; - ///encoding.u4-bytes + ///unsigned.u4-bytes ## u1 code[code_length]; (binary.size (get@ #code code)) ## u2 exception_table_length; - ///encoding.u2-bytes + ///unsigned.u2-bytes ## exception_table[exception_table_length]; (|> code (get@ #exception-table) row.size (n/* /exception.length)) ## u2 attributes_count; - ///encoding.u2-bytes + ///unsigned.u2-bytes ## attribute_info attributes[attributes_count]; (|> code (get@ #attributes) @@ -54,8 +55,8 @@ (All [attribute] (-> (Equivalence attribute) (Equivalence (Code attribute)))) ($_ equivalence.product - ///encoding.equivalence - ///encoding.equivalence + ///unsigned.equivalence + ///unsigned.equivalence binary.equivalence (row.equivalence /exception.equivalence) (row.equivalence attribute-equivalence) @@ -65,7 +66,7 @@ (def: #export (reader reader) (All [Attribute] (-> (Reader Attribute) (Reader (Code Attribute)))) (let [u2-reader (get@ #binaryF.reader - ///encoding.u2-format)] + ///unsigned.u2-format)] ($_ <>.and ## u2 max_stack; u2-reader @@ -92,10 +93,10 @@ (All [Attribute] (-> (Writer Attribute) (Writer (Code Attribute)))) ($_ binaryF@compose ## u2 max_stack; - ((get@ #binaryF.writer ///encoding.u2-format) + ((get@ #binaryF.writer ///unsigned.u2-format) (get@ #max-stack code)) ## u2 max_locals; - ((get@ #binaryF.writer ///encoding.u2-format) + ((get@ #binaryF.writer ///unsigned.u2-format) (get@ #max-locals code)) ## u4 code_length; ## u1 code[code_length]; diff --git a/stdlib/source/lux/target/jvm/attribute/code/exception.lux b/stdlib/source/lux/target/jvm/attribute/code/exception.lux index 6ec0a1773..c1f4bf581 100644 --- a/stdlib/source/lux/target/jvm/attribute/code/exception.lux +++ b/stdlib/source/lux/target/jvm/attribute/code/exception.lux @@ -9,8 +9,9 @@ ["#." label (#+ Label)] ["//#" /// #_ [constant (#+ Class)] - ["#." encoding (#+ U2)] - ["#." index (#+ Index)]]]) + ["#." index (#+ Index)] + [encoding + ["#." unsigned (#+ U2)]]]]) (type: #export Exception {#start-pc Label @@ -32,13 +33,13 @@ Nat ($_ n/+ ## u2 start_pc; - ////encoding.u2-bytes + ////unsigned.u2-bytes ## u2 end_pc; - ////encoding.u2-bytes + ////unsigned.u2-bytes ## u2 handler_pc; - ////encoding.u2-bytes + ////unsigned.u2-bytes ## u2 catch_type; - ////encoding.u2-bytes + ////unsigned.u2-bytes )) (def: #export format diff --git a/stdlib/source/lux/target/jvm/attribute/code/label.lux b/stdlib/source/lux/target/jvm/attribute/code/label.lux index c70e13a3e..98be2e8ba 100644 --- a/stdlib/source/lux/target/jvm/attribute/code/label.lux +++ b/stdlib/source/lux/target/jvm/attribute/code/label.lux @@ -6,14 +6,15 @@ [format [binary (#+ Format)]]]] ["." //// #_ - ["#." encoding (#+ U2)]]) + [encoding + ["#." unsigned (#+ U2)]]]) (type: #export Label U2) (def: #export equivalence (Equivalence Label) - ////encoding.equivalence) + ////unsigned.equivalence) (def: #export format (Format Label) - ////encoding.u2-format) + ////unsigned.u2-format) diff --git a/stdlib/source/lux/target/jvm/attribute/constant.lux b/stdlib/source/lux/target/jvm/attribute/constant.lux index 1cbe1f955..44e48acb1 100644 --- a/stdlib/source/lux/target/jvm/attribute/constant.lux +++ b/stdlib/source/lux/target/jvm/attribute/constant.lux @@ -7,7 +7,8 @@ [binary (#+ Format)]]]] ["." /// #_ [constant (#+ Value)] - ["#." encoding (#+ U2 U4)] + [encoding + ["#." unsigned (#+ U2 U4)]] ["#." index (#+ Index)]]) (type: #export Constant @@ -18,7 +19,7 @@ ///index.equivalence) (def: #export length - ///encoding.u2-bytes) + ///unsigned.u2-bytes) (def: #export format (Format Constant) diff --git a/stdlib/source/lux/target/jvm/class.lux b/stdlib/source/lux/target/jvm/class.lux index 6169556c5..cd269f038 100644 --- a/stdlib/source/lux/target/jvm/class.lux +++ b/stdlib/source/lux/target/jvm/class.lux @@ -17,15 +17,16 @@ [type [abstract (#+)]]] ["." // #_ - ["#." encoding (#+)] ["#." modifier (#+ Modifier modifiers:)] ["#." version (#+ Version Minor Major)] - ["#." name (#+ Internal)] ["#." magic (#+ Magic)] ["#." index (#+ Index)] ["#." attribute (#+ Attribute)] ["#." field (#+ Field)] ["#." method (#+ Method)] + [encoding + ["#." unsigned (#+)] + ["#." name (#+ Internal)]] ["#." constant (#+ Constant) ["#/." pool (#+ Pool)]]]) @@ -56,9 +57,9 @@ (def: #export equivalence (Equivalence Class) ($_ equivalence.product - //encoding.equivalence - //encoding.equivalence - //encoding.equivalence + //unsigned.equivalence + //unsigned.equivalence + //unsigned.equivalence //constant/pool.equivalence //modifier.equivalence //index.equivalence diff --git a/stdlib/source/lux/target/jvm/constant.lux b/stdlib/source/lux/target/jvm/constant.lux index aae32e757..af6b1b078 100644 --- a/stdlib/source/lux/target/jvm/constant.lux +++ b/stdlib/source/lux/target/jvm/constant.lux @@ -19,9 +19,10 @@ ["." / #_ ["#." tag ("#;." equivalence)] ["." // #_ - [encoding (#+ U4)] [descriptor (#+ Descriptor)] - ["#." index (#+ Index)]]]) + ["#." index (#+ Index)] + [encoding + [unsigned (#+ U4)]]]]) (type: #export UTF8 Text) diff --git a/stdlib/source/lux/target/jvm/constant/pool.lux b/stdlib/source/lux/target/jvm/constant/pool.lux index 7b29cc910..5fd123319 100644 --- a/stdlib/source/lux/target/jvm/constant/pool.lux +++ b/stdlib/source/lux/target/jvm/constant/pool.lux @@ -19,7 +19,8 @@ abstract]] ["." // (#+ UTF8 Class Constant) ("#;." class-equivalence) [// - ["." encoding] + [encoding + ["." unsigned]] ["." index (#+ Index)] ["." descriptor (#+ Descriptor)]]]) @@ -33,7 +34,7 @@ (template: (!add <=> ) (function (_ pool) - (with-expansions [ (as-is (index.index (encoding.u2 (n/+ offset idx)))) + (with-expansions [ (as-is (index.index (unsigned.u2 (n/+ offset idx)))) (as-is (recur (.inc idx)))] (loop [idx 0] (case (row.nth idx pool) @@ -53,7 +54,7 @@ ]))))) (template: (!raw-index ) - (|> index.number encoding.nat .nat)) + (|> index.number unsigned.nat .nat)) (exception: #export (invalid-index {index (Index Any)} {maximum Nat}) @@ -89,7 +90,7 @@ (template: (!find <=> <%> ) (function (_ pool) - (with-expansions [ (as-is (index.index (encoding.u2 (n/+ offset idx)))) + (with-expansions [ (as-is (index.index (unsigned.u2 (n/+ offset idx)))) (as-is (recur (.inc idx)))] (loop [idx 0] (case (row.nth idx pool) diff --git a/stdlib/source/lux/target/jvm/constant/tag.lux b/stdlib/source/lux/target/jvm/constant/tag.lux index 352fb8afe..b402037c4 100644 --- a/stdlib/source/lux/target/jvm/constant/tag.lux +++ b/stdlib/source/lux/target/jvm/constant/tag.lux @@ -8,22 +8,24 @@ [type abstract]] [/// - ["." encoding (#+ U1) ("u1/." equivalence)]]) + [encoding + ["." unsigned (#+ U1) ("u1@." equivalence)]]]) (abstract: #export Tag {} U1 - (structure: #export equivalence (Equivalence Tag) + (structure: #export equivalence + (Equivalence Tag) (def: (= reference sample) - (u1/= (:representation reference) + (u1@= (:representation reference) (:representation sample)))) (template [ ] [(def: #export Tag - (:abstraction (encoding.u1 )))] + (:abstraction (unsigned.u1 )))] [01 utf8] [03 integer] @@ -45,5 +47,5 @@ (Format Tag) (binary.adapt (|>> :abstraction) (|>> :representation) - encoding.u1-format)) + unsigned.u1-format)) ) diff --git a/stdlib/source/lux/target/jvm/descriptor.lux b/stdlib/source/lux/target/jvm/descriptor.lux index 992b6a0de..a5bd8599c 100644 --- a/stdlib/source/lux/target/jvm/descriptor.lux +++ b/stdlib/source/lux/target/jvm/descriptor.lux @@ -10,7 +10,8 @@ [type abstract]] ["." // #_ - ["#." name (#+ Internal)]]) + [encoding + ["#." name (#+ Internal)]]]) (abstract: #export Void' {} Any) diff --git a/stdlib/source/lux/target/jvm/encoding.lux b/stdlib/source/lux/target/jvm/encoding.lux deleted file mode 100644 index f5db7a81a..000000000 --- a/stdlib/source/lux/target/jvm/encoding.lux +++ /dev/null @@ -1,59 +0,0 @@ -(.module: - [lux (#- nat) - [abstract - [equivalence (#+ Equivalence)]] - [control - ["." parser ("#;." functor)]] - [data - [number - ["." i64]] - [format - ["." binary (#+ Format)]]] - [macro - ["." template]] - [type - abstract]]) - -(abstract: #export (Unsigned brand) - {} - (I64 Any) - - (def: #export nat - (-> (Unsigned Any) (I64 Any)) - (|>> :representation)) - - (structure: #export equivalence - (All [brand] (Equivalence (Unsigned brand))) - (def: (= reference sample) - ("lux i64 =" (:representation reference) (:representation sample)))) - - (template [ ] - [(with-expansions [ (template.identifier [ "'"])] - (abstract: #export {} Any) - (type: #export (Unsigned ))) - - (def: #export Nat ) - - (def: #export - - (|> (n/* i64.bits-per-byte) i64.mask :abstraction)) - - (def: #export - (-> (I64 Any) ) - (|>> (i64.and (:representation )) :abstraction))] - - [1 U1 u1-bytes u1 max-u1] - [2 U2 u2-bytes u2 max-u2] - [4 U4 u4-bytes u4 max-u4] - ) - ) - -(template [ ] - [(def: #export - (Format ) - (binary.adapt ..nat ))] - - [u1-format U1 binary.bits/8 ..u1] - [u2-format U2 binary.bits/16 ..u2] - [u4-format U4 binary.bits/32 ..u4] - ) diff --git a/stdlib/source/lux/target/jvm/encoding/name.lux b/stdlib/source/lux/target/jvm/encoding/name.lux new file mode 100644 index 000000000..7f2119bc0 --- /dev/null +++ b/stdlib/source/lux/target/jvm/encoding/name.lux @@ -0,0 +1,32 @@ +(.module: + [lux #* + [data + ["." text]] + [type + abstract]]) + +(def: #export internal-separator "/") +(def: #export external-separator ".") + +(type: #export External Text) + +(abstract: #export Internal + {} + + Text + + (def: #export internal + (-> Text Internal) + (|>> (text.replace-all ..external-separator + ..internal-separator) + :abstraction)) + + (def: #export read + (-> Internal Text) + (|>> :representation)) + + (def: #export external + (-> Internal External) + (|>> :representation + (text.replace-all ..internal-separator + ..external-separator)))) diff --git a/stdlib/source/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/lux/target/jvm/encoding/unsigned.lux new file mode 100644 index 000000000..f5db7a81a --- /dev/null +++ b/stdlib/source/lux/target/jvm/encoding/unsigned.lux @@ -0,0 +1,59 @@ +(.module: + [lux (#- nat) + [abstract + [equivalence (#+ Equivalence)]] + [control + ["." parser ("#;." functor)]] + [data + [number + ["." i64]] + [format + ["." binary (#+ Format)]]] + [macro + ["." template]] + [type + abstract]]) + +(abstract: #export (Unsigned brand) + {} + (I64 Any) + + (def: #export nat + (-> (Unsigned Any) (I64 Any)) + (|>> :representation)) + + (structure: #export equivalence + (All [brand] (Equivalence (Unsigned brand))) + (def: (= reference sample) + ("lux i64 =" (:representation reference) (:representation sample)))) + + (template [ ] + [(with-expansions [ (template.identifier [ "'"])] + (abstract: #export {} Any) + (type: #export (Unsigned ))) + + (def: #export Nat ) + + (def: #export + + (|> (n/* i64.bits-per-byte) i64.mask :abstraction)) + + (def: #export + (-> (I64 Any) ) + (|>> (i64.and (:representation )) :abstraction))] + + [1 U1 u1-bytes u1 max-u1] + [2 U2 u2-bytes u2 max-u2] + [4 U4 u4-bytes u4 max-u4] + ) + ) + +(template [ ] + [(def: #export + (Format ) + (binary.adapt ..nat ))] + + [u1-format U1 binary.bits/8 ..u1] + [u2-format U2 binary.bits/16 ..u2] + [u4-format U4 binary.bits/32 ..u4] + ) diff --git a/stdlib/source/lux/target/jvm/field.lux b/stdlib/source/lux/target/jvm/field.lux index 062b38ac6..5cdc1b6b9 100644 --- a/stdlib/source/lux/target/jvm/field.lux +++ b/stdlib/source/lux/target/jvm/field.lux @@ -17,7 +17,6 @@ [type [abstract (#+)]]] ["." // #_ - [encoding (#+)] ["." modifier (#+ Modifier modifiers:)] ["#." constant (#+ UTF8) ["#/." pool (#+ Pool)]] diff --git a/stdlib/source/lux/target/jvm/index.lux b/stdlib/source/lux/target/jvm/index.lux index d8dd1d9a5..6d7e280f6 100644 --- a/stdlib/source/lux/target/jvm/index.lux +++ b/stdlib/source/lux/target/jvm/index.lux @@ -8,7 +8,8 @@ [type abstract]] ["." // #_ - ["#." encoding (#+ U2)]]) + [encoding + ["#." unsigned (#+ U2)]]]) (abstract: #export (Index kind) {} @@ -27,11 +28,11 @@ (All [kind] (Equivalence (Index kind))) (:: equivalence.contravariant map-1 ..number - //encoding.equivalence)) + //unsigned.equivalence)) (def: #export format (All [kind] (Format (Index kind))) (binary.adapt ..index ..number - //encoding.u2-format)) + //unsigned.u2-format)) ) diff --git a/stdlib/source/lux/target/jvm/magic.lux b/stdlib/source/lux/target/jvm/magic.lux index c00d246a0..73fea4698 100644 --- a/stdlib/source/lux/target/jvm/magic.lux +++ b/stdlib/source/lux/target/jvm/magic.lux @@ -5,15 +5,16 @@ [format [binary (#+ Format)]]]] ["." // #_ - ["#." encoding (#+ U4)]]) + [encoding + ["#." unsigned (#+ U4)]]]) (type: #export Magic U4) (def: #export code Magic - (//encoding.u4 (hex "CAFEBABE"))) + (//unsigned.u4 (hex "CAFEBABE"))) (def: #export format (Format Magic) - //encoding.u4-format) + //unsigned.u4-format) diff --git a/stdlib/source/lux/target/jvm/method.lux b/stdlib/source/lux/target/jvm/method.lux index eb039d09b..e4f0c1f32 100644 --- a/stdlib/source/lux/target/jvm/method.lux +++ b/stdlib/source/lux/target/jvm/method.lux @@ -17,7 +17,6 @@ [type [abstract (#+)]]] ["." // #_ - [encoding (#+)] ["." modifier (#+ Modifier modifiers:)] ["#." constant (#+ UTF8) [pool (#+ Pool)]] diff --git a/stdlib/source/lux/target/jvm/modifier.lux b/stdlib/source/lux/target/jvm/modifier.lux index 417484c45..0e354d730 100644 --- a/stdlib/source/lux/target/jvm/modifier.lux +++ b/stdlib/source/lux/target/jvm/modifier.lux @@ -19,24 +19,25 @@ [syntax (#+ syntax:)] ["." code]]] ["." // #_ - ["#." encoding]]) + [encoding + ["#." unsigned]]]) (abstract: #export (Modifier of) {} - //encoding.U2 + //unsigned.U2 (template: (!wrap value) (|> value - //encoding.u2 + //unsigned.u2 :abstraction)) (template: (!unwrap value) (|> value :representation - //encoding.nat)) + //unsigned.nat)) (def: #export code - (-> (Modifier Any) //encoding.U2) + (-> (Modifier Any) //unsigned.U2) (|>> :representation)) (def: modifier @@ -46,7 +47,7 @@ (structure: #export equivalence (All [of] (Equivalence (Modifier of))) (def: (= reference sample) - (:: //encoding.equivalence = + (:: //unsigned.equivalence = (:representation reference) (:representation sample)))) @@ -65,7 +66,7 @@ (def: #export format (All [of] (Format (Modifier of))) - (let [(^open "_@.") //encoding.u2-format] + (let [(^open "_@.") //unsigned.u2-format] {#binaryF.reader (:: <>.functor map (|>> :abstraction) _@reader) #binaryF.writer (|>> :representation _@writer)})) ) diff --git a/stdlib/source/lux/target/jvm/name.lux b/stdlib/source/lux/target/jvm/name.lux deleted file mode 100644 index 7f2119bc0..000000000 --- a/stdlib/source/lux/target/jvm/name.lux +++ /dev/null @@ -1,32 +0,0 @@ -(.module: - [lux #* - [data - ["." text]] - [type - abstract]]) - -(def: #export internal-separator "/") -(def: #export external-separator ".") - -(type: #export External Text) - -(abstract: #export Internal - {} - - Text - - (def: #export internal - (-> Text Internal) - (|>> (text.replace-all ..external-separator - ..internal-separator) - :abstraction)) - - (def: #export read - (-> Internal Text) - (|>> :representation)) - - (def: #export external - (-> Internal External) - (|>> :representation - (text.replace-all ..internal-separator - ..external-separator)))) diff --git a/stdlib/source/lux/target/jvm/version.lux b/stdlib/source/lux/target/jvm/version.lux index ddfe7139c..f280743ba 100644 --- a/stdlib/source/lux/target/jvm/version.lux +++ b/stdlib/source/lux/target/jvm/version.lux @@ -4,7 +4,8 @@ [format ["." binary (#+ Format)]]]] ["." // #_ - ["#." encoding (#+ U2)]]) + [encoding + ["#." unsigned (#+ U2)]]]) (type: #export Version U2) (type: #export Minor Version) @@ -12,7 +13,7 @@ (def: #export version (-> Nat Version) - //encoding.u2) + //unsigned.u2) (template [ ] [(def: #export @@ -35,4 +36,4 @@ (def: #export format (Format Version) - //encoding.u2-format) + //unsigned.u2-format) diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux index da8eebbd9..e5032ed44 100644 --- a/stdlib/source/test/lux/target/jvm.lux +++ b/stdlib/source/test/lux/target/jvm.lux @@ -26,10 +26,11 @@ ["." / #_ ["#." loader (#+ Library)] ["#." version] - ["#." name] ["#." descriptor (#+ Descriptor Value)] ["#." field] ["#." class] + [encoding + ["#." name]] [modifier ["#.M" inner]]]}) -- cgit v1.2.3