diff options
author | Eduardo Julian | 2021-12-24 08:58:01 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-12-24 08:58:01 -0400 |
commit | 63b45e09c5f5ceb59a48ed05cdc2d2c6cb038a7b (patch) | |
tree | 22545f6a3a5d8ad3c3a8d59136e0de3d03c69218 /stdlib/source/library/lux/tool/compiler | |
parent | fad9e5b073a9efe995421db1132f191f1db94725 (diff) |
Dusting off the pure-Lux JVM compiler machinery.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
15 files changed, 629 insertions, 567 deletions
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 c91a7aa9f..449060cf0 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 @@ -1,65 +1,70 @@ (.using - [library - [lux {"-" Type Definition} - ["[0]" host] - [abstract - ["[0]" monad {"+" do}]] - [control - [pipe {"+" case>}] - ["<>" parser ("[1]#[0]" monad) - ["<c>" code {"+" Parser}] - ["<t>" text]]] - [data - ["[0]" product] - [text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" dictionary] - ["[0]" sequence]]] - [macro - ["[0]" template]] - [math - [number - ["[0]" i32]]] - [target - [jvm - ["_" bytecode {"+" Bytecode}] - ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)] - ["[0]" attribute] - ["[0]" field] - ["[0]" version] - ["[0]" class] - ["[0]" constant - ["[0]" pool {"+" Resource}]] - [encoding - ["[0]" name]] - ["[0]" type {"+" Type Constraint Argument Typed} - [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter}] - ["[0]T" lux {"+" Mapping}] - ["[0]" signature] - ["[0]" descriptor {"+" Descriptor}] - ["[0]" parser]]]] - [tool - [compiler - ["[0]" analysis] - ["[0]" synthesis] - ["[0]" generation] - ["[0]" directive {"+" Handler Bundle}] - ["[0]" phase - [analysis - ["[0]A" type]] - ["[0]" generation - [jvm - [runtime {"+" Anchor Definition}]]] - ["[0]" extension - ["[0]" bundle] + [library + [lux {"-" Type Definition Primitive} + ["[0]" ffi] + [abstract + ["[0]" monad {"+" do}]] + [control + [pipe {"+" case>}] + ["<>" parser ("[1]#[0]" monad) + ["<c>" code {"+" Parser}] + ["<t>" text]]] + [data + ["[0]" product] + [text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" dictionary] + ["[0]" sequence]]] + [macro + ["[0]" template]] + [math + [number + ["[0]" i32]]] + [target + [jvm + ["_" bytecode {"+" Bytecode}] + ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)] + ["[0]" attribute] + ["[0]" field] + ["[0]" version] + ["[0]" class] + ["[0]" constant + ["[0]" pool {"+" Resource}]] + [encoding + ["[0]" name]] + ["[0]" type {"+" Type Constraint Argument Typed} + [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter}] + ["[0]T" lux {"+" Mapping}] + ["[0]" signature] + ["[0]" descriptor {"+" Descriptor}] + ["[0]" parser]]]] + [tool + [compiler + ["[0]" phase] + [meta + [archive {"+" Archive}]] + [language + [lux + ["[0]" analysis] + ["[0]" synthesis] + ["[0]" generation] + ["[0]" directive {"+" Handler Bundle}] + [phase [analysis - ["[0]" jvm]] - [directive - ["/" lux]]]]]] - [type - ["[0]" check {"+" Check}]]]]) + ["[0]A" type]] + [generation + [jvm + [runtime {"+" Anchor Definition}]]] + ["[0]" extension + ["[0]" bundle] + [analysis + ["[0]" jvm]] + [directive + ["/" lux]]]]]]]] + [type + ["[0]" check {"+" Check}]]]]) (type: Operation (directive.Operation Anchor (Bytecode Any) Definition)) @@ -144,8 +149,9 @@ ))) (type: Field - {#Constant Constant} - {#Variable Variable}) + (Variant + {#Constant Constant} + {#Variable Variable})) (def: field (Parser Field) @@ -155,10 +161,11 @@ )) (type: Method_Definition - {#Constructor (jvm.Constructor Code)} - {#Virtual_Method (jvm.Virtual_Method Code)} - {#Static_Method (jvm.Static_Method Code)} - {#Overriden_Method (jvm.Overriden_Method Code)}) + (Variant + {#Constructor (jvm.Constructor Code)} + {#Virtual_Method (jvm.Virtual_Method Code)} + {#Static_Method (jvm.Static_Method Code)} + {#Overriden_Method (jvm.Overriden_Method Code)})) (def: method (Parser Method_Definition) @@ -199,7 +206,7 @@ [.#Int type.short [.i64 i32.i32 constant.integer pool.integer]] [.#Int type.int [.i64 i32.i32 constant.integer pool.integer]] [.#Int type.long [constant.long pool.long]] - [.#Frac type.float [host.double_to_float constant.float pool.float]] + [.#Frac type.float [ffi.double_to_float constant.float pool.float]] [.#Frac type.double [constant.double pool.double]] [.#Nat type.char [.i64 i32.i32 constant.integer pool.integer]] [.#Text (type.class "java.lang.String" (list)) [pool.string]] @@ -214,8 +221,10 @@ (field.field (modifier#composite visibility state) name type (sequence.sequence)))) -(def: (method_definition [mapping selfT] [analyse synthesize generate]) - (-> [Mapping .Type] +(def: (method_definition archive supers [mapping selfT] [analyse synthesize generate]) + (-> Archive + (List (Type Class)) + [Mapping .Type] [analysis.Phase synthesis.Phase (generation.Phase Anchor (Bytecode Any) Definition)] @@ -226,18 +235,18 @@ (directive.lifted_analysis (case methodC {#Constructor method} - (jvm.analyse_constructor_method analyse selfT mapping method) + (jvm.analyse_constructor_method analyse archive selfT mapping method) {#Virtual_Method method} - (jvm.analyse_virtual_method analyse selfT mapping method) + (jvm.analyse_virtual_method analyse archive selfT mapping method) {#Static_Method method} - (jvm.analyse_static_method analyse mapping method) + (jvm.analyse_static_method analyse archive mapping method) {#Overriden_Method method} - (jvm.analyse_overriden_method analyse selfT mapping method))))] + (jvm.analyse_overriden_method analyse archive selfT mapping supers method))))] (directive.lifted_synthesis - (synthesize methodA))))) + (synthesize archive methodA))))) (def: jvm::class (Handler Anchor (Bytecode Any) Definition) @@ -250,7 +259,7 @@ (<c>.tuple (<>.some ..annotation)) (<c>.tuple (<>.some ..field)) (<c>.tuple (<>.some ..method))) - (function (_ extension phase + (function (_ extension phase archive [[name parameters] super_class super_interfaces @@ -282,7 +291,7 @@ .let [analyse (value@ [directive.#analysis directive.#phase] state) synthesize (value@ [directive.#synthesis directive.#phase] state) generate (value@ [directive.#generation directive.#phase] state)] - methods (monad.each ! (..method_definition [mapping selfT] [analyse synthesize generate]) + methods (monad.each ! (..method_definition archive (list& super_class super_interfaces) [mapping selfT] [analyse synthesize generate]) methods) ... _ (directive.lifted_generation ... (generation.save! true ["" name] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index 4c7cd1294..9ed84603f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -1,46 +1,47 @@ (.using - [library - [lux {"-" Type} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try] - ["[0]" exception {"+" exception:}] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - [number - ["[0]" i32] - ["f" frac]] - [collection - ["[0]" list ("[1]#[0]" monad)] - ["[0]" dictionary]]] - [target - [jvm - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] - [encoding - ["[0]" signed {"+" S4}]] - ["[0]" type {"+" Type} - [category {"+" Primitive Class}]]]]]] - ["[0]" ///// "_" - [generation - [extension {"+" Nullary Unary Binary Trinary Variadic - nullary unary binary trinary variadic}] - ["///" jvm "_" - ["[1][0]" value] - ["[1][0]" runtime {"+" Operation Phase Bundle Handler}] - ["[1][0]" function "_" - ["[1]" abstract]]]] - [extension - ["[1]extension" /] - ["[1][0]" bundle]] - [// - ["/[1][0]" synthesis {"+" Synthesis %synthesis}] - [/// - ["[1]" phase] - [meta - [archive {"+" Archive}]]]]]) + [library + [lux {"-" Type Label Primitive} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try] + ["[0]" exception {"+" exception:}] + ["<>" parser + ["<[0]>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" monad)] + ["[0]" dictionary]]] + [math + [number + ["f" frac] + ["[0]" i32]]] + [target + [jvm + ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] + [encoding + ["[0]" signed {"+" S4}]] + ["[0]" type {"+" Type} + [category {"+" Primitive Class}]]]]]] + ["[0]" ///// "_" + [generation + [extension {"+" Nullary Unary Binary Trinary Variadic + nullary unary binary trinary variadic}] + ["///" jvm "_" + ["[1][0]" value] + ["[1][0]" runtime {"+" Operation Phase Bundle Handler}] + ["[1][0]" function "_" + ["[1]" abstract]]]] + [extension + ["[1]extension" /] + ["[1][0]" bundle]] + [// + ["/[1][0]" synthesis {"+" Synthesis %synthesis}] + [/// + ["[1]" phase] + [meta + [archive {"+" Archive}]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -48,7 +49,7 @@ (-> Text Phase Archive s (Operation (Bytecode Any)))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.result parser input) + (case (<synthesis>.result parser input) {try.#Success input'} (handler extension_name phase archive input') @@ -99,11 +100,11 @@ ... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and - <s>.any - <s>.any - (<>.some (<s>.tuple ($_ <>.and - (<s>.tuple (<>.many <s>.i64)) - <s>.any)))) + <synthesis>.any + <synthesis>.any + (<>.some (<synthesis>.tuple ($_ <>.and + (<synthesis>.tuple (<>.many <synthesis>.i64)) + <synthesis>.any)))) (function (_ extension_name phase archive [inputS elseS conditionalsS]) (do [! /////.monad] [@end ///runtime.forge_label @@ -227,7 +228,7 @@ (def: (::toString class from) (-> (Type Class) (Type Primitive) (Bytecode Any)) - (_.invokestatic class "toString" (type.method [(list from) ..$String (list)]))) + (_.invokestatic class "toString" (type.method [(list) (list from) ..$String (list)]))) (template [<name> <prepare> <transform>] [(def: (<name> inputG) @@ -304,7 +305,7 @@ ($_ _.composite inputG ..ensure_string - (_.invokevirtual ..$String "length" (type.method [(list) type.int (list)])) + (_.invokevirtual ..$String "length" (type.method [(list) (list) type.int (list)])) ..lux_int)) (def: no_op (Bytecode Any) (_#in [])) @@ -318,13 +319,13 @@ <op> <post>))] [text::= ..no_op ..no_op - (_.invokevirtual ..$Object "equals" (type.method [(list ..$Object) type.boolean (list)])) + (_.invokevirtual ..$Object "equals" (type.method [(list) (list ..$Object) type.boolean (list)])) (///value.wrap type.boolean)] [text::< ..ensure_string ..ensure_string - (_.invokevirtual ..$String "compareTo" (type.method [(list ..$String) type.int (list)])) + (_.invokevirtual ..$String "compareTo" (type.method [(list) (list ..$String) type.int (list)])) (..predicate _.iflt)] [text::char ..ensure_string ..jvm_int - (_.invokevirtual ..$String "charAt" (type.method [(list type.int) type.char (list)])) + (_.invokevirtual ..$String "charAt" (type.method [(list) (list type.int) type.char (list)])) ..lux_int] ) @@ -333,7 +334,7 @@ ($_ _.composite leftG ..ensure_string rightG ..ensure_string - (_.invokevirtual ..$String "concat" (type.method [(list ..$String) ..$String (list)])))) + (_.invokevirtual ..$String "concat" (type.method [(list) (list ..$String) ..$String (list)])))) (def: (text::clip [startG endG subjectG]) (Trinary (Bytecode Any)) @@ -341,9 +342,9 @@ subjectG ..ensure_string startG ..jvm_int endG ..jvm_int - (_.invokevirtual ..$String "substring" (type.method [(list type.int type.int) ..$String (list)])))) + (_.invokevirtual ..$String "substring" (type.method [(list) (list type.int type.int) ..$String (list)])))) -(def: index_method (type.method [(list ..$String type.int) type.int (list)])) +(def: index_method (type.method [(list) (list ..$String type.int) type.int (list)])) (def: (text::index [startG partG textG]) (Trinary (Bytecode Any)) (do _.monad @@ -377,7 +378,7 @@ (/////bundle.install "char" (binary ..text::char)) (/////bundle.install "clip" (trinary ..text::clip))))) -(def: string_method (type.method [(list ..$String) type.void (list)])) +(def: string_method (type.method [(list) (list ..$String) type.void (list)])) (def: (io::log messageG) (Unary (Bytecode Any)) ($_ _.composite 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 f367bd949..6b26d8cfb 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 @@ -1,73 +1,74 @@ (.using - [library - [lux {"-" Type} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" maybe] - ["[0]" try] - ["[0]" exception {"+" exception:}] - ["<>" parser - ["<t>" text] - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [number - ["[0]" i32]] - [collection - ["[0]" list ("[1]#[0]" monad)] - ["[0]" dictionary {"+" Dictionary}] - ["[0]" set] - ["[0]" sequence]] - ["[0]" format "_" - ["[1]" binary]]] - [target - [jvm - ["[0]" version] - ["[0]" modifier ("[1]#[0]" monoid)] - ["[0]" method {"+" Method}] - ["[0]" class {"+" Class}] - [constant - [pool {"+" Resource}]] - [encoding - ["[0]" name]] - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad) - ["__" instruction {"+" Primitive_Array_Type}]] - ["[0]" type {"+" Type Typed Argument} - ["[0]" category {"+" Void Value' Value Return' Return Primitive Object Array Var Parameter}] - ["[0]" box] - ["[0]" reflection] - ["[0]" signature] - ["[0]" parser]]]]]] - ["[0]" // "_" - [common {"+" custom}] - ["///[1]" //// "_" - [generation - [extension {"+" Nullary Unary Binary Trinary Variadic - nullary unary binary trinary variadic}] - ["///" jvm - ["[1][0]" runtime {"+" Operation Bundle Phase Handler}] - ["[1][0]" reference] - [function - [field - [variable - ["[0]" foreign]]]]]] - [extension - ["[1][0]" bundle] - [analysis - ["/" jvm]]] - ["/[1]" // "_" - [analysis {"+" Environment}] - ["[1][0]" synthesis {"+" Synthesis Path %synthesis}] - ["[1][0]" generation] - [/// - ["[1]" phase] - [reference - ["[1][0]" variable {"+" Variable}]] - [meta - ["[0]" archive {"+" Archive}]]]]]]) + [library + [lux {"-" Type Primitive} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" maybe] + ["[0]" exception {"+" exception:}] + ["<>" parser + ["<t>" text] + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" list ("[1]#[0]" monad monoid)] + ["[0]" dictionary {"+" Dictionary}] + ["[0]" set {"+" Set}] + ["[0]" sequence]] + ["[0]" format "_" + ["[1]" binary]]] + [math + [number + ["[0]" i32]]] + [target + [jvm + ["[0]" version] + ["[0]" modifier ("[1]#[0]" monoid)] + ["[0]" method {"+" Method}] + ["[0]" class {"+" Class}] + [constant + [pool {"+" Resource}]] + [encoding + ["[0]" name]] + ["_" bytecode {"+" Bytecode} ("[1]#[0]" monad) + ["__" instruction {"+" Primitive_Array_Type}]] + ["[0]" type {"+" Type Typed Argument} + ["[0]" category {"+" Void Value' Value Return' Return Primitive Object Array Var Parameter}] + ["[0]" box] + ["[0]" reflection] + ["[0]" signature] + ["[0]" parser]]]]]] + ["[0]" // "_" + [common {"+" custom}] + ["///[1]" //// "_" + [generation + [extension {"+" Nullary Unary Binary Trinary Variadic + nullary unary binary trinary variadic}] + ["///" jvm + ["[1][0]" runtime {"+" Operation Bundle Phase Handler}] + ["[1][0]" reference] + [function + [field + [variable + ["[0]" foreign]]]]]] + [extension + ["[1][0]" bundle] + [analysis + ["/" jvm]]] + ["/[1]" // "_" + [analysis {"+" Environment}] + ["[1][0]" synthesis {"+" Synthesis Path %synthesis}] + ["[1][0]" generation] + [/// + ["[1]" phase] + ["[1][0]" reference + ["[2][0]" variable {"+" Variable}]] + [meta + ["[0]" archive {"+" Archive} + ["[0]" artifact] + ["[0]" dependency]]]]]]]) (template [<name> <0> <1>] [(def: <name> @@ -554,7 +555,7 @@ [] (in ($_ _.composite (_.string class) - (_.invokestatic ..$Class "forName" (type.method [(list ..$String) ..$Class (list)]))))))])) + (_.invokestatic ..$Class "forName" (type.method [(list) (list ..$String) ..$Class (list)]))))))])) (def: object::instance? Handler @@ -566,7 +567,7 @@ (in ($_ _.composite objectG (_.instanceof (type.class class (list))) - (_.invokestatic ..$Boolean "valueOf" (type.method [(list type.boolean) ..$Boolean (list)]))))))])) + (_.invokestatic ..$Boolean "valueOf" (type.method [(list) (list type.boolean) ..$Boolean (list)]))))))])) (def: reflection (All (_ category) @@ -588,7 +589,7 @@ (let [$<object> (type.class <object> (list))] ($_ _.composite valueG - (_.invokestatic $<object> "valueOf" (type.method [(list <type>) $<object> (list)])))) + (_.invokestatic $<object> "valueOf" (type.method [(list) (list <type>) $<object> (list)])))) (and (text#= <object> from) @@ -598,7 +599,7 @@ ($_ _.composite valueG (_.checkcast $<object>) - (_.invokevirtual $<object> <unwrap> (type.method [(list) <type> (list)]))))] + (_.invokevirtual $<object> <unwrap> (type.method [(list) (list) <type> (list)]))))] [box.boolean type.boolean "booleanValue"] [box.byte type.byte "byteValue"] @@ -634,7 +635,7 @@ [(reflection.reflection reflection.float) type.float] [(reflection.reflection reflection.double) type.double] [(reflection.reflection reflection.char) type.char]) - (dictionary.from_list text.hash))) + (dictionary.of_list text.hash))) (def: get::static Handler @@ -718,7 +719,8 @@ valueG putG))))])) -(type: Input (Typed Synthesis)) +(type: Input + (Typed Synthesis)) (def: input (Parser Input) @@ -755,7 +757,7 @@ [inputsTG (monad.each ! (generate_input generate archive) inputsTS)] (in ($_ _.composite (monad.each _.monad product.right inputsTG) - (_.invokestatic class method (type.method [(list#each product.left inputsTG) outputT (list)])) + (_.invokestatic class method (type.method [(list) (list#each product.left inputsTG) outputT (list)])) (prepare_output outputT)))))])) (template [<name> <invoke>] @@ -771,7 +773,7 @@ objectG (_.checkcast class) (monad.each _.monad product.right inputsTG) - (<invoke> class method (type.method [(list#each product.left inputsTG) outputT (list)])) + (<invoke> class method (type.method [(list) (list#each product.left inputsTG) outputT (list)])) (prepare_output outputT)))))]))] [invoke::virtual _.invokevirtual] @@ -790,7 +792,7 @@ (_.new class) _.dup (monad.each _.monad product.right inputsTG) - (_.invokespecial class "<init>" (type.method [(list#each product.left inputsTG) type.void (list)]))))))])) + (_.invokespecial class "<init>" (type.method [(list) (list#each product.left inputsTG) type.void (list)]))))))])) (def: bundle::member Bundle @@ -875,10 +877,10 @@ (function (again body) (case body (^template [<tag>] - [(^ {<tag> value}) + [(^ <tag>) body]) - ([//////synthesis.#Primitive] - [//////synthesis.constant]) + ([{//////synthesis.#Primitive _}] + [(//////synthesis.constant _)]) (^ (//////synthesis.variant [lefts right? sub])) (//////synthesis.variant [lefts right? (again sub)]) @@ -936,7 +938,8 @@ (def: (anonymous_init_method env) (-> (Environment Synthesis) (Type category.Method)) - (type.method [(list.repeated (list.size env) ..$Object) + (type.method [(list) + (list.repeated (list.size env) ..$Object) type.void (list)])) @@ -955,7 +958,7 @@ {.#Some ($_ _.composite (_.aload 0) (monad.each _.monad product.right inputsTG) - (_.invokespecial super_class "<init>" (type.method [(list#each product.left inputsTG) type.void (list)])) + (_.invokespecial super_class "<init>" (type.method [(list) (list#each product.left inputsTG) type.void (list)])) store_capturedG _.return)}))) @@ -999,6 +1002,28 @@ ... (# type.equivalence = type.double returnT) _.dreturn)))) +(def: (method_dependencies archive method) + (-> Archive (/.Overriden_Method Synthesis) (Operation (Set artifact.Dependency))) + (let [[_super _name _strict_fp? _annotations + _t_vars _this _arguments _return _exceptions + bodyS] method] + (dependency.dependencies archive bodyS))) + +(def: (anonymous_dependencies archive inputsTS overriden_methods) + (-> Archive (List Input) (List [(Environment Synthesis) (/.Overriden_Method Synthesis)]) + (Operation (Set artifact.Dependency))) + (do [! //////.monad] + [all_input_dependencies (monad.each ! (|>> product.right (dependency.dependencies archive)) inputsTS) + all_closure_dependencies (|> overriden_methods + (list#each product.left) + list.together + (monad.each ! (dependency.dependencies archive))) + all_method_dependencies (monad.each ! (|>> product.right (method_dependencies archive)) overriden_methods)] + (in (dependency.all ($_ list#composite + all_input_dependencies + all_closure_dependencies + all_method_dependencies))))) + (def: class::anonymous Handler (..custom @@ -1011,7 +1036,8 @@ inputsTS overriden_methods]) (do [! //////.monad] - [[context _] (//////generation.with_new_context archive (in [])) + [all_dependencies (anonymous_dependencies archive inputsTS overriden_methods) + [context _] (//////generation.with_new_context archive all_dependencies (in [])) .let [[module_id artifact_id] context anonymous_class_name (///runtime.class_name context) class (type.class anonymous_class_name (list)) @@ -1021,14 +1047,14 @@ ... Combine them. list#conjoint ... Remove duplicates. - (set.from_list //////synthesis.hash) + (set.of_list //////synthesis.hash) set.list) global_mapping (|> total_environment ... Give them names as "foreign" variables. list.enumeration (list#each (function (_ [id capture]) [capture {//////variable.#Foreign id}])) - (dictionary.from_list //////variable.hash)) + (dictionary.of_list //////synthesis.hash)) normalized_methods (list#each (function (_ [environment [ownerT name strict_fp? annotations vars @@ -1041,7 +1067,7 @@ (|> global_mapping (dictionary.value capture) maybe.trusted)])) - (dictionary.from_list //////variable.hash))] + (dictionary.of_list //////variable.hash))] [ownerT name strict_fp? annotations vars self_name arguments returnT exceptionsT @@ -1062,7 +1088,8 @@ method.strict modifier#identity)) name - (type.method [(list#each product.right arguments) + (type.method [(list) + (list#each product.right arguments) returnT exceptionsT]) (list) @@ -1081,7 +1108,7 @@ method_definitions) (sequence.sequence))) _ (//////generation.execute! [anonymous_class_name bytecode]) - _ (//////generation.save! (%.nat artifact_id) [anonymous_class_name bytecode])] + _ (//////generation.save! artifact_id {.#None} [anonymous_class_name bytecode])] (anonymous_instance generate archive class total_environment)))])) (def: bundle::class diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 9be2267ea..0d2774331 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -1,39 +1,40 @@ (.using - [library - [lux {"-" Type if let case int} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function]] - [data - [number - ["[0]" i32] - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [target - [jvm - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] - ["[0]" type {"+" Type} - [category {"+" Method}]]]]]] - ["[0]" // "_" - ["[1][0]" type] - ["[1][0]" runtime {"+" Operation Phase Generator}] - ["[1][0]" value] - ["[1][0]" structure] - [//// - ["[0]" synthesis {"+" Path Synthesis}] - ["[0]" generation] - [/// - ["[0]" phase ("operation#[0]" monad)] - [reference - [variable {"+" Register}]]]]]) + [library + [lux {"-" Type Label if let case int} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function]] + [data + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + [number + ["n" nat] + ["[0]" i32]]] + [target + [jvm + ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] + ["[0]" type {"+" Type} + [category {"+" Method}]]]]]] + ["[0]" // "_" + ["[1][0]" type] + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" value] + ["[1][0]" structure] + [//// + ["[0]" synthesis {"+" Path Synthesis}] + ["[0]" generation] + [/// + ["[0]" phase ("operation#[0]" monad)] + [reference + [variable {"+" Register}]]]]]) (def: equals_name "equals") (def: equals_type - (type.method [(list //type.value) type.boolean (list)])) + (type.method [(list) (list //type.value) type.boolean (list)])) (def: (pop_alt stack_depth) (-> Nat (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index b9d62421b..fd110c5d2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -1,62 +1,65 @@ (.using - [library - [lux {"-" Type} - [abstract - ["[0]" monad {"+" do}]] - [data - [number - ["[0]" i32] - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" monoid functor)] - ["[0]" sequence]] - ["[0]" format "_" - ["[1]" binary]]] - [target - [jvm - ["[0]" version] - ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)] - ["[0]" field {"+" Field}] - ["[0]" method {"+" Method}] - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] - ["[0]" class {"+" Class}] - ["[0]" type {"+" Type} - [category {"+" Return' Value'}] - ["[0]" reflection]] - ["[0]" constant - [pool {"+" Resource}]] - [encoding - ["[0]" name {"+" External Internal}] - ["[0]" unsigned]]]] - [tool - [compiler - [meta - ["[0]" archive {"+" Archive}]]]]]] - ["[0]" / "_" - ["[1][0]" abstract] - [field - [constant - ["[1][0]" arity]] - [variable - ["[1][0]" foreign] - ["[1][0]" partial]]] - [method - ["[1][0]" init] - ["[1][0]" new] - ["[1][0]" implementation] - ["[1][0]" reset] - ["[1][0]" apply]] - ["/[1]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] - [//// - [analysis {"+" Environment}] - [synthesis {"+" Synthesis Abstraction Apply}] - ["[0]" generation] - [/// - ["[0]" arity {"+" Arity}] - ["[0]" phase] - [reference - [variable {"+" Register}]]]]]]) + [library + [lux {"-" Type Label} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" monoid functor)] + ["[0]" sequence]] + ["[0]" format "_" + ["[1]" binary]]] + [math + [number + ["n" nat] + ["[0]" i32]]] + [target + [jvm + ["[0]" version] + ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)] + ["[0]" field {"+" Field}] + ["[0]" method {"+" Method}] + ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] + ["[0]" class {"+" Class}] + ["[0]" type {"+" Type} + [category {"+" Return' Value'}] + ["[0]" reflection]] + ["[0]" constant + [pool {"+" Resource}]] + [encoding + ["[0]" name {"+" External Internal}] + ["[0]" unsigned]]]] + [tool + [compiler + [meta + ["[0]" archive {"+" Archive} + ["[0]" dependency]]]]]]] + ["[0]" / "_" + ["[1][0]" abstract] + [field + [constant + ["[1][0]" arity]] + [variable + ["[1][0]" foreign] + ["[1][0]" partial]]] + [method + ["[1][0]" init] + ["[1][0]" new] + ["[1][0]" implementation] + ["[1][0]" reset] + ["[1][0]" apply]] + ["/[1]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + [//// + [analysis {"+" Environment}] + [synthesis {"+" Synthesis Abstraction Apply}] + ["[0]" generation] + [/// + ["[0]" arity {"+" Arity}] + ["[0]" phase] + [reference + [variable {"+" Register}]]]]]]) (def: .public (with generate archive @begin class environment arity body) (-> Phase Archive Label External (Environment Synthesis) Arity (Bytecode Any) @@ -98,8 +101,9 @@ (def: .public (abstraction generate archive [environment arity bodyS]) (Generator Abstraction) (do phase.monad - [@begin //runtime.forge_label - [function_context bodyG] (generation.with_new_context archive + [dependencies (dependency.dependencies archive bodyS) + @begin //runtime.forge_label + [function_context bodyG] (generation.with_new_context archive dependencies (generation.with_anchor [@begin ..this_offset] (generate archive bodyS))) .let [function_class (//runtime.class_name function_context)] @@ -111,9 +115,9 @@ fields methods (sequence.sequence))) - .let [bytecode (format.result class.writer class)] - _ (generation.execute! [function_class bytecode]) - _ (generation.save! function_class {.#None} [function_class bytecode])] + .let [bytecode [function_class (format.result class.writer class)]] + _ (generation.execute! bytecode) + _ (generation.save! (product.right function_context) {.#None} bytecode)] (in instance))) (def: .public (apply generate archive [abstractionS inputsS]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux index cca523398..a0880a4e2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux @@ -1,33 +1,33 @@ (.using - [library - [lux {"-" Type} - [abstract - ["[0]" monad]] - [data - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [target - [jvm - ["[0]" field {"+" Field}] - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] - [type {"+" Type} - [category {"+" Class}]] - [constant - [pool {"+" Resource}]]]]]] - ["[0]" / "_" - ["[1][0]" count] - ["/[1]" // - ["/[1]" // "_" + [library + [lux {"-" Type} + [abstract + ["[0]" monad]] + [data + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["n" nat]]] + [target + [jvm + ["[0]" field {"+" Field}] + ["_" bytecode {"+" Bytecode} ("[1]#[0]" monad)] + [type {"+" Type} + [category {"+" Class}]] [constant - ["[1][0]" arity]] - ["//[1]" /// "_" - ["[1][0]" reference] - [////// - ["[0]" arity {"+" Arity}] - [reference - [variable {"+" Register}]]]]]]]) + [pool {"+" Resource}]]]]]] + ["[0]" // + ["[1][0]" count] + ["/[1]" // "_" + [constant + ["[1][0]" arity]] + ["//[1]" /// "_" + ["[1][0]" reference] + [////// + ["[0]" arity {"+" Arity}] + [reference + [variable {"+" Register}]]]]]]) (def: .public (initial amount) (-> Nat (Bytecode Any)) @@ -53,6 +53,6 @@ (-> Arity (Bytecode Any)) (if (arity.multiary? arity) ($_ _.composite - /count.initial + //count.initial (initial (n.- ///arity.minimum arity))) (_#in []))) 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 094287f9a..050ca318a 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 @@ -1,51 +1,52 @@ (.using - [library - [lux {"-" Type type} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try]] - [data - [number - ["n" nat] - ["i" int] - ["[0]" i32]] - [collection - ["[0]" list ("[1]#[0]" monoid functor)]]] - [target - [jvm - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] - ["[0]" method {"+" Method}] - [constant - [pool {"+" Resource}]] - [encoding - ["[0]" signed]] - ["[0]" type {"+" Type} - ["[0]" category {"+" Class}]]]]]] - ["[0]" // - ["[1][0]" reset] - ["[1][0]" implementation] - ["[1][0]" init] - ["/[1]" // "_" - ["[1][0]" abstract] - [field + [library + [lux {"-" Type Label type} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try]] + [data + [collection + ["[0]" list ("[1]#[0]" monoid functor)]]] + [math + [number + ["n" nat] + ["i" int] + ["[0]" i32]]] + [target + [jvm + ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)] + ["[0]" method {"+" Method}] [constant - ["[1][0]" arity]] - [variable - ["[1][0]" partial - ["[1]/[0]" count]] - ["[1][0]" foreign]]] - ["/[1]" // "_" - ["[1][0]" runtime] - ["[1][0]" value] - ["[1][0]" reference] - [//// - [analysis {"+" Environment}] - [synthesis {"+" Synthesis}] - [/// - [arity {"+" Arity}] - [reference - [variable {"+" Register}]]]]]]]) + [pool {"+" Resource}]] + [encoding + ["[0]" signed]] + ["[0]" type {"+" Type} + ["[0]" category {"+" Class}]]]]]] + ["[0]" // + ["[1][0]" reset] + ["[1][0]" implementation] + ["[1][0]" init] + ["/[1]" // "_" + ["[1][0]" abstract] + [field + [constant + ["[1][0]" arity]] + [variable + ["[1][0]" partial] + ["[1][0]" count] + ["[1][0]" foreign]]] + ["/[1]" // "_" + ["[1][0]" runtime] + ["[1][0]" value] + ["[1][0]" reference] + [//// + [analysis {"+" Environment}] + [synthesis {"+" Synthesis}] + [/// + [arity {"+" Arity}] + [reference + [variable {"+" Register}]]]]]]]) (def: (increment by) (-> Nat (Bytecode Any)) @@ -143,7 +144,7 @@ (_.new class) _.dup current_environment - ///partial/count.value + ///count.value (..increment apply_arity) current_partials (..inputs ..this_offset apply_arity) @@ -152,6 +153,6 @@ _.areturn))))))) (monad.all _.monad))]] ($_ _.composite - ///partial/count.value + ///count.value (_.tableswitch (try.trusted (signed.s4 +0)) @default [@labelsH @labelsT]) cases)))}))) 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 11e2013e2..664e0fbc8 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 @@ -1,28 +1,29 @@ (.using - [library - [lux {"-" Type type} - [data - [collection - ["[0]" list]]] - [target - [jvm - ["[0]" method {"+" Method}] - ["_" bytecode {"+" Label Bytecode}] - [constant - [pool {"+" Resource}]] - ["[0]" type {"+" Type} - ["[0]" category]]]]]] - ["[0]" // - ["//[1]" /// "_" - ["[1][0]" type] - [////// - [arity {"+" Arity}]]]]) + [library + [lux {"-" Type Label type} + [data + [collection + ["[0]" list]]] + [target + [jvm + ["[0]" method {"+" Method}] + ["_" bytecode {"+" Label Bytecode}] + [constant + [pool {"+" Resource}]] + ["[0]" type {"+" Type} + ["[0]" category]]]]]] + ["[0]" // + ["//[1]" /// "_" + ["[1][0]" type] + [////// + [arity {"+" Arity}]]]]) (def: .public name "impl") (def: .public (type arity) (-> Arity (Type category.Method)) - (type.method [(list.repeated arity ////type.value) + (type.method [(list) + (list.repeated arity ////type.value) ////type.value (list)])) 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 a4559bbd0..37278725b 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 @@ -1,45 +1,46 @@ (.using - [library - [lux {"-" Type type} - [abstract - ["[0]" monad]] - [control - ["[0]" try]] - [data - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" monoid functor)]]] - [target - [jvm - ["_" bytecode {"+" Bytecode}] - ["[0]" method {"+" Method}] - [encoding - ["[0]" unsigned]] - [constant - [pool {"+" Resource}]] - ["[0]" type {"+" Type} - ["[0]" category {"+" Class Value}]]]]]] - ["[0]" // - ["[1][0]" implementation] - ["/[1]" // "_" - ["[1][0]" abstract] - [field + [library + [lux {"-" Type type} + [abstract + ["[0]" monad]] + [control + ["[0]" try]] + [data + [collection + ["[0]" list ("[1]#[0]" monoid functor)]]] + [math + [number + ["n" nat]]] + [target + [jvm + ["_" bytecode {"+" Bytecode}] + ["[0]" method {"+" Method}] + [encoding + ["[0]" signed]] [constant - ["[1][0]" arity]] - [variable - ["[1][0]" foreign] - ["[1][0]" partial]]] - ["/[1]" // "_" - ["[1][0]" type] - ["[1][0]" reference] - [//// - [analysis {"+" Environment}] - [synthesis {"+" Synthesis}] - [/// - ["[0]" arity {"+" Arity}] - [reference - [variable {"+" Register}]]]]]]]) + [pool {"+" Resource}]] + ["[0]" type {"+" Type} + ["[0]" category {"+" Class Value}]]]]]] + ["[0]" // + ["[1][0]" implementation] + ["/[1]" // "_" + ["[1][0]" abstract] + [field + [constant + ["[1][0]" arity]] + [variable + ["[1][0]" foreign] + ["[1][0]" partial]]] + ["/[1]" // "_" + ["[1][0]" type] + ["[1][0]" reference] + [//// + [analysis {"+" Environment}] + [synthesis {"+" Synthesis}] + [/// + ["[0]" arity {"+" Arity}] + [reference + [variable {"+" Register}]]]]]]]) (def: .public name "<init>") @@ -49,7 +50,8 @@ (def: .public (type environment arity) (-> (Environment Synthesis) Arity (Type category.Method)) - (type.method [(list#composite (///foreign.closure environment) + (type.method [(list) + (list#composite (///foreign.closure environment) (if (arity.multiary? arity) (list& ///arity.type (..partials arity)) (list))) @@ -57,8 +59,8 @@ (list)])) (def: no_partials - (|> 0 - unsigned.u1 + (|> +0 + signed.s1 try.trusted _.bipush)) 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 5c059f5a7..5c03b472b 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 @@ -1,46 +1,47 @@ (.using - [library - [lux {"-" Type type} - [abstract - ["[0]" monad {"+" do}]] - [data - [number - ["n" nat]] - [collection - ["[0]" list]]] - [target - [jvm - ["[0]" field {"+" Field}] - ["[0]" method {"+" Method}] - ["_" bytecode {"+" Bytecode}] - ["[0]" constant - [pool {"+" Resource}]] - [type {"+" Type} - ["[0]" category {"+" Class Value Return}]]]] - [tool - [compiler - [meta - ["[0]" archive {"+" Archive}]]]]]] - ["[0]" // - ["[1][0]" init] - ["[1][0]" implementation] + [library + [lux {"-" Type type} + [abstract + ["[0]" monad {"+" do}]] + [data + [collection + ["[0]" list]]] + [math + [number + ["n" nat]]] + [target + [jvm + ["[0]" field {"+" Field}] + ["[0]" method {"+" Method}] + ["_" bytecode {"+" Bytecode}] + ["[0]" constant + [pool {"+" Resource}]] + [type {"+" Type} + ["[0]" category {"+" Class Value Return}]]]] + [tool + [compiler + [meta + ["[0]" archive {"+" Archive}]]]]]] + ["[0]" // + ["[1][0]" init] + ["[1][0]" implementation] + ["/[1]" // "_" + [field + [constant + ["[1][0]" arity]] + [variable + ["[1][0]" foreign] + ["[1][0]" partial]]] ["/[1]" // "_" - [field - [constant - ["[1][0]" arity]] - [variable - ["[1][0]" foreign] - ["[1][0]" partial]]] - ["/[1]" // "_" - [runtime {"+" Operation Phase}] - ["[1][0]" value] - ["[1][0]" reference] - [//// - [analysis {"+" Environment}] - [synthesis {"+" Synthesis}] - [/// - ["[0]" arity {"+" Arity}] - ["[0]" phase]]]]]]) + [runtime {"+" Operation Phase}] + ["[1][0]" value] + ["[1][0]" reference] + [//// + [analysis {"+" Environment}] + [synthesis {"+" Synthesis}] + [/// + ["[0]" arity {"+" Arity}] + ["[0]" phase]]]]]]) (def: .public (instance' foreign_setup class environment arity) (-> (List (Bytecode Any)) (Type Class) (Environment Synthesis) Arity (Bytecode Any)) 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 112f1b0fc..d1a78ce86 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 @@ -30,7 +30,7 @@ (def: .public (type class) (-> (Type Class) (Type category.Method)) - (type.method [(list) class (list)])) + (type.method [(list) (list) class (list)])) (def: (current_environment class) (-> (Type Class) (Environment Synthesis) (List (Bytecode Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index 60c42160b..60f6c3b2a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -1,29 +1,30 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function]] - [data - ["[0]" product] - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [target - [jvm - ["_" bytecode {"+" Label Bytecode} ("[1]#[0]" monad)]]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] - ["[1][0]" value] - [//// - ["[0]" synthesis {"+" Path Synthesis}] - ["[0]" generation] - [/// - ["[0]" phase] - [reference - [variable {"+" Register}]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["n" nat]]] + [target + [jvm + ["_" bytecode {"+" Bytecode} ("[1]#[0]" monad)]]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" value] + [//// + ["[0]" synthesis {"+" Path Synthesis}] + ["[0]" generation] + [/// + ["[0]" phase] + [reference + [variable {"+" Register}]]]]]) (def: (invariant? register changeS) (-> Register Synthesis Bit) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index 12bddd14d..44200c2d2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -1,17 +1,22 @@ (.using - [library - [lux {"-" i64} - ["[0]" ffi {"+" import:}] - [abstract - [monad {"+" do}]] - [target - [jvm - ["_" bytecode {"+" Bytecode}] - ["[0]" type] - [encoding - ["[0]" signed]]]]]] - ["[0]" // "_" - ["[1][0]" runtime]]) + [library + [lux {"-" i64} + ["[0]" ffi {"+" import:}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try]] + [math + [number + ["i" int]]] + [target + [jvm + ["_" bytecode {"+" Bytecode}] + ["[0]" type] + [encoding + ["[0]" signed]]]]]] + ["[0]" // "_" + ["[1][0]" runtime]]) (def: $Boolean (type.class "java.lang.Boolean" (list))) (def: $Long (type.class "java.lang.Long" (list))) @@ -22,7 +27,7 @@ (_.getstatic $Boolean (if value "TRUE" "FALSE") $Boolean)) (def: wrap_i64 - (_.invokestatic $Long "valueOf" (type.method [(list type.long) $Long (list)]))) + (_.invokestatic $Long "valueOf" (type.method [(list) (list type.long) $Long (list)]))) (def: .public (i64 value) (-> (I64 Any) (Bytecode Any)) @@ -71,10 +76,15 @@ ..wrap_i64))))) (def: wrap_f64 - (_.invokestatic $Double "valueOf" (type.method [(list type.double) $Double (list)]))) + (_.invokestatic $Double "valueOf" (type.method [(list) (list type.double) $Double (list)]))) (import: java/lang/Double - ("static" doubleToRawLongBits "manual" [double] int)) + ["[1]::[0]" + ("static" doubleToRawLongBits "manual" [double] int)]) + +(def: d0_bits + Int + (java/lang/Double::doubleToRawLongBits +0.0)) (def: .public (f64 value) (-> Frac (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux index f06e89e38..0f0012727 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux @@ -1,39 +1,42 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [data - [number - ["[0]" i32]] - [collection - ["[0]" list]]] - [target - [jvm - ["_" bytecode {"+" Bytecode}] - ["[0]" type] - [encoding - ["[0]" signed]]]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] - ["[1][0]" primitive] - ["///[1]" //// "_" - [analysis {"+" Variant Tuple}] - ["[1][0]" synthesis {"+" Synthesis}] - [/// - ["[0]" phase]]]]) + [library + [lux {"-" Variant Tuple} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try]] + [data + [collection + ["[0]" list]]] + [math + [number + ["[0]" i32]]] + [target + [jvm + ["_" bytecode {"+" Bytecode}] + ["[0]" type] + [encoding + ["[0]" signed]]]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" primitive] + ["///[1]" //// "_" + [analysis {"+" Variant Tuple}] + ["[1][0]" synthesis {"+" Synthesis}] + [/// + ["[0]" phase]]]]) (def: $Object (type.class "java.lang.Object" (list))) -(def: .public (tuple generate archive membersS) +(def: .public (tuple phase archive membersS) (Generator (Tuple Synthesis)) (case membersS {.#End} (# phase.monad in //runtime.unit) {.#Item singletonS {.#End}} - (generate archive singletonS) + (phase archive singletonS) _ (do [! phase.monad] @@ -41,7 +44,7 @@ list.enumeration (monad.each ! (function (_ [idx member]) (do ! - [memberI (generate archive member)] + [memberI (phase archive member)] (in (do _.monad [_ _.dup _ (_.int (.i64 idx)) @@ -81,15 +84,16 @@ //runtime.right_flag //runtime.left_flag)) -(def: .public (variant generate archive [lefts right? valueS]) +(def: .public (variant phase archive [lefts right? valueS]) (Generator (Variant Synthesis)) (do phase.monad - [valueI (generate archive valueS)] + [valueI (phase archive valueS)] (in (do _.monad [_ (..tag lefts right?) _ (..flag right?) _ valueI] (_.invokestatic //runtime.class "variant" - (type.method [(list type.int $Object $Object) + (type.method [(list) + (list type.int $Object $Object) (type.array $Object) (list)])))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux index c9ffff258..25f68450d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux @@ -6,4 +6,4 @@ (def: .public version Version - 00,06,05) + 00,07,00) |