From 2ea0bda182d76015df4f53ed82efd6f37e93cba6 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 8 Feb 2022 19:34:35 -0400 Subject: Optimized integer addition for Lux/Ruby in MRuby. --- stdlib/source/library/lux/target/jvm/field.lux | 4 +- stdlib/source/library/lux/target/jvm/method.lux | 9 +-- .../library/lux/tool/compiler/default/platform.lux | 17 +++-- .../lux/tool/compiler/language/lux/analysis.lux | 16 ++--- .../compiler/language/lux/analysis/inference.lux | 2 +- .../language/lux/phase/analysis/complex.lux | 4 +- .../language/lux/phase/analysis/function.lux | 4 +- .../language/lux/phase/extension/analysis/jvm.lux | 14 ++-- .../language/lux/phase/extension/directive/jvm.lux | 26 ++++---- .../lux/phase/extension/generation/jvm/host.lux | 5 +- .../generation/jvm/function/field/constant.lux | 2 +- .../generation/jvm/function/field/variable.lux | 2 +- .../phase/generation/jvm/function/method/apply.lux | 2 +- .../jvm/function/method/implementation.lux | 2 +- .../phase/generation/jvm/function/method/init.lux | 2 +- .../phase/generation/jvm/function/method/new.lux | 2 +- .../phase/generation/jvm/function/method/reset.lux | 2 +- .../language/lux/phase/generation/jvm/host.lux | 5 +- .../language/lux/phase/generation/jvm/program.lux | 3 +- .../language/lux/phase/generation/jvm/runtime.lux | 31 +++++---- .../lux/phase/generation/ruby/function.lux | 2 +- .../language/lux/phase/generation/ruby/runtime.lux | 75 +++++++--------------- .../library/lux/tool/compiler/meta/export.lux | 71 ++++++++++++++++++++ .../library/lux/tool/compiler/meta/io/context.lux | 4 +- 24 files changed, 178 insertions(+), 128 deletions(-) create mode 100644 stdlib/source/library/lux/tool/compiler/meta/export.lux (limited to 'stdlib/source/library') diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux index ee6daa975..494583650 100644 --- a/stdlib/source/library/lux/target/jvm/field.lux +++ b/stdlib/source/library/lux/target/jvm/field.lux @@ -60,8 +60,8 @@ [(binaryF.sequence/16 //attribute.writer) #attributes])) ))) -(def: .public (field modifier name type with_signature? attributes) - (-> (Modifier Field) UTF8 (Type Value) Bit (Sequence Attribute) +(def: .public (field modifier name with_signature? type attributes) + (-> (Modifier Field) UTF8 Bit (Type Value) (Sequence Attribute) (Resource Field)) (do [! //constant/pool.monad] [@name (//constant/pool.utf8 name) diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux index 00647a199..c5011887a 100644 --- a/stdlib/source/library/lux/target/jvm/method.lux +++ b/stdlib/source/library/lux/target/jvm/method.lux @@ -50,14 +50,15 @@ ["1000" synthetic] ) -(def: .public (method modifier name type attributes code) - (-> (Modifier Method) UTF8 (Type //category.Method) (List (Resource Attribute)) (Maybe (Bytecode Any)) +(def: .public (method modifier name with_signature? type attributes code) + (-> (Modifier Method) UTF8 Bit (Type //category.Method) (List (Resource Attribute)) (Maybe (Bytecode Any)) (Resource Method)) (do [! //pool.monad] [@name (//pool.utf8 name) @descriptor (//pool.descriptor (//type.descriptor type)) - attributes (|> attributes - (list& (//attribute.signature (//type.signature type))) + attributes (|> (if with_signature? + (list& (//attribute.signature (//type.signature type)) attributes) + attributes) (monad.all !) (# ! each sequence.of_list)) attributes (case code diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 02b35d0e7..42d8b9958 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -197,11 +197,11 @@ state (///directive.Operation Any) - (do ///phase.monad + (do [! ///phase.monad] [_ (///directive.lifted_analysis - (///analysis.install analysis_state)) - _ (///directive.lifted_analysis - (extension.with extender analysers)) + (do ! + [_ (///analysis.set_state analysis_state)] + (extension.with extender analysers))) _ (///directive.lifted_synthesis (extension.with extender synthesizers)) _ (///directive.lifted_generation @@ -214,11 +214,10 @@ (def: (phase_wrapper archive platform state) (All (_ ) (-> Archive (Try [ ///phase.Wrapper]))) - (let [phase_wrapper (value@ #phase_wrapper platform)] - (|> archive - phase_wrapper - ///directive.lifted_generation - (///phase.result' state)))) + (|> archive + ((value@ #phase_wrapper platform)) + ///directive.lifted_generation + (///phase.result' state))) (def: (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives]) (All (_ ) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 116d84299..2d231f1cc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -256,8 +256,8 @@ {try.#Success [[bundle' (with@ .#source old_source state')] output]} - {try.#Failure error} - {try.#Failure error})))) + failure + failure)))) (def: .public (with_current_module name) (All (_ a) (-> Text (Operation a) (Operation a))) @@ -276,8 +276,8 @@ {try.#Success [[bundle' (with@ .#location old_location state')] output]} - {try.#Failure error} - {try.#Failure error}))))) + failure + failure))))) (def: (locate_error location error) (-> Location Text Text) @@ -299,7 +299,7 @@ (# phase.monad in []) (..except exception parameters))) -(def: .public (with_stack exception message action) +(def: .public (with_exception exception message action) (All (_ e o) (-> (Exception e) e (Operation o) (Operation o))) (function (_ bundle,state) (.case (exception.with exception message @@ -308,10 +308,10 @@ (let [[bundle state] bundle,state] {try.#Failure (locate_error (value@ .#location state) error)}) - output - output))) + success + success))) -(def: .public (install state) +(def: .public (set_state state) (-> .Lux (Operation Any)) (function (_ [bundle _]) {try.#Success [[bundle state] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index 1d903e7d6..893f9df5a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -119,7 +119,7 @@ {.#Function inputT outputT} (do phase.monad [[outputT' args'A] (general archive analyse outputT args') - argA (<| (/.with_stack ..cannot_infer_argument [inputT argC]) + argA (<| (/.with_exception ..cannot_infer_argument [inputT argC]) (/type.expecting inputT) (analyse archive argC))] (in [outputT' (list& argA args'A)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 678a626da..726860314 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -106,7 +106,7 @@ (do [! ///.monad] [expectedT (///extension.lifted meta.expected_type) expectedT' (/type.check (check.clean expectedT))] - (/.with_stack ..cannot_analyse_variant [expectedT' lefts right? valueC] + (/.with_exception ..cannot_analyse_variant [expectedT' lefts right? valueC] (case expectedT {.#Sum _} (|> (analyse archive valueC) @@ -221,7 +221,7 @@ (-> Phase Archive (List Code) (Operation Analysis)) (do [! ///.monad] [expectedT (///extension.lifted meta.expected_type)] - (/.with_stack ..cannot_analyse_tuple [expectedT membersC] + (/.with_exception ..cannot_analyse_tuple [expectedT membersC] (case expectedT {.#Product _} (..typed_product analyse expectedT archive membersC) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index 63c315954..347604a35 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -51,7 +51,7 @@ (do [! ///.monad] [functionT (///extension.lifted meta.expected_type)] (loop [expectedT functionT] - (/.with_stack ..cannot_analyse [expectedT function_name arg_name body] + (/.with_exception ..cannot_analyse [expectedT function_name arg_name body] (case expectedT {.#Named name unnamedT} (again unnamedT) @@ -108,7 +108,7 @@ (def: .public (apply analyse argsC+ functionT functionA archive functionC) (-> Phase (List Code) Type Analysis Phase) - (<| (/.with_stack ..cannot_apply [functionT functionC argsC+]) + (<| (/.with_exception ..cannot_apply [functionT functionC argsC+]) (do ///.monad [[applyT argsA+] (/inference.general archive analyse functionT argsC+)]) (in (/.reified [functionA argsA+])))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index fa1a73e1e..a7d889777 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -2333,7 +2333,7 @@ (do pool.monad [constant (`` (|> value (~~ (template.spliced )))) attribute (attribute.constant constant)] - (field.field ..constant::modifier name true (sequence.sequence attribute)))]) + (field.field ..constant::modifier name #1 (sequence.sequence attribute)))]) ([.#Bit jvm.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] [.#Int jvm.byte [.i64 i32.i32 constant.integer pool.integer]] [.#Int jvm.short [.i64 i32.i32 constant.integer pool.integer]] @@ -2352,7 +2352,7 @@ ... TODO: Handle annotations. {#Variable [name visibility state annotations type]} (field.field (modifier#composite visibility state) - name type true sequence.empty))) + name #1 type sequence.empty))) (def: method_privacy (-> ffi.Privacy (Modifier method.Method)) @@ -2421,7 +2421,7 @@ method.strict modifier.empty)) ..constructor_name - (jvm.method [variables (list#each product.right arguments) jvm.void exceptions]) + #0 (jvm.method [variables (list#each product.right arguments) jvm.void exceptions]) (list) {.#Some ($_ _.composite (_.aload 0) @@ -2442,7 +2442,7 @@ method.strict modifier.empty)) name - (jvm.method [variables (list#each product.right arguments) return exceptions]) + #0 (jvm.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -2458,7 +2458,7 @@ method.final modifier.empty)) name - (jvm.method [variables (list#each product.right arguments) return exceptions]) + #0 (jvm.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -2472,7 +2472,7 @@ method.strict modifier.empty)) name - (jvm.method [variables (list#each product.right arguments) return exceptions]) + #0 (jvm.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -2482,7 +2482,7 @@ method.abstract (..method_privacy privacy)) name - (jvm.method [variables (list#each product.right arguments) return exceptions]) + #0 (jvm.method [variables (list#each product.right arguments) return exceptions]) (list) {.#None}) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 49cb5d6f0..b0660d074 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -229,7 +229,7 @@ (do pool.monad [constant (`` (|> value (~~ (template.spliced )))) attribute (attribute.constant constant)] - (field.field ..constant::modifier name true (sequence.sequence attribute)))]) + (field.field ..constant::modifier name #1 (sequence.sequence attribute)))]) ([.#Bit type.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] [.#Int type.byte [.i64 i32.i32 constant.integer pool.integer]] [.#Int type.short [.i64 i32.i32 constant.integer pool.integer]] @@ -248,7 +248,7 @@ ... TODO: Handle annotations. {#Variable [name visibility state annotations type]} (field.field (modifier#composite visibility state) - name type true sequence.empty))) + name #1 type sequence.empty))) (def: annotation_parameter_synthesis (.Parser (jvm.Annotation_Parameter Synthesis)) @@ -498,7 +498,7 @@ method.strict modifier.empty)) ..constructor_name - (type.method [method_tvars argumentsT type.void exceptions]) + #1 (type.method [method_tvars argumentsT type.void exceptions]) (list) {.#Some ($_ _.composite (_.aload 0) @@ -564,7 +564,7 @@ method.strict modifier.empty)) method_name - (type.method [method_tvars argumentsT returnJ exceptionsJ]) + #1 (type.method [method_tvars argumentsT returnJ exceptionsJ]) (list) {.#Some ($_ _.composite (method_arguments 1 argumentsT) @@ -591,7 +591,7 @@ method.final modifier.empty)) method_name - (type.method [method_tvars argumentsT returnJ exceptionsJ]) + #1 (type.method [method_tvars argumentsT returnJ exceptionsJ]) (list) {.#Some ($_ _.composite (method_arguments 1 argumentsT) @@ -616,7 +616,7 @@ method.strict modifier.empty)) method_name - (type.method [method_tvars argumentsT returnJ exceptionsJ]) + #1 (type.method [method_tvars argumentsT returnJ exceptionsJ]) (list) {.#Some ($_ _.composite (method_arguments 0 argumentsT) @@ -631,7 +631,7 @@ (..method_privacy privacy) method.abstract) name - (type.method [variables (list#each product.right arguments) return exceptions]) + #1 (type.method [variables (list#each product.right arguments) return exceptions]) (list) {.#None}))) @@ -774,7 +774,7 @@ method.strict modifier.empty)) ..constructor_name - (type.method [variables (list#each product.right arguments) type.void exceptions]) + #1 (type.method [variables (list#each product.right arguments) type.void exceptions]) (list) {.#Some ($_ _.composite (_.aload 0) @@ -795,7 +795,7 @@ method.strict modifier.empty)) name - (type.method [variables (list#each product.right arguments) return exceptions]) + #1 (type.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -811,7 +811,7 @@ method.final modifier.empty)) name - (type.method [variables (list#each product.right arguments) return exceptions]) + #1 (type.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -825,7 +825,7 @@ method.strict modifier.empty)) name - (type.method [variables (list#each product.right arguments) return exceptions]) + #1 (type.method [variables (list#each product.right arguments) return exceptions]) (list) {.#Some (..mock_return return)}) @@ -835,7 +835,7 @@ method.abstract (..method_privacy privacy)) name - (type.method [variables (list#each product.right arguments) return exceptions]) + #1 (type.method [variables (list#each product.right arguments) return exceptions]) (list) {.#None}) )) @@ -943,7 +943,7 @@ method.public method.abstract) /#name - type + #1 type (list) {.#None}))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index 6f35d182a..4b4956d82 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -1028,7 +1028,8 @@ (_.aload 0) (_.aload (n.+ inputs_offset (++ register))) (_.putfield class (///reference.foreign_name register) $Object)))))] - (method.method method.public "" (anonymous_init_method env inputsTG) + (method.method method.public "" + #1 (anonymous_init_method env inputsTG) (list) {.#Some ($_ _.composite (_.aload 0) @@ -1212,7 +1213,7 @@ method.strict modifier#identity)) name - methodT + #1 methodT (list) {.#Some ($_ _.composite (prepare_arguments 1 argumentsT) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux index 10bf59a29..7d0bc8ae0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux @@ -23,4 +23,4 @@ (def: .public (constant name type) (-> Text (Type Value) (Resource Field)) - (field.field ..modifier name type false (sequence.sequence))) + (field.field ..modifier name #0 type (sequence.sequence))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux index cc22b43b9..4e0684215 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux @@ -46,7 +46,7 @@ (def: .public (variable name type) (-> Text (Type Value) (Resource Field)) - (field.field ..modifier name type false (sequence.sequence))) + (field.field ..modifier name #0 type (sequence.sequence))) (def: .public (variables naming amount) (-> (-> Register Text) Nat (List (Resource Field))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index a7f0d7ac6..5020c98c0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux @@ -84,7 +84,7 @@ over_extent (i.- (.int apply_arity) (.int function_arity))] (method.method //.modifier ////runtime.apply::name - (////runtime.apply::type apply_arity) + #0 (////runtime.apply::type apply_arity) (list) {.#Some (case num_partials 0 ($_ _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux index 6c8a9ee75..22e3a8b0d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux @@ -30,7 +30,7 @@ (def: .public (method' name arity @begin body) (-> Text Arity Label (Bytecode Any) (Resource Method)) (method.method //.modifier name - (..type arity) + #0 (..type arity) (list) {.#Some ($_ _.composite (_.set_label @begin) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index 37278725b..14d2fdc03 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -94,7 +94,7 @@ offset_partial (: (-> Register Register) (|>> offset_arity (n.+ 1)))] (method.method //.modifier ..name - (..type environment arity) + #0 (..type environment arity) (list) {.#Some ($_ _.composite ////reference.this diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux index 5c03b472b..3edbe1e05 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux @@ -68,7 +68,7 @@ after_arity (: (-> Nat Nat) (|>> after_environment (n.+ 1)))] (method.method //.modifier //init.name - (//init.type environment arity) + #0 (//init.type environment arity) (list) {.#Some ($_ _.composite ////reference.this diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux index d1a78ce86..037f2958d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux @@ -41,7 +41,7 @@ (def: .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (method.method //.modifier ..name - (..type class) + #0 (..type class) (list) {.#Some ($_ _.composite (if (arity.multiary? arity) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index e232874c4..e852b63a3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -125,8 +125,9 @@ (encoding/name.internal bytecode_name) {.#None} (encoding/name.internal "java.lang.Object") (list) - (list (field.field ..value::modifier ..value::field ..value::type false (sequence.sequence))) - (list (method.method ..init::modifier "" ..init::type + (list (field.field ..value::modifier ..value::field #0 ..value::type (sequence.sequence))) + (list (method.method ..init::modifier "" + #0 ..init::type (list) {.#Some ($_ _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux index 7f72697ca..23ec9402e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux @@ -144,7 +144,8 @@ (def: .public (program artifact_name context program) (-> (-> unit.ID Text) (Program (Bytecode Any) Definition)) (let [super_class (|> ..^Object type.reflection reflection.reflection name.internal) - main (method.method ..main::modifier "main" ..main::type + main (method.method ..main::modifier "main" + #0 ..main::type (list) {.#Some ($_ _.composite program diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 55cbcdb67..fc96c025f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -154,7 +154,7 @@ $right? _.aload_1 $value _.aload_2] (method.method ..modifier ..variant::name - ..variant::type + #0 ..variant::type (list) {.#Some ($_ _.composite new_variant ... A[3] @@ -216,7 +216,7 @@ (def: decode_frac::method (method.method ..modifier ..decode_frac::name - ..decode_frac::type + #0 ..decode_frac::type (list) {.#Some (..risky @@ -253,7 +253,7 @@ (def: (failure name message) (-> Text Text (Resource Method)) (method.method ..modifier name - ..failure::type + #0 ..failure::type (list) {.#Some ($_ _.composite @@ -275,7 +275,7 @@ (def: push::method (method.method ..modifier ..push::name - ..push::type + #0 ..push::type (list) {.#Some (let [new_stack_frame! ($_ _.composite @@ -294,7 +294,8 @@ (def: .public case (..procedure ..case::name ..case::type)) (def: case::method - (method.method ..modifier ..case::name ..case::type + (method.method ..modifier ..case::name + #0 ..case::type (list) {.#Some (do _.monad @@ -405,7 +406,8 @@ (_.goto @loop)))) left_projection::method - (method.method ..modifier ..left_projection::name ..projection_type + (method.method ..modifier ..left_projection::name + #0 ..projection_type (list) {.#Some (do _.monad @@ -424,7 +426,8 @@ (recur @loop)))}) right_projection::method - (method.method ..modifier ..right_projection::name ..projection_type + (method.method ..modifier ..right_projection::name + #0 ..projection_type (list) {.#Some (do _.monad @@ -479,7 +482,8 @@ (def: true _.iconst_1) (def: try::method - (method.method ..modifier ..try::name ..try::type + (method.method ..modifier ..try::name + #0 ..try::type (list) {.#Some (do _.monad @@ -573,7 +577,8 @@ (++ //function/arity.minimum) //function/arity.maximum) (list#each (function (_ arity) - (method.method method.public ..apply::name (..apply::type arity) + (method.method method.public ..apply::name + #0 (..apply::type arity) (list) {.#Some (let [previous_inputs (|> arity @@ -587,10 +592,12 @@ (_.invokevirtual //function.class ..apply::name (..apply::type //function/arity.minimum)) _.areturn))}))) (list& (method.method (modifier#composite method.public method.abstract) - ..apply::name (..apply::type //function/arity.minimum) + ..apply::name + #0 (..apply::type //function/arity.minimum) (list) {.#None}))) - ::method (method.method method.public "" //function.init + ::method (method.method method.public "" + #0 //function.init (list) {.#Some (let [$partials _.iload_1] @@ -609,7 +616,7 @@ partial_count (: (Resource Field) (field.field (modifier#composite field.public field.final) //function/count.field - //function/count.type .false + #0 //function/count.type sequence.empty)) bytecode (<| (format.result class.writer) try.trusted diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 2e9deb0e4..1e427dbfc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -21,7 +21,7 @@ ["//[1]" /// "_" [synthesis {"+" Synthesis}] [analysis {"+" Environment Abstraction Reification Analysis}] - ["[1][0]" generation {"+" Context}] + ["[1][0]" generation] ["//[1]" /// "_" [arity {"+" Arity}] ["[1][0]" phase] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 8a3196fb2..5249d2c55 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -37,7 +37,7 @@ [variable {"+" Register}]] [meta [archive {"+" Output Archive} - ["[0]" artifact] + ["[0]" unit] ["[0]" registry {"+" Registry}]]]]]]) (template [ ] @@ -399,59 +399,19 @@ (_.- extra) (_./ parameter))))) -(def: i16##high - (_.bit_shr (_.int +16))) - -(def: i16##low - (_.bit_and (_.manual "+0xFFFF"))) - -(def: i16##up - (_.bit_shl (_.int +16))) - (runtime: (i64##+ parameter subject) [..normal_ruby? (_.return (i64##i64 (_.+ parameter subject)))] - (let [hh (|>> i32##high i16##high) - hl (|>> i32##high i16##low) - lh (|>> i32##low i16##high) - ll (|>> i32##low i16##low)] - (with_vars [l48 l32 l16 l00 - r48 r32 r16 r00 - x48 x32 x16 x00 - high low] - ($_ _.then - (_.set (list l48) (hh subject)) - (_.set (list l32) (hl subject)) - (_.set (list l16) (lh subject)) - (_.set (list l00) (ll subject)) - - (_.set (list r48) (hh parameter)) - (_.set (list r32) (hl parameter)) - (_.set (list r16) (lh parameter)) - (_.set (list r00) (ll parameter)) - - (_.set (list x00) (_.+ l00 r00)) - - (_.set (list x16) (|> (i16##high x00) - (_.+ l16) - (_.+ r16))) - (_.set (list x00) (i16##low x00)) - - (_.set (list x32) (|> (i16##high x16) - (_.+ l32) - (_.+ r32))) - (_.set (list x16) (i16##low x16)) - - (_.set (list x48) (|> (i16##high x32) - (_.+ l48) - (_.+ r48) - i16##low)) - (_.set (list x32) (i16##low x32)) - - (_.set (list high) (_.bit_or (i16##up x48) x32)) - (_.set (list low) (_.bit_or (i16##up x16) x00)) - (_.return (..i64 high low)) - ))) - ) + (with_vars [high low] + ($_ _.then + (_.set (list low) (_.+ (i32##low subject) + (i32##low parameter))) + (_.set (list high) (|> (i32##high low) + (_.+ (i32##high subject)) + (_.+ (i32##high parameter)) + i32##low)) + + (_.return (..i64 high (i32##low low))) + ))) (def: i64##min (_.manual "-0x8000000000000000")) @@ -465,6 +425,15 @@ [..normal_ruby? (_.return (i64##i64 (_.- parameter subject)))] (_.return (i64##+ (i64##opposite parameter) subject))) +(def: i16##high + (_.bit_shr (_.int +16))) + +(def: i16##low + (_.bit_and (_.manual "+0xFFFF"))) + +(def: i16##up + (_.bit_shl (_.int +16))) + (runtime: (i64##* parameter subject) [..normal_ruby? (_.return (i64##i64 (_.* parameter subject)))] (let [hh (|>> i32##high i16##high) @@ -623,7 +592,7 @@ [_ (/////generation.execute! ..runtime) _ (/////generation.save! ..module_id {.#None} ..runtime)] (in [(|> registry.empty - (registry.resource true artifact.no_dependencies) + (registry.resource true unit.none) product.right) (sequence.sequence [..module_id {.#None} diff --git a/stdlib/source/library/lux/tool/compiler/meta/export.lux b/stdlib/source/library/lux/tool/compiler/meta/export.lux new file mode 100644 index 000000000..79c5a2a44 --- /dev/null +++ b/stdlib/source/library/lux/tool/compiler/meta/export.lux @@ -0,0 +1,71 @@ +(.using + [library + [lux {"-" Source} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try {"+" Try} ("[1]#[0]" monad)] + [concurrency + ["[0]" async {"+" Async} ("[1]#[0]" functor)]]] + [data + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" sequence]] + [format + ["[0]" binary] + ["[0]" tar]]] + [time + ["[0]" instant]] + [tool + [compiler + [meta + [cli {"+" Source Export}] + ["[0]" io "_" + ["[1]" context]]]]] + [world + ["[0]" file]]]]) + +(def: .public file + "library.tar") + +(def: commons + tar.Ownership + (let [commons (: tar.Owner + [tar.#name tar.anonymous + tar.#id tar.no_id])] + [tar.#user commons + tar.#group commons])) + +(def: .public (library fs sources) + (-> (file.System Async) (List Source) (Async (Try tar.Tar))) + (|> sources + (io.listing fs) + (async#each (|>> (try#each (|>> dictionary.entries + (monad.each try.monad + (function (_ [path source_code]) + (do try.monad + [path (|> path + (text.replaced (# fs separator) .module_separator) + tar.path)] + (try#each (|>> [path + (instant.of_millis +0) + ($_ tar.and + tar.read_by_owner tar.write_by_owner + tar.read_by_group tar.write_by_group + tar.read_by_other) + ..commons] + {tar.#Normal}) + (tar.content source_code))))) + (try#each sequence.of_list))) + try#conjoint)))) + +(def: .public (export fs [sources target]) + (-> (file.System Async) Export (Async (Try Any))) + (do [! (try.with async.monad)] + [tar (|> sources + (..library fs) + (# ! each (binary.result tar.writer))) + .let [/ (# fs separator)]] + (# fs write tar (format target / ..file)))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 400c9e6d2..2f99ddce1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -45,7 +45,7 @@ (type: .public Extension Text) -(def: lux_extension +(def: .public lux_extension Extension ".lux") @@ -151,7 +151,7 @@ (if (text.ends_with? ..lux_extension file) (do ! [source_code (# fs read file)] - (async#in (dictionary.has' (text.replaced context "" file) source_code enumeration))) + (async#in (dictionary.has' (text.replaced/1 context "" file) source_code enumeration))) (in enumeration))) enumeration)) (# ! conjoint))] -- cgit v1.2.3