aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/ffi.jvm.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/ffi.jvm.lux')
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux387
1 files changed, 146 insertions, 241 deletions
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index a93701270..a1d5abe96 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -1,12 +1,10 @@
(.using
[library
- ["[0]" lux {"-" Primitive Type type int char :as function}
+ [lux {"-" Primitive Type type int char :as}
["[0]" meta]
[abstract
- ["[0]" monad {"+" Monad do}]
- ["[0]" enum]]
+ ["[0]" monad {"+" do}]]
[control
- ["[0]" function]
["[0]" io]
["[0]" maybe]
["[0]" try {"+" Try}]
@@ -26,17 +24,17 @@
["[0]" code]
["[0]" template]]
[target
- [jvm
+ ["[0]" jvm "_"
[encoding
["[0]" name {"+" External}]]
- ["[0]" type {"+" Type Argument Typed}
+ ["[1]" type {"+" Type Argument Typed}
["[0]" category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}]
["[0]" box]
["[0]" descriptor]
["[0]" signature]
["[0]" reflection]
["[0]" parser]]]]
- ["[1]_[0]" type ("[1]#[0]" equivalence)
+ ["[0]" type ("[1]#[0]" equivalence)
["[0]" check]]]])
(def: internal
@@ -47,12 +45,12 @@
(def: signature
(All (_ category)
(-> (Type category) Text))
- (|>> type.signature signature.signature))
+ (|>> jvm.signature signature.signature))
(def: reflection
(All (_ category)
(-> (Type (<| Return' Value' category)) Text))
- (|>> type.reflection reflection.reflection))
+ (|>> jvm.reflection reflection.reflection))
(template [<name> <class>]
[(`` (def: .public <name>
@@ -101,15 +99,15 @@
(def: boxes
(Dictionary (Type Value) Text)
- (|> (list [type.boolean box.boolean]
- [type.byte box.byte]
- [type.short box.short]
- [type.int box.int]
- [type.long box.long]
- [type.float box.float]
- [type.double box.double]
- [type.char box.char])
- (dictionary.of_list type.hash)))
+ (|> (list [jvm.boolean box.boolean]
+ [jvm.byte box.byte]
+ [jvm.short box.short]
+ [jvm.int box.int]
+ [jvm.long box.long]
+ [jvm.float box.float]
+ [jvm.double box.double]
+ [jvm.char box.char])
+ (dictionary.of_list jvm.hash)))
(template [<name> <pre> <post>]
[(def: (<name> unboxed boxed raw)
@@ -329,32 +327,32 @@
(-> Primitive_Mode (Type Primitive) Code)
(case mode
{#ManualPrM}
- (cond (# type.equivalence = type.boolean type) (` ..Boolean)
- (# type.equivalence = type.byte type) (` ..Byte)
- (# type.equivalence = type.short type) (` ..Short)
- (# type.equivalence = type.int type) (` ..Integer)
- (# type.equivalence = type.long type) (` ..Long)
- (# type.equivalence = type.float type) (` ..Float)
- (# type.equivalence = type.double type) (` ..Double)
- (# type.equivalence = type.char type) (` ..Character)
+ (cond (# jvm.equivalence = jvm.boolean type) (` ..Boolean)
+ (# jvm.equivalence = jvm.byte type) (` ..Byte)
+ (# jvm.equivalence = jvm.short type) (` ..Short)
+ (# jvm.equivalence = jvm.int type) (` ..Integer)
+ (# jvm.equivalence = jvm.long type) (` ..Long)
+ (# jvm.equivalence = jvm.float type) (` ..Float)
+ (# jvm.equivalence = jvm.double type) (` ..Double)
+ (# jvm.equivalence = jvm.char type) (` ..Character)
... else
(undefined))
{#AutoPrM}
- (cond (# type.equivalence = type.boolean type)
+ (cond (# jvm.equivalence = jvm.boolean type)
(` .Bit)
- (or (# type.equivalence = type.short type)
- (# type.equivalence = type.byte type)
- (# type.equivalence = type.int type)
- (# type.equivalence = type.long type))
+ (or (# jvm.equivalence = jvm.short type)
+ (# jvm.equivalence = jvm.byte type)
+ (# jvm.equivalence = jvm.int type)
+ (# jvm.equivalence = jvm.long type))
(` .Int)
- (or (# type.equivalence = type.float type)
- (# type.equivalence = type.double type))
+ (or (# jvm.equivalence = jvm.float type)
+ (# jvm.equivalence = jvm.double type))
(` .Frac)
- (# type.equivalence = type.char type)
+ (# jvm.equivalence = jvm.char type)
(` .Nat)
... else
@@ -380,7 +378,7 @@
[parser.array? elementT
(case (parser.primitive? elementT)
{.#Some elementT}
- (` {.#Primitive (~ (code.text (..reflection (type.array elementT)))) {.#End}})
+ (` {.#Primitive (~ (code.text (..reflection (jvm.array elementT)))) {.#End}})
{.#None}
(` {.#Primitive (~ (code.text array.type_name))
@@ -587,7 +585,7 @@
($_ <>.either
(<>.and class_name^ (<>#in (list)))
(<code>.form (<>.and class_name^ (<>.some (parameter^ type_vars))))))]
- (in (type.class (name.safe name) parameters))))
+ (in (jvm.class (name.safe name) parameters))))
(exception: .public (unknown_type_variable [name Text
type_vars (List (Type Var))])
@@ -601,13 +599,13 @@
[name <code>.local_symbol
_ (..assertion ..unknown_type_variable [name options]
(list.member? text.equivalence (list#each parser.name options) name))]
- (in (type.var name))))
+ (in (jvm.var name))))
(def: wildcard^
(Parser (Type Parameter))
(do <>.monad
[_ (<code>.this! (' ?))]
- (in type.wildcard)))
+ (in jvm.wildcard)))
(template [<name> <comparison> <constructor>]
[(def: <name>
@@ -617,14 +615,14 @@
<code>.tuple
(# <>.monad each <constructor>)))]
- [upper^ < type.upper]
- [lower^ > type.lower]
+ [upper^ < jvm.upper]
+ [lower^ > jvm.lower]
)
(def: (parameter^ type_vars)
(-> (List (Type Var)) (Parser (Type Parameter)))
(<>.rec
- (.function (_ _)
+ (function (_ _)
(let [class^ (..class^' parameter^ type_vars)]
($_ <>.either
(..type_variable type_vars)
@@ -645,25 +643,25 @@
(def: primitive^
(Parser (Type Primitive))
($_ <>.either
- (itself^ type.boolean)
- (itself^ type.byte)
- (itself^ type.short)
- (itself^ type.int)
- (itself^ type.long)
- (itself^ type.float)
- (itself^ type.double)
- (itself^ type.char)
+ (itself^ jvm.boolean)
+ (itself^ jvm.byte)
+ (itself^ jvm.short)
+ (itself^ jvm.int)
+ (itself^ jvm.long)
+ (itself^ jvm.float)
+ (itself^ jvm.double)
+ (itself^ jvm.char)
))
(def: array^
(-> (Parser (Type Value)) (Parser (Type Array)))
(|>> <code>.tuple
- (# <>.monad each type.array)))
+ (# <>.monad each jvm.array)))
(def: (type^ type_vars)
(-> (List (Type Var)) (Parser (Type Value)))
(<>.rec
- (.function (_ type^)
+ (function (_ type^)
($_ <>.either
..primitive^
(..parameter^ type_vars)
@@ -674,7 +672,7 @@
(Parser (Type Void))
(do <>.monad
[_ (<code>.symbol! ["" (reflection.reflection reflection.void)])]
- (in type.void)))
+ (in jvm.void)))
(def: (return^ type_vars)
(-> (List (Type Var)) (Parser (Type Return)))
@@ -683,7 +681,7 @@
(def: var^
(Parser (Type Var))
- (# <>.monad each type.var <code>.local_symbol))
+ (# <>.monad each jvm.var <code>.local_symbol))
(def: vars^
(Parser (List (Type Var)))
@@ -698,7 +696,7 @@
(<code>.form (<>.and (..valid_class_name (list))
(<>.some var^)))
))]
- (in (type.declaration name variables))))
+ (in (jvm.declaration name variables))))
(def: (class^ type_vars)
(-> (List (Type Var)) (Parser (Type Class)))
@@ -1203,7 +1201,7 @@
(def: $Object
(Type Class)
- (type.class "java.lang.Object" (list)))
+ (jvm.class "java.lang.Object" (list)))
(syntax: .public (class: [.let [! <>.monad]
im inheritance_modifier^
@@ -1222,7 +1220,7 @@
(list#each (method->parser class_vars fully_qualified_class_name))
(list#mix <>.either (<>.failure ""))))]]
(in (list (` ("jvm class"
- (~ (declaration$ (type.declaration full_class_name class_vars)))
+ (~ (declaration$ (jvm.declaration full_class_name class_vars)))
(~ (class$ super))
[(~+ (list#each class$ interfaces))]
(~ (inheritance_modifier$ im))
@@ -1237,7 +1235,7 @@
annotations ..annotations^
members (<>.some (..method_decl^ class_vars))])
(in (list (` ("jvm class interface"
- (~ (declaration$ (type.declaration full_class_name class_vars)))
+ (~ (declaration$ (jvm.declaration full_class_name class_vars)))
[(~+ (list#each class$ supers))]
[(~+ (list#each annotation$ annotations))]
(~+ (list#each method_decl$ members)))))))
@@ -1297,7 +1295,7 @@
{.#None}
(in (list (` (: (-> (.Primitive "java.lang.Object") (~ check_type))
- (.function ((~ g!_) (~ g!unchecked))
+ (function ((~ g!_) (~ g!unchecked))
(~ check_code))))))
))))
@@ -1349,13 +1347,13 @@
(do [! meta.monad]
[arg_inputs (monad.each !
(: (-> [Bit (Type Value)] (Meta [Bit Code]))
- (.function (_ [maybe? _])
+ (function (_ [maybe? _])
(with_symbols [arg_name]
(in [maybe? arg_name]))))
#import_member_args)
.let [input_jvm_types (list#each product.right #import_member_args)
arg_types (list#each (: (-> [Bit (Type Value)] Code)
- (.function (_ [maybe? arg])
+ (function (_ [maybe? arg])
(let [arg_type (value_type (value@ #import_member_mode commons) arg)]
(if maybe?
(` (Maybe (~ arg_type)))
@@ -1415,7 +1413,7 @@
{#AutoPrM}
(with_expansions [<special+>' (template.spliced <special+>)
<cond_cases> (template [<primitive> <pre> <post>]
- [(# type.equivalence = <primitive> unboxed)
+ [(# jvm.equivalence = <primitive> unboxed)
(with_expansions [<post>' (template.spliced <post>)]
[<primitive>
(` (.|> (~ raw) (~+ <pre>)))
@@ -1443,23 +1441,23 @@
(` (.|> (~ unboxed/boxed) (~+ post))))))]
[#1 with_automatic_input_conversion ..unbox
- [[type.boolean (list (` (.:as (.Primitive (~ (code.text box.boolean)))))) []]
- [type.byte (list (` (.:as (.Primitive (~ (code.text box.byte)))))) []]
- [type.short (list (` (.:as (.Primitive (~ (code.text box.short)))))) []]
- [type.int (list (` (.: (.Primitive (~ (code.text box.int)))))) []]
- [type.long (list (` (.:as (.Primitive (~ (code.text box.long)))))) []]
- [type.char (list (` (.:as (.Primitive (~ (code.text box.char)))))) []]
- [type.float (list (` (.:as (.Primitive (~ (code.text box.float)))))) []]
- [type.double (list (` (.:as (.Primitive (~ (code.text box.double)))))) []]]]
+ [[jvm.boolean (list (` (.:as (.Primitive (~ (code.text box.boolean)))))) []]
+ [jvm.byte (list (` (.:as (.Primitive (~ (code.text box.byte)))))) []]
+ [jvm.short (list (` (.:as (.Primitive (~ (code.text box.short)))))) []]
+ [jvm.int (list (` (.: (.Primitive (~ (code.text box.int)))))) []]
+ [jvm.long (list (` (.:as (.Primitive (~ (code.text box.long)))))) []]
+ [jvm.char (list (` (.:as (.Primitive (~ (code.text box.char)))))) []]
+ [jvm.float (list (` (.:as (.Primitive (~ (code.text box.float)))))) []]
+ [jvm.double (list (` (.:as (.Primitive (~ (code.text box.double)))))) []]]]
[#0 with_automatic_output_conversion ..box
- [[type.boolean (list) [(` (.: (.Primitive (~ (code.text box.boolean)))))]]
- [type.byte (list) [(` (.: (.Primitive (~ (code.text box.byte)))))]]
- [type.short (list) [(` (.: (.Primitive (~ (code.text box.short)))))]]
- [type.int (list) [(` (.: (.Primitive (~ (code.text box.int)))))]]
- [type.long (list) [(` (.: (.Primitive (~ (code.text box.long)))))]]
- [type.char (list) [(` (.: (.Primitive (~ (code.text box.char)))))]]
- [type.float (list) [(` (.: (.Primitive (~ (code.text box.float)))))]]
- [type.double (list) [(` (.: (.Primitive (~ (code.text box.double)))))]]]]
+ [[jvm.boolean (list) [(` (.: (.Primitive (~ (code.text box.boolean)))))]]
+ [jvm.byte (list) [(` (.: (.Primitive (~ (code.text box.byte)))))]]
+ [jvm.short (list) [(` (.: (.Primitive (~ (code.text box.short)))))]]
+ [jvm.int (list) [(` (.: (.Primitive (~ (code.text box.int)))))]]
+ [jvm.long (list) [(` (.: (.Primitive (~ (code.text box.long)))))]]
+ [jvm.char (list) [(` (.: (.Primitive (~ (code.text box.char)))))]]
+ [jvm.float (list) [(` (.: (.Primitive (~ (code.text box.float)))))]]
+ [jvm.double (list) [(` (.: (.Primitive (~ (code.text box.double)))))]]]]
)
(def: (un_quoted quoted)
@@ -1470,7 +1468,7 @@
(-> Primitive_Mode (List (Type Value)) (List [Bit Code]) (List Code))
(|> inputs
(list.zipped/2 classes)
- (list#each (.function (_ [class [maybe? input]])
+ (list#each (function (_ [class [maybe? input]])
(|> (if maybe?
(` (: (.Primitive (~ (code.text (..reflection class))))
((~! !!!) (~ (..un_quoted input)))))
@@ -1486,7 +1484,7 @@
(def: syntax_inputs
(-> (List Code) (List Code))
- (|>> (list#each (.function (_ name)
+ (|>> (list#each (function (_ name)
(list name (` (~! <code>.any)))))
list#conjoint))
@@ -1507,7 +1505,7 @@
(` (All ((~ g!_) (~+ =class_tvars))
(.Primitive (~ (code.text full_name)) [(~+ =class_tvars)]))))))
getter_interop (: (-> Text Code)
- (.function (_ name)
+ (function (_ name)
(let [getter_name (code.symbol ["" (..import_name import_format method_prefix name)])]
(` (def: (~ getter_name)
(~ enum_type)
@@ -1516,7 +1514,7 @@
{#ConstructorDecl [commons _]}
(do meta.monad
- [.let [classT (type.class full_name (list))
+ [.let [classT (jvm.class full_name (list))
def_name (code.symbol ["" (..import_name import_format method_prefix (value@ #import_member_alias commons))])
jvm_interop (|> [classT
(` ("jvm member invoke constructor"
@@ -1564,13 +1562,13 @@
[(~+ (list#each ..var$ (value@ #import_member_tvars commons)))]
(~+ (|> object_ast
(list#each ..un_quoted)
- (list.zipped/2 (list (type.class full_name (list))))
+ (list.zipped/2 (list (jvm.class full_name (list))))
(list#each (with_automatic_input_conversion (value@ #import_member_mode commons)))))
(~+ (|> (jvm_invoke_inputs (value@ #import_member_mode commons) input_jvm_types arg_function_inputs)
(list.zipped/2 input_jvm_types)
(list#each ..decorate_input))))))
jvm_interop (: Code
- (case (type.void? method_return)
+ (case (jvm.void? method_return)
{.#Left method_return}
(|> [method_return
callC]
@@ -1674,7 +1672,7 @@
(do [! meta.monad]
[kind (class_kind declaration)
=members (|> bundles
- (list#each (.function (_ [import_format members])
+ (list#each (function (_ [import_format members])
(list#each (|>> [import_format]) members)))
list.together
(monad.each ! (member_import$ class_type_vars kind declaration)))]
@@ -1688,19 +1686,19 @@
"jvm object cast"
"jvm conversion long-to-int"))]
(`` (cond (~~ (template [<primitive> <array_op>]
- [(# type.equivalence = <primitive> type)
+ [(# jvm.equivalence = <primitive> type)
(in (list (` (<array_op> (~ g!size)))))]
- [type.boolean "jvm array new boolean"]
- [type.byte "jvm array new byte"]
- [type.short "jvm array new short"]
- [type.int "jvm array new int"]
- [type.long "jvm array new long"]
- [type.float "jvm array new float"]
- [type.double "jvm array new double"]
- [type.char "jvm array new char"]))
+ [jvm.boolean "jvm array new boolean"]
+ [jvm.byte "jvm array new byte"]
+ [jvm.short "jvm array new short"]
+ [jvm.int "jvm array new int"]
+ [jvm.long "jvm array new long"]
+ [jvm.float "jvm array new float"]
+ [jvm.double "jvm array new double"]
+ [jvm.char "jvm array new char"]))
... else
- (in (list (` (: (~ (value_type {#ManualPrM} (type.array type)))
+ (in (list (` (: (~ (value_type {#ManualPrM} (jvm.array type)))
("jvm array new object" (~ g!size))))))))))
(exception: .public (cannot_convert_to_jvm_type [type .Type])
@@ -1710,7 +1708,7 @@
(with_expansions [<failure> (as_is (meta.failure (exception.error ..cannot_convert_to_jvm_type [type])))]
(def: (lux_type->jvm_type context type)
(-> Type_Context .Type (Meta (Type Value)))
- (if (lux_type#= .Any type)
+ (if (type#= .Any type)
(# meta.monad in $Object)
(case type
{.#Primitive name params}
@@ -1723,37 +1721,37 @@
_
<failure>)]
- [type.boolean]
- [type.byte]
- [type.short]
- [type.int]
- [type.long]
- [type.float]
- [type.double]
- [type.char]))
+ [jvm.boolean]
+ [jvm.byte]
+ [jvm.short]
+ [jvm.int]
+ [jvm.long]
+ [jvm.float]
+ [jvm.double]
+ [jvm.char]))
(~~ (template [<type>]
- [(text#= (..reflection (type.array <type>)) name)
+ [(text#= (..reflection (jvm.array <type>)) name)
(case params
{.#End}
- (# meta.monad in (type.array <type>))
+ (# meta.monad in (jvm.array <type>))
_
<failure>)]
- [type.boolean]
- [type.byte]
- [type.short]
- [type.int]
- [type.long]
- [type.float]
- [type.double]
- [type.char]))
+ [jvm.boolean]
+ [jvm.byte]
+ [jvm.short]
+ [jvm.int]
+ [jvm.long]
+ [jvm.float]
+ [jvm.double]
+ [jvm.char]))
(text#= array.type_name name)
(case params
{.#Item elementLT {.#End}}
- (# meta.monad each type.array
+ (# meta.monad each jvm.array
(lux_type->jvm_type context elementLT))
_
@@ -1763,17 +1761,17 @@
(case params
{.#End}
(let [[_ unprefixed] (maybe.trusted (text.split_by descriptor.array_prefix name))]
- (# meta.monad each type.array
+ (# meta.monad each jvm.array
(lux_type->jvm_type context {.#Primitive unprefixed (list)})))
_
<failure>)
... else
- (# meta.monad each (type.class name)
+ (# meta.monad each (jvm.class name)
(: (Meta (List (Type Parameter)))
(monad.each meta.monad
- (.function (_ paramLT)
+ (function (_ paramLT)
(do meta.monad
[paramJT (lux_type->jvm_type context paramLT)]
(case (parser.parameter? paramJT)
@@ -1785,7 +1783,7 @@
params)))))
{.#Apply A F}
- (case (lux_type.applied (list A) F)
+ (case (type.applied (list A) F)
{.#None}
<failure>
@@ -1814,19 +1812,19 @@
context meta.type_context
array_jvm_type (lux_type->jvm_type context array_type)
.let [g!extension (code.text (`` (cond (~~ (template [<primitive> <extension>]
- [(# type.equivalence =
- (type.array <primitive>)
+ [(# jvm.equivalence =
+ (jvm.array <primitive>)
array_jvm_type)
<extension>]
- [type.boolean "jvm array length boolean"]
- [type.byte "jvm array length byte"]
- [type.short "jvm array length short"]
- [type.int "jvm array length int"]
- [type.long "jvm array length long"]
- [type.float "jvm array length float"]
- [type.double "jvm array length double"]
- [type.char "jvm array length char"]))
+ [jvm.boolean "jvm array length boolean"]
+ [jvm.byte "jvm array length byte"]
+ [jvm.short "jvm array length short"]
+ [jvm.int "jvm array length int"]
+ [jvm.long "jvm array length long"]
+ [jvm.float "jvm array length float"]
+ [jvm.double "jvm array length double"]
+ [jvm.char "jvm array length char"]))
... else
"jvm array length object")))]]
@@ -1855,21 +1853,21 @@
"jvm object cast"
"jvm conversion long-to-int"))]]
(`` (cond (~~ (template [<primitive> <extension> <box>]
- [(# type.equivalence =
- (type.array <primitive>)
+ [(# jvm.equivalence =
+ (jvm.array <primitive>)
array_jvm_type)
(in (list (` (.|> (<extension> (~ g!idx) (~ array))
"jvm object cast"
(.: (.Primitive (~ (code.text <box>))))))))]
- [type.boolean "jvm array read boolean" box.boolean]
- [type.byte "jvm array read byte" box.byte]
- [type.short "jvm array read short" box.short]
- [type.int "jvm array read int" box.int]
- [type.long "jvm array read long" box.long]
- [type.float "jvm array read float" box.float]
- [type.double "jvm array read double" box.double]
- [type.char "jvm array read char" box.char]))
+ [jvm.boolean "jvm array read boolean" box.boolean]
+ [jvm.byte "jvm array read byte" box.byte]
+ [jvm.short "jvm array read short" box.short]
+ [jvm.int "jvm array read int" box.int]
+ [jvm.long "jvm array read long" box.long]
+ [jvm.float "jvm array read float" box.float]
+ [jvm.double "jvm array read double" box.double]
+ [jvm.char "jvm array read char" box.char]))
... else
(in (list (` ("jvm array read object" (~ g!idx) (~ array))))))))
@@ -1894,22 +1892,22 @@
"jvm object cast"
"jvm conversion long-to-int"))]]
(`` (cond (~~ (template [<primitive> <extension> <box>]
- [(# type.equivalence =
- (type.array <primitive>)
+ [(# jvm.equivalence =
+ (jvm.array <primitive>)
array_jvm_type)
(let [g!value (` (.|> (~ value)
(.:as (.Primitive (~ (code.text <box>))))
"jvm object cast"))]
(in (list (` (<extension> (~ g!idx) (~ g!value) (~ array))))))]
- [type.boolean "jvm array write boolean" box.boolean]
- [type.byte "jvm array write byte" box.byte]
- [type.short "jvm array write short" box.short]
- [type.int "jvm array write int" box.int]
- [type.long "jvm array write long" box.long]
- [type.float "jvm array write float" box.float]
- [type.double "jvm array write double" box.double]
- [type.char "jvm array write char" box.char]))
+ [jvm.boolean "jvm array write boolean" box.boolean]
+ [jvm.byte "jvm array write byte" box.byte]
+ [jvm.short "jvm array write short" box.short]
+ [jvm.int "jvm array write int" box.int]
+ [jvm.long "jvm array write long" box.long]
+ [jvm.float "jvm array write float" box.float]
+ [jvm.double "jvm array write double" box.double]
+ [jvm.char "jvm array write char" box.char]))
... else
(in (list (` ("jvm array write object" (~ g!idx) (~ value) (~ array))))))))
@@ -1967,96 +1965,3 @@
[as_char .Int ..long_to_char ..Long ..char_to_long ..Character of_char]
[as_float .Frac ..double_to_float ..Double ..float_to_double ..Float of_float]
)
-
-(type: (API of)
- (Record
- [#interface of
- #type Code
- #term Code]))
-
-(def: (api of)
- (All (_ of) (-> (Parser of) (Parser (API of))))
- (<code>.form
- ($_ <>.and
- of
- <code>.any
- <code>.any
- )))
-
-(type: Constant
- Text)
-
-(def: constant
- (Parser Constant)
- <code>.local_symbol)
-
-(type: Function
- (Record
- [#variables (List Text)
- #name Text
- #requirements (List [Text Code])]))
-
-(def: function
- (Parser Function)
- (<code>.form
- ($_ <>.and
- (<>.else (list) (<code>.tuple (<>.some <code>.local_symbol)))
- <code>.local_symbol
- (<code>.tuple (<>.some ($_ <>.and
- <code>.local_symbol
- <code>.any
- )))
- )))
-
-(type: Export
- (Variant
- {#Constant (API Constant)}
- {#Function (API Function)}))
-
-(def: export
- (Parser Export)
- ($_ <>.or
- (..api ..constant)
- (..api ..function)
- ))
-
-(syntax: .public (export: [api <code>.local_symbol
- exports (<>.many ..export)])
- (let [initialization (: (List (API Constant))
- (list.all (.function (_ it)
- (case it
- {#Constant it}
- {.#Some it}
-
- _
- {.#None}))
- exports))]
- (in (list (` (..class: "final" (~ (code.local_symbol api))
- (~+ (list#each (.function (_ it)
- (case it
- {#Constant [name type term]}
- (` ("public" "final" "static" (~ (code.local_symbol name)) (~ type)))
-
- {#Function [[variables name requirements] type term]}
- (` ("public" "strict" "static"
- [(~+ (list#each code.local_symbol variables))]
- ((~ (code.local_symbol name))
- [(~+ (|> requirements
- (list#each (.function (_ [name type])
- (list (code.local_symbol name)
- type)))
- list#conjoint))])
- (~ type)
- (~ term)))))
- exports))
- ... Useless constructor
- ("private" [] ((~' new) (~' self) []) [] [])
- ("public" "strict" "static" [] ((~' <clinit>) [])
- (~' void)
- [(~+ (list#each (.function (_ [name type term])
- (` ("jvm member put static"
- (~ (code.text api))
- (~ (code.text name))
- ("jvm object cast" (~ term)))))
- initialization))])
- ))))))