From e3986e8a7b9a997441477cdb333d3a8537dc49fb Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 18 Feb 2022 17:37:21 -0400 Subject: Yet more fixes for JVM interop. --- stdlib/source/library/lux/control/parser/type.lux | 52 +++---- stdlib/source/library/lux/target/python.lux | 4 +- .../compiler/language/lux/phase/analysis/case.lux | 169 +++++++++++---------- .../language/lux/phase/analysis/complex.lux | 13 +- .../language/lux/phase/extension/analysis/jvm.lux | 127 ++++++++++------ .../lux/phase/extension/generation/jvm/host.lux | 18 ++- .../lux/phase/generation/python/runtime.lux | 2 +- .../lux/tool/compiler/meta/packager/script.lux | 3 - stdlib/source/library/lux/type/poly.lux | 50 +++--- 9 files changed, 248 insertions(+), 190 deletions(-) (limited to 'stdlib/source/library') diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux index 03483c788..3f4da5ee2 100644 --- a/stdlib/source/library/lux/control/parser/type.lux +++ b/stdlib/source/library/lux/control/parser/type.lux @@ -1,26 +1,26 @@ (.using - [library - [lux {"-" function local} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}] - ["[0]" function]] - [data - ["[0]" text ("[1]#[0]" monoid) - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" dictionary {"+" Dictionary}]]] - [macro - ["[0]" code]] - [math - [number - ["n" nat ("[1]#[0]" decimal)]]] - ["[0]" type ("[1]#[0]" equivalence) - ["[0]" check]]]] - ["[0]" //]) + [library + [lux {"-" function local} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}] + ["[0]" function]] + [data + ["[0]" text ("[1]#[0]" monoid) + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["[0]" code]] + [math + [number + ["n" nat ("[1]#[0]" decimal)]]] + ["[0]" type ("[1]#[0]" equivalence) + ["[0]" check]]]] + ["[0]" //]) (template: (|recursion_dummy|) [{.#Primitive "" {.#End}}]) @@ -245,7 +245,7 @@ [super (function.flipped check.subsumes?)] ) -(def: .public (adjusted_idx env idx) +(def: .public (argument env idx) (-> Env Nat Nat) (let [env_level (n./ 2 (dictionary.size env)) parameter_level (n./ 2 idx) @@ -259,7 +259,7 @@ headT any] (case headT {.#Parameter idx} - (case (dictionary.value (adjusted_idx env idx) env) + (case (dictionary.value (..argument env idx) env) {.#Some [poly_type poly_code]} (in poly_code) @@ -276,7 +276,7 @@ headT any] (case headT {.#Parameter idx} - (if (n.= id (adjusted_idx env idx)) + (if (n.= id (..argument env idx)) (in []) (//.failure (exception.error ..wrong_parameter [{.#Parameter id} headT]))) @@ -328,7 +328,7 @@ headT any] (case (type.anonymous headT) (^multi (^ {.#Apply (|recursion_dummy|) {.#Parameter funcT_idx}}) - (n.= 0 (adjusted_idx env funcT_idx)) + (n.= 0 (..argument env funcT_idx)) [(dictionary.value 0 env) {.#Some [self_type self_call]}]) (in self_call) diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux index b574b6688..1e0d3a59b 100644 --- a/stdlib/source/library/lux/target/python.lux +++ b/stdlib/source/library/lux/target/python.lux @@ -211,13 +211,13 @@ ) (def: .public (slice from to list) - (-> (Expression Any) (Expression Any) (Expression Any) (Computation Any)) + (-> (Expression Any) (Expression Any) (Expression Any) Access) (<| :abstraction ... ..expression (format (:representation list) "[" (:representation from) ":" (:representation to) "]"))) (def: .public (slice_from from list) - (-> (Expression Any) (Expression Any) (Computation Any)) + (-> (Expression Any) (Expression Any) Access) (<| :abstraction ... ..expression (format (:representation list) "[" (:representation from) ":]"))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index 3e81c08b8..2c957abe7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -20,7 +20,7 @@ [macro ["[0]" code]] ["[0]" type - ["[0]" check]]]] + ["[0]" check {"+" Check}]]]] ["[0]" / "_" ["/[1]" // "_" ["[1][0]" complex] @@ -37,8 +37,8 @@ [/// ["[1]" phase]]]]]]) -(exception: .public (cannot_match_with_pattern [type Type - pattern Code]) +(exception: .public (mismatch [type Type + pattern Code]) (exception.report ["Type" (%.type type)] ["Pattern" (%.code pattern)])) @@ -49,15 +49,15 @@ ["Case" (%.nat case)] ["Type" (%.type type)])) -(exception: .public (not_a_pattern [code Code]) - (exception.report ["Code" (%.code code)])) +(exception: .public (invalid [it Code]) + (exception.report ["Pattern" (%.code it)])) -(exception: .public (cannot_simplify_for_pattern_matching [type Type]) +(exception: .public (non_tuple [type Type]) (exception.report ["Type" (%.type type)])) -(exception: .public (non_exhaustive_pattern_matching [input Code - branches (List [Code Code]) - coverage Coverage]) +(exception: .public (non_exhaustive [input Code + branches (List [Code Code]) + coverage Coverage]) (exception.report ["Input" (%.code input)] ["Branches" (%.code (code.tuple (|> branches @@ -66,17 +66,16 @@ list#conjoint)))] ["Coverage" (/coverage.format coverage)])) -(exception: .public (cannot_have_empty_branches [message Text]) - message) +(exception: .public empty_branches) -(def: (re_quantify envs baseT) +(def: (quantified envs baseT) (-> (List (List Type)) Type Type) (.case envs {.#End} baseT {.#Item head tail} - (re_quantify tail {.#UnivQ head baseT}))) + (quantified tail {.#UnivQ head baseT}))) ... Type-checking on the input value is done during the analysis of a ... "case" expression, to ensure that the patterns being used make @@ -85,21 +84,21 @@ ... type-variables or quantifications. ... This function makes it easier for "case" analysis to properly ... type-check the input with respect to the patterns. -(def: (simplify_case caseT) - (-> Type (Operation Type)) +(def: .public (tuple :it:) + (-> Type (Check [(List check.Var) Type])) (loop [envs (: (List (List Type)) (list)) - caseT caseT] - (.case caseT + :it: :it:] + (.case :it: {.#Var id} - (do ///.monad - [?caseT' (/type.check (check.peek id))] - (.case ?caseT' - {.#Some caseT'} - (again envs caseT') + (do check.monad + [?:it:' (check.peek id)] + (.case ?:it:' + {.#Some :it:'} + (again envs :it:') _ - (/.except ..cannot_simplify_for_pattern_matching caseT))) + (check.except ..non_tuple :it:))) {.#Named name unnamedT} (again envs unnamedT) @@ -108,44 +107,46 @@ (again {.#Item env envs} unquantifiedT) {.#ExQ _} - (do ///.monad - [[var_id varT] (/type.check check.var)] - (again envs (maybe.trusted (type.applied (list varT) caseT)))) - - {.#Apply inputT funcT} - (.case funcT - {.#Var funcT_id} - (do ///.monad - [funcT' (/type.check - (do check.monad - [?funct' (check.peek funcT_id)] - (.case ?funct' - {.#Some funct'} - (in funct') - - _ - (check.except ..cannot_simplify_for_pattern_matching caseT))))] - (again envs {.#Apply inputT funcT'})) - - _ - (.case (type.applied (list inputT) funcT) - {.#Some outputT} - (again envs outputT) + (do check.monad + [[@head :head:] check.var + [tail :tuple:] (again envs (maybe.trusted (type.applied (list :head:) :it:)))] + (in [(list& @head tail) :tuple:])) + + {.#Apply _} + (do [! check.monad] + [.let [[:abstraction: :parameters:] (type.flat_application :it:)] + :abstraction: (.case :abstraction: + {.#Var @abstraction} + (do ! + [?:abstraction: (check.peek @abstraction)] + (.case ?:abstraction: + {.#Some :abstraction:} + (in :abstraction:) + + _ + (check.except ..non_tuple :it:))) + + _ + (in :abstraction:))] + (.case (type.applied :parameters: :abstraction:) + {.#Some :it:} + (again envs :it:) {.#None} - (/.except ..cannot_simplify_for_pattern_matching caseT))) + (check.except ..non_tuple :it:))) {.#Product _} - (|> caseT + (|> :it: type.flat_tuple - (list#each (re_quantify envs)) + (list#each (..quantified envs)) type.tuple - (# ///.monad in)) + [(list)] + (# check.monad in)) _ - (# ///.monad in (re_quantify envs caseT))))) + (# check.monad in [(list) (..quantified envs :it:)])))) -(def: (analyse_simple type inputT location output next) +(def: (simple_pattern_analysis type inputT location output next) (All (_ a) (-> Type Type Location Pattern (Operation a) (Operation [Pattern a]))) (/.with_location location (do ///.monad @@ -153,12 +154,12 @@ outputA next] (in [output outputA])))) -(def: (analyse_tuple_pattern analyse_pattern inputT sub_patterns next) +(def: (tuple_pattern_analysis pattern_analysis inputT sub_patterns next) (All (_ a) (-> (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])) Type (List Code) (Operation a) (Operation [Pattern a]))) (do [! ///.monad] - [inputT' (simplify_case inputT)] + [[@ex_var+ inputT'] (/type.check (..tuple inputT))] (.case inputT' {.#Product _} (let [matches (loop [types (type.flat_tuple inputT') @@ -190,18 +191,19 @@ (function (_ [memberT memberC] then) (do ! [[memberP [memberP+ thenA]] ((:as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) - analyse_pattern) + pattern_analysis) {.#None} memberT memberC then)] (in [(list& memberP memberP+) thenA])))) (do ! [nextA next] (in [(list) nextA])) - matches)] + matches) + _ (/type.check (monad.each check.monad check.forget! @ex_var+))] (in [(/pattern.tuple memberP+) thenA]))) _ - (/.except ..cannot_match_with_pattern [inputT' (code.tuple sub_patterns)])))) + (/.except ..mismatch [inputT' (code.tuple sub_patterns)])))) ... This function handles several concerns at once, but it must be that ... way because those concerns are interleaved when doing @@ -219,7 +221,7 @@ ... body expressions. ... That is why the body must be analysed in the context of the ... pattern, and not separately. -(def: (analyse_pattern num_tags inputT pattern next) +(def: (pattern_analysis num_tags inputT pattern next) (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) (.case pattern [location {.#Symbol ["" name]}] @@ -232,7 +234,7 @@ (^template [ ] [[location ] - (analyse_simple inputT location {/pattern.#Simple } next)]) + (simple_pattern_analysis inputT location {/pattern.#Simple } next)]) ([Bit {.#Bit pattern_value} {/simple.#Bit pattern_value}] [Nat {.#Nat pattern_value} {/simple.#Nat pattern_value}] [Int {.#Int pattern_value} {/simple.#Int pattern_value}] @@ -242,12 +244,12 @@ [Any {.#Tuple {.#End}} {/simple.#Unit}]) (^ [location {.#Tuple (list singleton)}]) - (analyse_pattern {.#None} inputT singleton next) + (pattern_analysis {.#None} inputT singleton next) [location {.#Tuple sub_patterns}] (/.with_location location (do [! ///.monad] - [record (//complex.normal sub_patterns) + [record (//complex.normal true sub_patterns) record_size,members,recordT (: (Operation (Maybe [Nat (List Code) Type])) (.case record {.#Some record} @@ -266,18 +268,18 @@ (in []))] (.case members (^ (list singleton)) - (analyse_pattern {.#None} inputT singleton next) + (pattern_analysis {.#None} inputT singleton next) _ - (analyse_tuple_pattern analyse_pattern inputT members next))) + (..tuple_pattern_analysis pattern_analysis inputT members next))) {.#None} - (analyse_tuple_pattern analyse_pattern inputT sub_patterns next)))) + (..tuple_pattern_analysis pattern_analysis inputT sub_patterns next)))) (^ [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) (/.with_location location (do ///.monad - [inputT' (simplify_case inputT)] + [[@ex_var+ inputT'] (/type.check (..tuple inputT))] (.case inputT' {.#Sum _} (let [flat_sum (type.flat_variant inputT') @@ -290,11 +292,12 @@ (do ///.monad [[testP nextA] (if (and (n.> num_cases size_sum) (n.= (-- num_cases) idx)) - (analyse_pattern {.#None} - (type.variant (list.after (-- num_cases) flat_sum)) - (` [(~+ values)]) - next) - (analyse_pattern {.#None} caseT (` [(~+ values)]) next))] + (pattern_analysis {.#None} + (type.variant (list.after (-- num_cases) flat_sum)) + (` [(~+ values)]) + next) + (pattern_analysis {.#None} caseT (` [(~+ values)]) next)) + _ (/type.check (monad.each check.monad check.forget! @ex_var+))] (in [(/pattern.variant [lefts right? testP]) nextA])) @@ -303,14 +306,16 @@ {.#UnivQ _} (do ///.monad - [[ex_id exT] (/type.check check.existential)] - (analyse_pattern num_tags - (maybe.trusted (type.applied (list exT) inputT')) - pattern - next)) + [[ex_id exT] (/type.check check.existential) + it (pattern_analysis num_tags + (maybe.trusted (type.applied (list exT) inputT')) + pattern + next) + _ (/type.check (monad.each check.monad check.forget! @ex_var+))] + (in it)) _ - (/.except ..cannot_match_with_pattern [inputT' pattern])))) + (/.except ..mismatch [inputT' pattern])))) (^ [location {.#Variant (list& [_ {.#Symbol tag}] values)}]) (/.with_location location @@ -319,10 +324,10 @@ [idx group variantT] (///extension.lifted (meta.tag tag)) _ (/type.check (check.check inputT variantT)) .let [[lefts right?] (/complex.choice (list.size group) idx)]] - (analyse_pattern {.#Some (list.size group)} inputT (` {(~ (code.nat lefts)) (~ (code.bit right?)) (~+ values)}) next))) + (pattern_analysis {.#Some (list.size group)} inputT (` {(~ (code.nat lefts)) (~ (code.bit right?)) (~+ values)}) next))) _ - (/.except ..not_a_pattern pattern) + (/.except ..invalid [pattern]) )) (def: .public (case analyse branches archive inputC) @@ -332,16 +337,16 @@ (do [! ///.monad] [[inputT inputA] (/type.inferring (analyse archive inputC)) - outputH (analyse_pattern {.#None} inputT patternH (analyse archive bodyH)) + outputH (pattern_analysis {.#None} inputT patternH (analyse archive bodyH)) outputT (monad.each ! (function (_ [patternT bodyT]) - (analyse_pattern {.#None} inputT patternT (analyse archive bodyT))) + (pattern_analysis {.#None} inputT patternT (analyse archive bodyT))) branchesT) outputHC (|> outputH product.left /coverage.coverage /.of_try) outputTC (monad.each ! (|>> product.left /coverage.coverage /.of_try) outputT) _ (.case (monad.mix try.monad /coverage.composite outputHC outputTC) {try.#Success coverage} - (///.assertion ..non_exhaustive_pattern_matching [inputC branches coverage] + (///.assertion ..non_exhaustive [inputC branches coverage] (/coverage.exhaustive? coverage)) {try.#Failure error} @@ -349,4 +354,4 @@ (in {/.#Case inputA [outputH outputT]})) {.#End} - (/.except ..cannot_have_empty_branches ""))) + (/.except ..empty_branches []))) 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 cce7b1f00..1bf6a48b9 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 @@ -286,12 +286,19 @@ ... records, so they must be normalized for further analysis. ... Normalization just means that all the tags get resolved to their ... canonical form (with their corresponding module identified). -(def: .public (normal record) - (-> (List Code) (Operation (Maybe (List [Symbol Code])))) +(def: .public (normal pattern_matching? record) + (-> Bit (List Code) (Operation (Maybe (List [Symbol Code])))) (loop [input record output (: (List [Symbol Code]) {.#End})] (case input + (^ (list& [_ {.#Symbol ["" slotH]}] valueH tail)) + (if pattern_matching? + (///#in {.#None}) + (do ///.monad + [slotH (///extension.lifted (meta.normal ["" slotH]))] + (again tail {.#Item [slotH valueH] output}))) + (^ (list& [_ {.#Symbol slotH}] valueH tail)) (do ///.monad [slotH (///extension.lifted (meta.normal slotH))] @@ -398,7 +405,7 @@ _ (do [! ///.monad] - [?members (normal members)] + [?members (..normal false members)] (case ?members {.#None} (..product analyse archive members) 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 2338824c4..540e38eb0 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 @@ -142,7 +142,9 @@ (getDeclaredField [java/lang/String] "try" java/lang/reflect/Field) (getConstructors [] [(java/lang/reflect/Constructor java/lang/Object)]) (getDeclaredMethods [] [java/lang/reflect/Method]) - (getDeclaredAnnotations [] [java/lang/annotation/Annotation])]) + (getDeclaredAnnotations [] [java/lang/annotation/Annotation]) + (getSuperclass [] "?" (java/lang/Class java/lang/Object)) + (getInterfaces [] [(java/lang/Class java/lang/Object)])]) (template [] [(exception: .public ( [class External @@ -456,15 +458,16 @@ (function (_ extension_name analyse archive args) (case args (^ (list arrayC)) - (do phase.monad - [_ (typeA.inference ..int) - [var_id varT] (typeA.check check.var) - arrayA (<| (typeA.expecting (.type (array.Array varT))) - (analyse archive arrayC)) - varT (typeA.check (check.clean (list) varT)) - arrayJT (jvm_array_type (.type (array.Array varT)))] - (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) - arrayA)})) + (<| typeA.with_var + (function (_ [@var :var:])) + (do phase.monad + [_ (typeA.inference ..int) + arrayA (<| (typeA.expecting (.type (array.Array :var:))) + (analyse archive arrayC)) + :var: (typeA.check (check.clean (list) :var:)) + arrayJT (jvm_array_type (.type (array.Array :var:)))] + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) + arrayA)}))) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -662,18 +665,19 @@ (function (_ extension_name analyse archive args) (case args (^ (list idxC arrayC)) - (do phase.monad - [[var_id varT] (typeA.check check.var) - _ (typeA.inference varT) - arrayA (<| (typeA.expecting (.type (array.Array varT))) - (analyse archive arrayC)) - varT (typeA.check (check.clean (list) varT)) - arrayJT (jvm_array_type (.type (array.Array varT))) - idxA (<| (typeA.expecting ..int) - (analyse archive idxC))] - (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) - idxA - arrayA)})) + (<| typeA.with_var + (function (_ [@var :var:])) + (do phase.monad + [_ (typeA.inference :var:) + arrayA (<| (typeA.expecting (.type (array.Array :var:))) + (analyse archive arrayC)) + :var: (typeA.check (check.clean (list) :var:)) + arrayJT (jvm_array_type (.type (array.Array :var:))) + idxA (<| (typeA.expecting ..int) + (analyse archive idxC))] + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) + idxA + arrayA)}))) _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) @@ -705,21 +709,22 @@ (function (_ extension_name analyse archive args) (case args (^ (list idxC valueC arrayC)) - (do phase.monad - [[var_id varT] (typeA.check check.var) - _ (typeA.inference (.type (array.Array varT))) - arrayA (<| (typeA.expecting (.type (array.Array varT))) - (analyse archive arrayC)) - varT (typeA.check (check.clean (list) varT)) - arrayJT (jvm_array_type (.type (array.Array varT))) - idxA (<| (typeA.expecting ..int) - (analyse archive idxC)) - valueA (<| (typeA.expecting varT) - (analyse archive valueC))] - (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) - idxA - valueA - arrayA)})) + (<| typeA.with_var + (function (_ [@var :var:])) + (do phase.monad + [_ (typeA.inference (.type (array.Array :var:))) + arrayA (<| (typeA.expecting (.type (array.Array :var:))) + (analyse archive arrayC)) + :var: (typeA.check (check.clean (list) :var:)) + arrayJT (jvm_array_type (.type (array.Array :var:))) + idxA (<| (typeA.expecting ..int) + (analyse archive idxC)) + valueA (<| (typeA.expecting :var:) + (analyse archive valueC))] + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) + idxA + valueA + arrayA)}))) _ (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)])))) @@ -1608,13 +1613,45 @@ (list (/////analysis.text argument) (value_analysis argumentJT)))) -(template [ ] +(def: (family_tree' it) + (-> (java/lang/Class java/lang/Object) + (List (java/lang/Class java/lang/Object))) + (let [interfaces (array.list {.#None} (java/lang/Class::getInterfaces it)) + supers (case (java/lang/Class::getSuperclass it) + {.#Some class} + (list& class interfaces) + + {.#None} + interfaces)] + (|> supers + (list#each family_tree') + list#conjoint + (list& it)))) + +(def: family_tree + (-> (java/lang/Class java/lang/Object) + (List (java/lang/Class java/lang/Object))) + (|>> ..family_tree' + ... De-duplication + (list#mix (function (_ class all) + (dictionary.has (java/lang/Class::getName class) class all)) + (dictionary.empty text.hash)) + dictionary.values)) + +(def: (all_declared_methods it) + (-> (java/lang/Class java/lang/Object) + (List java/lang/reflect/Method)) + (|> it + ..family_tree + (list#each (|>> java/lang/Class::getDeclaredMethods (array.list {.#None}))) + list#conjoint)) + +(template [ ] [(def: ( [type class]) (-> [(Type Class) (java/lang/Class java/lang/Object)] (Try (List [(Type Class) Text (Type Method)]))) (|> class - java/lang/Class::getDeclaredMethods - (array.list {.#None}) + (list.only (|>> java/lang/reflect/Method::getModifiers (predicate.or (|>> java/lang/reflect/Modifier::isPublic) (|>> java/lang/reflect/Modifier::isProtected)))) @@ -1640,8 +1677,10 @@ concrete_exceptions generic_exceptions)])]))))))] - [abstract_methods (list.only (|>> java/lang/reflect/Method::getModifiers java/lang/reflect/Modifier::isAbstract))] - [methods (<|)] + [abstract_methods (list.only (|>> java/lang/reflect/Method::getModifiers java/lang/reflect/Modifier::isAbstract)) + (<| (array.list {.#None}) java/lang/Class::getDeclaredMethods)] + [methods (<|) + ..all_declared_methods] ) (def: jvm_package_separator ".") @@ -2089,8 +2128,8 @@ [[_ exT] (typeA.check check.existential)] (in [var exT]))) vars)] - (in (list#mix (function (_ [varJ varT] mapping) - (dictionary.has (parser.name varJ) varT mapping)) + (in (list#mix (function (_ [varJ :var:] mapping) + (dictionary.has (parser.name varJ) :var: mapping)) mapping pairings)))) 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 4b4956d82..23a64f59c 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 @@ -4,7 +4,7 @@ [abstract ["[0]" monad {"+" do}]] [control - ["[0]" maybe] + ["[0]" maybe ("[1]#[0]" functor)] ["[0]" exception {"+" exception:}] ["<>" parser ["<[0]>" text] @@ -917,14 +917,24 @@ [//////synthesis.#Seq]) (^template [] - [(^ { _}) + [{ _} path]) ([//////synthesis.#Pop] [//////synthesis.#Bind] [//////synthesis.#Access]) - _ - (undefined)))) + {//////synthesis.#Bit_Fork when then else} + {//////synthesis.#Bit_Fork when (again then) (maybe#each again else)} + + (^template [] + [{ [[exampleH nextH] tail]} + { [[exampleH (again nextH)] + (list#each (function (_ [example next]) + [example (again next)]) + tail)]}]) + ([//////synthesis.#I64_Fork] + [//////synthesis.#F64_Fork] + [//////synthesis.#Text_Fork])))) (type: Mapping (Dictionary Synthesis Variable)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index ebe9f4e75..7449d550b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -174,7 +174,7 @@ (runtime: (lux::exec code globals) ($_ _.then - (_.exec code {.#Some globals}) + (_.exec {.#Some globals} code) (_.return ..unit))) (def: runtime::lux diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux index 67b7250c3..5843f0670 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -17,9 +17,6 @@ ["[0]" sequence] ["[0]" set {"+" Set}] ["[0]" list ("[1]#[0]" functor)]]]]] - [program - [compositor - ["[0]" static {"+" Static}]]] ["[0]" // {"+" Packager} [// ["[0]" archive {"+" Output} diff --git a/stdlib/source/library/lux/type/poly.lux b/stdlib/source/library/lux/type/poly.lux index 10070fc6a..f2cecab1e 100644 --- a/stdlib/source/library/lux/type/poly.lux +++ b/stdlib/source/library/lux/type/poly.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["[0]" meta] - ["[0]" type] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" maybe] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" type {"+" Env}] - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" dictionary]]] - [macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]] - [math - [number - ["n" nat]]]]]) + [library + [lux "*" + ["[0]" meta] + ["[0]" type] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" maybe] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" type {"+" Env}] + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" dictionary]]] + [macro {"+" with_symbols} + ["[0]" code] + [syntax {"+" syntax:}]] + [math + [number + ["n" nat]]]]]) (def: polyP (Parser [Code Text Code]) @@ -61,14 +61,14 @@ ([.#Var] [.#Ex]) {.#Parameter idx} - (let [idx (.adjusted_idx env idx)] + (let [idx (.argument env idx)] (if (n.= 0 idx) (|> (dictionary.value idx env) maybe.trusted product.left (code env)) (` (.$ (~ (code.nat (-- idx))))))) {.#Apply {.#Primitive "" {.#End}} {.#Parameter idx}} - (case (.adjusted_idx env idx) + (case (.argument env idx) 0 (|> env (dictionary.value 0) maybe.trusted product.left (code env)) idx (undefined)) -- cgit v1.2.3