diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/host.jvm.lux | 168 | ||||
-rw-r--r-- | stdlib/source/lux/target/jvm/type.lux | 58 | ||||
-rw-r--r-- | stdlib/source/lux/target/jvm/type/box.lux | 15 | ||||
-rw-r--r-- | stdlib/source/lux/target/jvm/type/reflection.lux | 48 | ||||
-rw-r--r-- | stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux | 204 |
5 files changed, 251 insertions, 242 deletions
diff --git a/stdlib/source/lux/host.jvm.lux b/stdlib/source/lux/host.jvm.lux index 9410972f8..e1735cf8e 100644 --- a/stdlib/source/lux/host.jvm.lux +++ b/stdlib/source/lux/host.jvm.lux @@ -27,30 +27,32 @@ ["." template]] [target ["." jvm #_ - ["#" type (#+ Primitive Var Bound Class Generic Type Argument Return Typed)]]]]) + ["#" type (#+ Primitive Var Bound Class Generic Type Argument Return Typed) + ["." box] + ["." reflection]]]]]) (template [<name> <class>] [(def: #export <name> .Type (#.Primitive <class> #.Nil))] ## Boxes - [Boolean jvm.boolean-box] - [Byte jvm.byte-box] - [Short jvm.short-box] - [Integer jvm.int-box] - [Long jvm.long-box] - [Float jvm.float-box] - [Double jvm.double-box] - [Character jvm.char-box] + [Boolean box.boolean] + [Byte box.byte] + [Short box.short] + [Integer box.int] + [Long box.long] + [Float box.float] + [Double box.double] + [Character box.char] ## Primitives - [boolean jvm.boolean-reflection] - [byte jvm.byte-reflection] - [short jvm.short-reflection] - [int jvm.int-reflection] - [long jvm.long-reflection] - [float jvm.float-reflection] - [double jvm.double-reflection] - [char jvm.char-reflection] + [boolean reflection.boolean] + [byte reflection.byte] + [short reflection.short] + [int reflection.int] + [long reflection.long] + [float reflection.float] + [double reflection.double] + [char reflection.char] ) (def: (get-static-field class field) @@ -68,26 +70,26 @@ (def: boxes (Dictionary Text Text) - (|> (list [jvm.boolean-descriptor jvm.boolean-box] - [jvm.byte-descriptor jvm.byte-box] - [jvm.short-descriptor jvm.short-box] - [jvm.int-descriptor jvm.int-box] - [jvm.long-descriptor jvm.long-box] - [jvm.float-descriptor jvm.float-box] - [jvm.double-descriptor jvm.double-box] - [jvm.char-descriptor jvm.char-box]) + (|> (list [jvm.boolean-descriptor box.boolean] + [jvm.byte-descriptor box.byte] + [jvm.short-descriptor box.short] + [jvm.int-descriptor box.int] + [jvm.long-descriptor box.long] + [jvm.float-descriptor box.float] + [jvm.double-descriptor box.double] + [jvm.char-descriptor box.char]) (dictionary.from-list text.hash))) (def: reflections (Dictionary Text Text) - (|> (list [jvm.boolean-descriptor jvm.boolean-reflection] - [jvm.byte-descriptor jvm.byte-reflection] - [jvm.short-descriptor jvm.short-reflection] - [jvm.int-descriptor jvm.int-reflection] - [jvm.long-descriptor jvm.long-reflection] - [jvm.float-descriptor jvm.float-reflection] - [jvm.double-descriptor jvm.double-reflection] - [jvm.char-descriptor jvm.char-reflection]) + (|> (list [jvm.boolean-descriptor reflection.boolean] + [jvm.byte-descriptor reflection.byte] + [jvm.short-descriptor reflection.short] + [jvm.int-descriptor reflection.int] + [jvm.long-descriptor reflection.long] + [jvm.float-descriptor reflection.float] + [jvm.double-descriptor reflection.double] + [jvm.char-descriptor reflection.char]) (dictionary.from-list text.hash))) (template [<name> <pre> <post>] @@ -608,14 +610,14 @@ (def: primitive^ (Parser Primitive) ($_ p.or - (s.identifier! ["" jvm.boolean-reflection]) - (s.identifier! ["" jvm.byte-reflection]) - (s.identifier! ["" jvm.short-reflection]) - (s.identifier! ["" jvm.int-reflection]) - (s.identifier! ["" jvm.long-reflection]) - (s.identifier! ["" jvm.float-reflection]) - (s.identifier! ["" jvm.double-reflection]) - (s.identifier! ["" jvm.char-reflection]) + (s.identifier! ["" reflection.boolean]) + (s.identifier! ["" reflection.byte]) + (s.identifier! ["" reflection.short]) + (s.identifier! ["" reflection.int]) + (s.identifier! ["" reflection.long]) + (s.identifier! ["" reflection.float]) + (s.identifier! ["" reflection.double]) + (s.identifier! ["" reflection.char]) )) (def: (type^ imports type-vars) @@ -1012,14 +1014,14 @@ (case type (#jvm.Primitive primitive) (case primitive - #jvm.Boolean (code.local-identifier jvm.boolean-reflection) - #jvm.Byte (code.local-identifier jvm.byte-reflection) - #jvm.Short (code.local-identifier jvm.short-reflection) - #jvm.Int (code.local-identifier jvm.int-reflection) - #jvm.Long (code.local-identifier jvm.long-reflection) - #jvm.Float (code.local-identifier jvm.float-reflection) - #jvm.Double (code.local-identifier jvm.double-reflection) - #jvm.Char (code.local-identifier jvm.char-reflection)) + #jvm.Boolean (code.local-identifier reflection.boolean) + #jvm.Byte (code.local-identifier reflection.byte) + #jvm.Short (code.local-identifier reflection.short) + #jvm.Int (code.local-identifier reflection.int) + #jvm.Long (code.local-identifier reflection.long) + #jvm.Float (code.local-identifier reflection.float) + #jvm.Double (code.local-identifier reflection.double) + #jvm.Char (code.local-identifier reflection.char)) (#jvm.Generic generic) (generic$ generic) @@ -1534,22 +1536,22 @@ (` (.|> (~ unboxed/boxed) (~+ post))))))] [#1 auto-convert-input ..unbox - [[jvm.boolean-descriptor jvm.boolean-descriptor (list (` (.: .Bit)) (` (.:coerce (.primitive (~ (code.text jvm.boolean-box)))))) []] - [jvm.byte-descriptor jvm.byte-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text jvm.long-box))))) (` ..long-to-byte)) []] - [jvm.short-descriptor jvm.short-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text jvm.long-box))))) (` ..long-to-short)) []] - [jvm.int-descriptor jvm.int-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text jvm.long-box))))) (` ..long-to-int)) []] - [jvm.long-descriptor jvm.long-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text jvm.long-box)))))) []] - [jvm.float-descriptor jvm.float-descriptor (list (` (.: .Frac)) (` (.:coerce (.primitive (~ (code.text jvm.double-box))))) (` ..double-to-float)) []] - [jvm.double-descriptor jvm.double-descriptor (list (` (.: .Frac)) (` (.:coerce (.primitive (~ (code.text jvm.double-box)))))) []] + [[jvm.boolean-descriptor jvm.boolean-descriptor (list (` (.: .Bit)) (` (.:coerce (.primitive (~ (code.text box.boolean)))))) []] + [jvm.byte-descriptor jvm.byte-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text box.long))))) (` ..long-to-byte)) []] + [jvm.short-descriptor jvm.short-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text box.long))))) (` ..long-to-short)) []] + [jvm.int-descriptor jvm.int-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text box.long))))) (` ..long-to-int)) []] + [jvm.long-descriptor jvm.long-descriptor (list (` (.: .Int)) (` (.:coerce (.primitive (~ (code.text box.long)))))) []] + [jvm.float-descriptor jvm.float-descriptor (list (` (.: .Frac)) (` (.:coerce (.primitive (~ (code.text box.double))))) (` ..double-to-float)) []] + [jvm.double-descriptor jvm.double-descriptor (list (` (.: .Frac)) (` (.:coerce (.primitive (~ (code.text box.double)))))) []] [..string-descriptor ..string-descriptor (list (` (.: .Text)) (` (.:coerce (.primitive (~ (code.text ..string-class)))))) []]]] [#0 auto-convert-output ..box - [[jvm.boolean-descriptor jvm.boolean-descriptor (list) [(` (.: (.primitive (~ (code.text jvm.boolean-box))))) (` (.:coerce .Bit))]] - [jvm.byte-descriptor jvm.long-descriptor (list (` "jvm conversion byte-to-long")) [(` (.: (.primitive (~ (code.text jvm.long-box))))) (` (.:coerce .Int))]] - [jvm.short-descriptor jvm.long-descriptor (list (` "jvm conversion short-to-long")) [(` (.: (.primitive (~ (code.text jvm.long-box))))) (` (.:coerce .Int))]] - [jvm.int-descriptor jvm.long-descriptor (list (` "jvm conversion int-to-long")) [(` (.: (.primitive (~ (code.text jvm.long-box))))) (` (.:coerce .Int))]] - [jvm.long-descriptor jvm.long-descriptor (list) [(` (.: (.primitive (~ (code.text jvm.long-box))))) (` (.:coerce .Int))]] - [jvm.float-descriptor jvm.double-descriptor (list (` "jvm conversion float-to-double")) [(` (.: (.primitive (~ (code.text jvm.double-box))))) (` (.:coerce .Frac))]] - [jvm.double-descriptor jvm.double-descriptor (list) [(` (.: (.primitive (~ (code.text jvm.double-box))))) (` (.:coerce .Frac))]] + [[jvm.boolean-descriptor jvm.boolean-descriptor (list) [(` (.: (.primitive (~ (code.text box.boolean))))) (` (.:coerce .Bit))]] + [jvm.byte-descriptor jvm.long-descriptor (list (` "jvm conversion byte-to-long")) [(` (.: (.primitive (~ (code.text box.long))))) (` (.:coerce .Int))]] + [jvm.short-descriptor jvm.long-descriptor (list (` "jvm conversion short-to-long")) [(` (.: (.primitive (~ (code.text box.long))))) (` (.:coerce .Int))]] + [jvm.int-descriptor jvm.long-descriptor (list (` "jvm conversion int-to-long")) [(` (.: (.primitive (~ (code.text box.long))))) (` (.:coerce .Int))]] + [jvm.long-descriptor jvm.long-descriptor (list) [(` (.: (.primitive (~ (code.text box.long))))) (` (.:coerce .Int))]] + [jvm.float-descriptor jvm.double-descriptor (list (` "jvm conversion float-to-double")) [(` (.: (.primitive (~ (code.text box.double))))) (` (.:coerce .Frac))]] + [jvm.double-descriptor jvm.double-descriptor (list) [(` (.: (.primitive (~ (code.text box.double))))) (` (.:coerce .Frac))]] [..string-descriptor ..string-descriptor (list) [(` (.: (.primitive (~ (code.text ..string-class))))) (` (.:coerce .Text))]]]] ) @@ -1810,7 +1812,7 @@ (array java/lang/Object 10))} (let [g!size (` (|> (~ size) (.: .Nat) - (.:coerce (.primitive (~ (code.text jvm.long-box)))) + (.:coerce (.primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))] (case type @@ -1872,7 +1874,7 @@ (wrap (list (` (.|> ((~ g!extension) (~ array)) "jvm conversion int-to-long" "jvm object cast" - (.: (.primitive (~ (code.text jvm.long-box)))) + (.: (.primitive (~ (code.text box.long)))) (.:coerce .Nat)))))) _ @@ -1890,7 +1892,7 @@ array-jvm-type (type->class-name array-type) #let [g!idx (` (.|> (~ idx) (.: .Nat) - (.:coerce (.primitive (~ (code.text jvm.long-box)))) + (.:coerce (.primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))]] (case array-jvm-type @@ -1899,14 +1901,14 @@ (wrap (list (` (.|> (<array-op> (~ g!idx) (~ array)) "jvm object cast" (.: (.primitive (~ (code.text <box>))))))))) - (["[Z" "jvm array read boolean" jvm.boolean-box] - ["[B" "jvm array read byte" jvm.byte-box] - ["[S" "jvm array read short" jvm.short-box] - ["[I" "jvm array read int" jvm.int-box] - ["[J" "jvm array read long" jvm.long-box] - ["[F" "jvm array read float" jvm.float-box] - ["[D" "jvm array read double" jvm.double-box] - ["[C" "jvm array read char" jvm.char-box]) + (["[Z" "jvm array read boolean" box.boolean] + ["[B" "jvm array read byte" box.byte] + ["[S" "jvm array read short" box.short] + ["[I" "jvm array read int" box.int] + ["[J" "jvm array read long" box.long] + ["[F" "jvm array read float" box.float] + ["[D" "jvm array read double" box.double] + ["[C" "jvm array read char" box.char]) _ (wrap (list (` ("jvm array read object" (~ g!idx) (~ array))))))) @@ -1926,7 +1928,7 @@ array-jvm-type (type->class-name array-type) #let [g!idx (` (.|> (~ idx) (.: .Nat) - (.:coerce (.primitive (~ (code.text jvm.long-box)))) + (.:coerce (.primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))]] (case array-jvm-type @@ -1936,14 +1938,14 @@ (.:coerce (.primitive (~ (code.text <box>)))) "jvm object cast"))] (wrap (list (` (<array-op> (~ g!idx) (~ g!value) (~ array))))))) - (["[Z" "jvm array write boolean" jvm.boolean-box] - ["[B" "jvm array write byte" jvm.byte-box] - ["[S" "jvm array write short" jvm.short-box] - ["[I" "jvm array write int" jvm.int-box] - ["[J" "jvm array write long" jvm.long-box] - ["[F" "jvm array write float" jvm.float-box] - ["[D" "jvm array write double" jvm.double-box] - ["[C" "jvm array write char" jvm.char-box]) + (["[Z" "jvm array write boolean" box.boolean] + ["[B" "jvm array write byte" box.byte] + ["[S" "jvm array write short" box.short] + ["[I" "jvm array write int" box.int] + ["[J" "jvm array write long" box.long] + ["[F" "jvm array write float" box.float] + ["[D" "jvm array write double" box.double] + ["[C" "jvm array write char" box.char]) _ (wrap (list (` ("jvm array write object" (~ g!idx) (~ value) (~ array))))))) diff --git a/stdlib/source/lux/target/jvm/type.lux b/stdlib/source/lux/target/jvm/type.lux index c6af8ffc5..4b62f33a7 100644 --- a/stdlib/source/lux/target/jvm/type.lux +++ b/stdlib/source/lux/target/jvm/type.lux @@ -25,33 +25,6 @@ ["C" char-descriptor] ) -(template [<name> <reflection>] - [(def: #export <name> <reflection>)] - - [void-reflection "void"] - [boolean-reflection "boolean"] - [byte-reflection "byte"] - [short-reflection "short"] - [int-reflection "int"] - [long-reflection "long"] - [float-reflection "float"] - [double-reflection "double"] - [char-reflection "char"] - ) - -(template [<name> <box>] - [(def: #export <name> <box>)] - - [boolean-box "java.lang.Boolean"] - [byte-box "java.lang.Byte"] - [short-box "java.lang.Short"] - [int-box "java.lang.Integer"] - [long-box "java.lang.Long"] - [float-box "java.lang.Float"] - [double-box "java.lang.Double"] - [char-box "java.lang.Character"] - ) - (def: #export array-prefix "[") (def: object-prefix "L") (def: var-prefix "T") @@ -340,34 +313,3 @@ (|> (get@ #exceptions method) (list@map (|>> #Generic signature (format "^"))) (text.join-with "")))) - -(def: #export (reflection-class type) - (-> Type Text) - (case type - (#Primitive prim) - (case prim - #Boolean ..boolean-reflection - #Byte ..byte-reflection - #Short ..short-reflection - #Int ..int-reflection - #Long ..long-reflection - #Float ..float-reflection - #Double ..double-reflection - #Char ..char-reflection) - - (#Array sub) - (syntax-name (descriptor type)) - - (#Generic generic) - (case generic - (#Class class params) - (syntax-name class) - - (^or (#Var name) - (#Wildcard #.None) - (#Wildcard (#.Some [#Lower bound]))) - ..object-class - - (#Wildcard (#.Some [#Upper bound])) - (reflection-class (#Generic bound))) - )) diff --git a/stdlib/source/lux/target/jvm/type/box.lux b/stdlib/source/lux/target/jvm/type/box.lux new file mode 100644 index 000000000..37f160458 --- /dev/null +++ b/stdlib/source/lux/target/jvm/type/box.lux @@ -0,0 +1,15 @@ +(.module: + [lux (#- int char)]) + +(template [<name> <box>] + [(def: #export <name> <box>)] + + [boolean "java.lang.Boolean"] + [byte "java.lang.Byte"] + [short "java.lang.Short"] + [int "java.lang.Integer"] + [long "java.lang.Long"] + [float "java.lang.Float"] + [double "java.lang.Double"] + [char "java.lang.Character"] + ) diff --git a/stdlib/source/lux/target/jvm/type/reflection.lux b/stdlib/source/lux/target/jvm/type/reflection.lux new file mode 100644 index 000000000..6526256b7 --- /dev/null +++ b/stdlib/source/lux/target/jvm/type/reflection.lux @@ -0,0 +1,48 @@ +(.module: + [lux (#- int char)] + ["." //]) + +(template [<name> <reflection>] + [(def: #export <name> <reflection>)] + + [void "void"] + [boolean "boolean"] + [byte "byte"] + [short "short"] + [int "int"] + [long "long"] + [float "float"] + [double "double"] + [char "char"] + ) + +(def: #export (class type) + (-> //.Type Text) + (case type + (#//.Primitive prim) + (case prim + #//.Boolean ..boolean + #//.Byte ..byte + #//.Short ..short + #//.Int ..int + #//.Long ..long + #//.Float ..float + #//.Double ..double + #//.Char ..char) + + (#//.Array sub) + (//.syntax-name (//.descriptor type)) + + (#//.Generic generic) + (case generic + (#//.Class class params) + (//.syntax-name class) + + (^or (#//.Var name) + (#//.Wildcard #.None) + (#//.Wildcard (#.Some [#//.Lower bound]))) + //.object-class + + (#//.Wildcard (#.Some [#//.Upper bound])) + (class (#//.Generic bound))) + )) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux index 358c666c7..01265c29a 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux @@ -24,7 +24,9 @@ ["." check (#+ Check) ("#@." monad)]] [target ["." jvm #_ - ["#" type (#+ Var Bound Primitive Generic Class Type Argument Return Typed)]]]] + ["#" type (#+ Var Bound Primitive Generic Class Type Argument Return Typed) + ["." box] + ["." reflection]]]]] ["." // #_ ["#." common] ["/#" // @@ -60,25 +62,25 @@ [(def: #export <name> .Type (#.Primitive <class> #.Nil))] ## Boxes - [Boolean jvm.boolean-box] - [Byte jvm.byte-box] - [Short jvm.short-box] - [Integer jvm.int-box] - [Long jvm.long-box] - [Float jvm.float-box] - [Double jvm.double-box] - [Character jvm.char-box] + [Boolean box.boolean] + [Byte box.byte] + [Short box.short] + [Integer box.int] + [Long box.long] + [Float box.float] + [Double box.double] + [Character box.char] [String "java.lang.String"] ## Primitives - [boolean jvm.boolean-reflection] - [byte jvm.byte-reflection] - [short jvm.short-reflection] - [int jvm.int-reflection] - [long jvm.long-reflection] - [float jvm.float-reflection] - [double jvm.double-reflection] - [char jvm.char-reflection] + [boolean reflection.boolean] + [byte reflection.byte] + [short reflection.short] + [int reflection.int] + [long reflection.long] + [float reflection.float] + [double reflection.double] + [char reflection.char] ) (type: Mapping @@ -322,8 +324,8 @@ (///bundle.install "ushr" (//common.binary <type> Integer <type>)) )))] - [bundle::int jvm.int-reflection ..long] - [bundle::long jvm.long-reflection ..long] + [bundle::int reflection.int ..long] + [bundle::long reflection.long ..long] ) (template [<name> <prefix> <type>] @@ -340,13 +342,13 @@ (///bundle.install "<" (//common.binary <type> <type> Bit)) )))] - [bundle::float jvm.float-reflection ..float] - [bundle::double jvm.double-reflection ..double] + [bundle::float reflection.float ..float] + [bundle::double reflection.double ..double] ) (def: bundle::char Bundle - (<| (///bundle.prefix jvm.char-reflection) + (<| (///bundle.prefix reflection.char) (|> ///bundle.empty (///bundle.install "=" (//common.binary ..char ..char Bit)) (///bundle.install "<" (//common.binary ..char ..char Bit)) @@ -354,14 +356,14 @@ (def: #export boxes (Dictionary Text Text) - (|> (list [jvm.boolean-reflection jvm.boolean-box] - [jvm.byte-reflection jvm.byte-box] - [jvm.short-reflection jvm.short-box] - [jvm.int-reflection jvm.int-box] - [jvm.long-reflection jvm.long-box] - [jvm.float-reflection jvm.float-box] - [jvm.double-reflection jvm.double-box] - [jvm.char-reflection jvm.char-box]) + (|> (list [reflection.boolean box.boolean] + [reflection.byte box.byte] + [reflection.short box.short] + [reflection.int box.int] + [reflection.long box.long] + [reflection.float box.float] + [reflection.double box.double] + [reflection.char box.char]) (dictionary.from-list text.hash))) (def: (array-type-info allow-primitives? arrayT) @@ -466,14 +468,14 @@ (case objectT (#.Primitive name #.Nil) (case name - (^ (static jvm.boolean-reflection)) (////@wrap jvm.boolean) - (^ (static jvm.byte-reflection)) (////@wrap jvm.byte) - (^ (static jvm.short-reflection)) (////@wrap jvm.short) - (^ (static jvm.int-reflection)) (////@wrap jvm.int) - (^ (static jvm.long-reflection)) (////@wrap jvm.long) - (^ (static jvm.float-reflection)) (////@wrap jvm.float) - (^ (static jvm.double-reflection)) (////@wrap jvm.double) - (^ (static jvm.char-reflection)) (////@wrap jvm.char) + (^ (static reflection.boolean)) (////@wrap jvm.boolean) + (^ (static reflection.byte)) (////@wrap jvm.byte) + (^ (static reflection.short)) (////@wrap jvm.short) + (^ (static reflection.int)) (////@wrap jvm.int) + (^ (static reflection.long)) (////@wrap jvm.long) + (^ (static reflection.float)) (////@wrap jvm.float) + (^ (static reflection.double)) (////@wrap jvm.double) + (^ (static reflection.char)) (////@wrap jvm.char) _ (if (text.starts-with? jvm.array-prefix name) (////.lift (<t>.run jvm.parse-signature name)) (////@wrap (jvm.class name (list))))) @@ -526,7 +528,7 @@ (def: (check-object objectT) (-> .Type (Operation Text)) (do ////.monad - [name (:: @ map jvm.reflection-class (check-jvm objectT))] + [name (:: @ map reflection.class (check-jvm objectT))] (if (dictionary.contains? name ..boxes) (/////analysis.throw ..primitives-are-not-objects [name]) (////@wrap name)))) @@ -629,47 +631,47 @@ (|> ///bundle.empty (dictionary.merge (<| (///bundle.prefix "length") (|> ///bundle.empty - (///bundle.install jvm.boolean-reflection (primitive-array-length-handler jvm.boolean)) - (///bundle.install jvm.byte-reflection (primitive-array-length-handler jvm.byte)) - (///bundle.install jvm.short-reflection (primitive-array-length-handler jvm.short)) - (///bundle.install jvm.int-reflection (primitive-array-length-handler jvm.int)) - (///bundle.install jvm.long-reflection (primitive-array-length-handler jvm.long)) - (///bundle.install jvm.float-reflection (primitive-array-length-handler jvm.float)) - (///bundle.install jvm.double-reflection (primitive-array-length-handler jvm.double)) - (///bundle.install jvm.char-reflection (primitive-array-length-handler jvm.char)) + (///bundle.install reflection.boolean (primitive-array-length-handler jvm.boolean)) + (///bundle.install reflection.byte (primitive-array-length-handler jvm.byte)) + (///bundle.install reflection.short (primitive-array-length-handler jvm.short)) + (///bundle.install reflection.int (primitive-array-length-handler jvm.int)) + (///bundle.install reflection.long (primitive-array-length-handler jvm.long)) + (///bundle.install reflection.float (primitive-array-length-handler jvm.float)) + (///bundle.install reflection.double (primitive-array-length-handler jvm.double)) + (///bundle.install reflection.char (primitive-array-length-handler jvm.char)) (///bundle.install "object" array::length::object)))) (dictionary.merge (<| (///bundle.prefix "new") (|> ///bundle.empty - (///bundle.install jvm.boolean-reflection (new-primitive-array-handler jvm.boolean)) - (///bundle.install jvm.byte-reflection (new-primitive-array-handler jvm.byte)) - (///bundle.install jvm.short-reflection (new-primitive-array-handler jvm.short)) - (///bundle.install jvm.int-reflection (new-primitive-array-handler jvm.int)) - (///bundle.install jvm.long-reflection (new-primitive-array-handler jvm.long)) - (///bundle.install jvm.float-reflection (new-primitive-array-handler jvm.float)) - (///bundle.install jvm.double-reflection (new-primitive-array-handler jvm.double)) - (///bundle.install jvm.char-reflection (new-primitive-array-handler jvm.char)) + (///bundle.install reflection.boolean (new-primitive-array-handler jvm.boolean)) + (///bundle.install reflection.byte (new-primitive-array-handler jvm.byte)) + (///bundle.install reflection.short (new-primitive-array-handler jvm.short)) + (///bundle.install reflection.int (new-primitive-array-handler jvm.int)) + (///bundle.install reflection.long (new-primitive-array-handler jvm.long)) + (///bundle.install reflection.float (new-primitive-array-handler jvm.float)) + (///bundle.install reflection.double (new-primitive-array-handler jvm.double)) + (///bundle.install reflection.char (new-primitive-array-handler jvm.char)) (///bundle.install "object" array::new::object)))) (dictionary.merge (<| (///bundle.prefix "read") (|> ///bundle.empty - (///bundle.install jvm.boolean-reflection (read-primitive-array-handler ..boolean jvm.boolean)) - (///bundle.install jvm.byte-reflection (read-primitive-array-handler ..byte jvm.byte)) - (///bundle.install jvm.short-reflection (read-primitive-array-handler ..short jvm.short)) - (///bundle.install jvm.int-reflection (read-primitive-array-handler ..int jvm.int)) - (///bundle.install jvm.long-reflection (read-primitive-array-handler ..long jvm.long)) - (///bundle.install jvm.float-reflection (read-primitive-array-handler ..float jvm.float)) - (///bundle.install jvm.double-reflection (read-primitive-array-handler ..double jvm.double)) - (///bundle.install jvm.char-reflection (read-primitive-array-handler ..char jvm.char)) + (///bundle.install reflection.boolean (read-primitive-array-handler ..boolean jvm.boolean)) + (///bundle.install reflection.byte (read-primitive-array-handler ..byte jvm.byte)) + (///bundle.install reflection.short (read-primitive-array-handler ..short jvm.short)) + (///bundle.install reflection.int (read-primitive-array-handler ..int jvm.int)) + (///bundle.install reflection.long (read-primitive-array-handler ..long jvm.long)) + (///bundle.install reflection.float (read-primitive-array-handler ..float jvm.float)) + (///bundle.install reflection.double (read-primitive-array-handler ..double jvm.double)) + (///bundle.install reflection.char (read-primitive-array-handler ..char jvm.char)) (///bundle.install "object" array::read::object)))) (dictionary.merge (<| (///bundle.prefix "write") (|> ///bundle.empty - (///bundle.install jvm.boolean-reflection (write-primitive-array-handler ..boolean jvm.boolean)) - (///bundle.install jvm.byte-reflection (write-primitive-array-handler ..byte jvm.byte)) - (///bundle.install jvm.short-reflection (write-primitive-array-handler ..short jvm.short)) - (///bundle.install jvm.int-reflection (write-primitive-array-handler ..int jvm.int)) - (///bundle.install jvm.long-reflection (write-primitive-array-handler ..long jvm.long)) - (///bundle.install jvm.float-reflection (write-primitive-array-handler ..float jvm.float)) - (///bundle.install jvm.double-reflection (write-primitive-array-handler ..double jvm.double)) - (///bundle.install jvm.char-reflection (write-primitive-array-handler ..char jvm.char)) + (///bundle.install reflection.boolean (write-primitive-array-handler ..boolean jvm.boolean)) + (///bundle.install reflection.byte (write-primitive-array-handler ..byte jvm.byte)) + (///bundle.install reflection.short (write-primitive-array-handler ..short jvm.short)) + (///bundle.install reflection.int (write-primitive-array-handler ..int jvm.int)) + (///bundle.install reflection.long (write-primitive-array-handler ..long jvm.long)) + (///bundle.install reflection.float (write-primitive-array-handler ..float jvm.float)) + (///bundle.install reflection.double (write-primitive-array-handler ..double jvm.double)) + (///bundle.install reflection.char (write-primitive-array-handler ..char jvm.char)) (///bundle.install "object" array::write::object)))) ))) @@ -900,7 +902,7 @@ (case (array.size (java/lang/Class::getTypeParameters java-type)) 0 (case class-name - (^ (static jvm.void-reflection)) + (^ (static reflection.void)) (////@wrap Any) _ @@ -1009,7 +1011,7 @@ (monad.map ////.monad (function (_ superT) (do ////.monad - [super-name (:: @ map jvm.reflection-class (check-jvm superT)) + [super-name (:: @ map reflection.class (check-jvm superT)) super-class (load-class super-name)] (wrap [[super-name superT] (java/lang/Class::isAssignableFrom super-class to-class)]))) @@ -1025,10 +1027,10 @@ (^ (list fromC)) (do ////.monad [toT (///.lift macro.expected-type) - to-name (:: @ map jvm.reflection-class (check-jvm toT)) + to-name (:: @ map reflection.class (check-jvm toT)) [fromT fromA] (typeA.with-inference (analyse fromC)) - from-name (:: @ map jvm.reflection-class (check-jvm fromT)) + from-name (:: @ map reflection.class (check-jvm fromT)) can-cast? (: (Operation Bit) (case [from-name to-name] (^template [<primitive> <object>] @@ -1036,14 +1038,14 @@ (^ [(static <object>) (static <primitive>)]) (^ [(static <primitive>) (static <primitive>)])) (wrap #1)) - ([jvm.boolean-reflection jvm.boolean-box] - [jvm.byte-reflection jvm.byte-box] - [jvm.short-reflection jvm.short-box] - [jvm.int-reflection jvm.int-box] - [jvm.long-reflection jvm.long-box] - [jvm.float-reflection jvm.float-box] - [jvm.double-reflection jvm.double-box] - [jvm.char-reflection jvm.char-box]) + ([reflection.boolean box.boolean] + [reflection.byte box.byte] + [reflection.short box.short] + [reflection.int box.int] + [reflection.long box.long] + [reflection.float box.float] + [reflection.double box.double] + [reflection.char box.char]) _ (do @ @@ -1281,7 +1283,7 @@ (def: reflection-arguments (-> (List Text) (Operation (List Text))) (|>> (monad.map error.monad (<t>.run jvm.parse-signature)) - (:: error.monad map (list@map jvm.reflection-class)) + (:: error.monad map (list@map reflection.class)) ////.lift)) (def: (check-method class method-name method-style arg-classes method) @@ -1629,14 +1631,14 @@ (def: primitive (Parser Primitive) ($_ p.or - (s.identifier! ["" jvm.boolean-reflection]) - (s.identifier! ["" jvm.byte-reflection]) - (s.identifier! ["" jvm.short-reflection]) - (s.identifier! ["" jvm.int-reflection]) - (s.identifier! ["" jvm.long-reflection]) - (s.identifier! ["" jvm.float-reflection]) - (s.identifier! ["" jvm.double-reflection]) - (s.identifier! ["" jvm.char-reflection]) + (s.identifier! ["" reflection.boolean]) + (s.identifier! ["" reflection.byte]) + (s.identifier! ["" reflection.short]) + (s.identifier! ["" reflection.int]) + (s.identifier! ["" reflection.long]) + (s.identifier! ["" reflection.float]) + (s.identifier! ["" reflection.double]) + (s.identifier! ["" reflection.char]) )) (def: type @@ -1672,7 +1674,7 @@ (def: return (Parser Return) - (p.or (s.identifier! ["" jvm.void-reflection]) + (p.or (s.identifier! ["" reflection.void]) ..type)) (type: #export (Overriden-Method a) @@ -1754,14 +1756,14 @@ (case type (#jvm.Primitive primitive) (case primitive - #jvm.Boolean (/////analysis.constant ["" jvm.boolean-reflection]) - #jvm.Byte (/////analysis.constant ["" jvm.byte-reflection]) - #jvm.Short (/////analysis.constant ["" jvm.short-reflection]) - #jvm.Int (/////analysis.constant ["" jvm.int-reflection]) - #jvm.Long (/////analysis.constant ["" jvm.long-reflection]) - #jvm.Float (/////analysis.constant ["" jvm.float-reflection]) - #jvm.Double (/////analysis.constant ["" jvm.double-reflection]) - #jvm.Char (/////analysis.constant ["" jvm.char-reflection])) + #jvm.Boolean (/////analysis.constant ["" reflection.boolean]) + #jvm.Byte (/////analysis.constant ["" reflection.byte]) + #jvm.Short (/////analysis.constant ["" reflection.short]) + #jvm.Int (/////analysis.constant ["" reflection.int]) + #jvm.Long (/////analysis.constant ["" reflection.long]) + #jvm.Float (/////analysis.constant ["" reflection.float]) + #jvm.Double (/////analysis.constant ["" reflection.double]) + #jvm.Char (/////analysis.constant ["" reflection.char])) (#jvm.Generic generic) (generic-analysis generic) |