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.lux70
1 files changed, 35 insertions, 35 deletions
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index 5684fb32a..b8c9650d4 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -333,32 +333,32 @@
(-> Primitive_Mode (Type Primitive) Code)
(when mode
{#ManualPrM}
- (cond (at jvm.equivalence = jvm.boolean type) (` ..Boolean)
- (at jvm.equivalence = jvm.byte type) (` ..Byte)
- (at jvm.equivalence = jvm.short type) (` ..Short)
- (at jvm.equivalence = jvm.int type) (` ..Integer)
- (at jvm.equivalence = jvm.long type) (` ..Long)
- (at jvm.equivalence = jvm.float type) (` ..Float)
- (at jvm.equivalence = jvm.double type) (` ..Double)
- (at jvm.equivalence = jvm.char type) (` ..Character)
+ (cond (of jvm.equivalence = jvm.boolean type) (` ..Boolean)
+ (of jvm.equivalence = jvm.byte type) (` ..Byte)
+ (of jvm.equivalence = jvm.short type) (` ..Short)
+ (of jvm.equivalence = jvm.int type) (` ..Integer)
+ (of jvm.equivalence = jvm.long type) (` ..Long)
+ (of jvm.equivalence = jvm.float type) (` ..Float)
+ (of jvm.equivalence = jvm.double type) (` ..Double)
+ (of jvm.equivalence = jvm.char type) (` ..Character)
... else
(undefined))
{#AutoPrM}
- (cond (at jvm.equivalence = jvm.boolean type)
+ (cond (of jvm.equivalence = jvm.boolean type)
(` .Bit)
- (or (at jvm.equivalence = jvm.short type)
- (at jvm.equivalence = jvm.byte type)
- (at jvm.equivalence = jvm.int type)
- (at jvm.equivalence = jvm.long type))
+ (or (of jvm.equivalence = jvm.short type)
+ (of jvm.equivalence = jvm.byte type)
+ (of jvm.equivalence = jvm.int type)
+ (of jvm.equivalence = jvm.long type))
(` .Int)
- (or (at jvm.equivalence = jvm.float type)
- (at jvm.equivalence = jvm.double type))
+ (or (of jvm.equivalence = jvm.float type)
+ (of jvm.equivalence = jvm.double type))
(` .Frac)
- (at jvm.equivalence = jvm.char type)
+ (of jvm.equivalence = jvm.char type)
(` .Nat)
... else
@@ -496,7 +496,7 @@
(|>> (<>.after (<code>.this (' <comparison>)))
(<>.after ..wildcard^)
<code>.tuple
- (at <>.monad each <constructor>)))]
+ (of <>.monad each <constructor>)))]
[upper^ < jvm.upper]
[lower^ > jvm.lower]
@@ -539,7 +539,7 @@
(def array^
(-> (Parser (Type Value)) (Parser (Type Array)))
(|>> <code>.tuple
- (at <>.monad each jvm.array)))
+ (of <>.monad each jvm.array)))
(def (type^ type_vars)
(-> (List (Type Var)) (Parser (Type Value)))
@@ -564,7 +564,7 @@
(def var^
(Parser (Type Var))
- (at <>.monad each jvm.var <code>.local))
+ (of <>.monad each jvm.var <code>.local))
(def vars^
(Parser (List (Type Var)))
@@ -631,7 +631,7 @@
(all <>.or
(<code>.this (' "volatile"))
(<code>.this (' "final"))
- (at <>.monad in [])))
+ (of <>.monad in [])))
(def (field_decl^ type_vars)
(-> (List (Type Var)) (Parser [Member_Declaration FieldDecl]))
@@ -1360,7 +1360,7 @@
(def .public class
(syntax (_ [.let [! <>.monad]
im inheritance_modifier^
- [full_class_name class_vars] (at ! each parser.declaration ..declaration^)
+ [full_class_name class_vars] (of ! each parser.declaration ..declaration^)
super (<>.else $Object
(class^ class_vars))
interfaces (<>.else (list)
@@ -1380,7 +1380,7 @@
(def .public interface
(syntax (_ [.let [! <>.monad]
- [full_class_name class_vars] (at ! each parser.declaration ..declaration^)
+ [full_class_name class_vars] (of ! each parser.declaration ..declaration^)
supers (<>.else (list)
(<code>.tuple (<>.some (class^ class_vars))))
annotations ..annotations^
@@ -1520,7 +1520,7 @@
(in [arg_inputs input_jvm_types arg_types])))
_
- (at meta.monad in [(list) (list) (list)])))
+ (of meta.monad in [(list) (list) (list)])))
(def (with_return_maybe member never_null? unboxed return_term)
(-> Import_Member_Declaration Bit (Type Value) Code Code)
@@ -1571,7 +1571,7 @@
{#AutoPrM}
(with_expansions [<special+>' (template.spliced <special+>)
<cond_cases> (with_template [<primitive> <pre> <post>]
- [(at jvm.equivalence = <primitive> unboxed)
+ [(of jvm.equivalence = <primitive> unboxed)
(with_expansions [<post>' (template.spliced <post>)]
[<primitive>
(` (.|> (, raw) (,* <pre>)))
@@ -1835,7 +1835,7 @@
(let [[class_name _] (parser.declaration declaration)]
(when (load_class class_name)
{.#Right class}
- (at meta.monad in (if (interface? class)
+ (of meta.monad in (if (interface? class)
{#Interface}
{#Class}))
@@ -1863,7 +1863,7 @@
.jvm_object_cast#
.jvm_conversion_long_to_int#))]
(`` (cond (,, (with_template [<primitive> <array_op>]
- [(at jvm.equivalence = <primitive> type)
+ [(of jvm.equivalence = <primitive> type)
(in (list (` (<array_op> (, g!size)))))]
[jvm.boolean .jvm_array_new_boolean#]
@@ -1888,14 +1888,14 @@
(def (lux_type->jvm_type context type)
(-> Type_Context .Type (Meta (Type Value)))
(if (type#= .Any type)
- (at meta.monad in $Object)
+ (of meta.monad in $Object)
(when type
{.#Nominal name params}
(`` (cond (,, (with_template [<type>]
[(text#= (..reflection <type>) name)
(when params
{.#End}
- (at meta.monad in <type>)
+ (of meta.monad in <type>)
_
<failure>)]
@@ -1913,7 +1913,7 @@
[(text#= (..reflection (jvm.array <type>)) name)
(when params
{.#End}
- (at meta.monad in (jvm.array <type>))
+ (of meta.monad in (jvm.array <type>))
_
<failure>)]
@@ -1930,7 +1930,7 @@
(text#= array.nominal name)
(when params
{.#Item {.#Apply writeLT {.#Apply readLT _Mutable}} {.#End}}
- (at meta.monad each jvm.array
+ (of meta.monad each jvm.array
(lux_type->jvm_type context readLT))
_
@@ -1940,14 +1940,14 @@
(when params
{.#End}
(let [[_ unprefixed] (maybe.trusted (text.split_by descriptor.array_prefix name))]
- (at meta.monad each jvm.array
+ (of meta.monad each jvm.array
(lux_type->jvm_type context {.#Nominal unprefixed (list)})))
_
<failure>)
... else
- (at meta.monad each (jvm.class name)
+ (of meta.monad each (jvm.class name)
(.is (Meta (List (Type Parameter)))
(monad.each meta.monad
(function (_ paramLT)
@@ -1992,7 +1992,7 @@
context meta.type_context
array_jvm_type (lux_type->jvm_type context array_type)
.let [g!extension (`` (cond (,, (with_template [<primitive> <extension>]
- [(at jvm.equivalence =
+ [(of jvm.equivalence =
(jvm.array <primitive>)
array_jvm_type)
(` <extension>)]
@@ -2034,7 +2034,7 @@
.jvm_object_cast#
.jvm_conversion_long_to_int#))]]
(`` (cond (,, (with_template [<primitive> <extension> <box>]
- [(at jvm.equivalence =
+ [(of jvm.equivalence =
(jvm.array <primitive>)
array_jvm_type)
(in (list (` (.|> (<extension> (, g!idx) (, array))
@@ -2074,7 +2074,7 @@
.jvm_object_cast#
.jvm_conversion_long_to_int#))]]
(`` (cond (,, (with_template [<primitive> <extension> <box>]
- [(at jvm.equivalence =
+ [(of jvm.equivalence =
(jvm.array <primitive>)
array_jvm_type)
(let [g!value (` (.|> (, value)