aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/ffi.old.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/ffi.old.lux')
-rw-r--r--stdlib/source/library/lux/ffi.old.lux84
1 files changed, 42 insertions, 42 deletions
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index 2208f9ee4..7444e1d3a 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -284,7 +284,7 @@
... Utils
(def (manual_primitive_type class)
(-> Text (Maybe Code))
- (case class
+ (when class
(^.with_template [<prim> <type>]
[<prim>
{.#Some (' <type>)}])
@@ -303,7 +303,7 @@
(def (auto_primitive_type class)
(-> Text (Maybe Code))
- (case class
+ (when class
(^.with_template [<prim> <type>]
[<prim>
{.#Some (' <type>)}])
@@ -328,7 +328,7 @@
(-> Primitive_Mode (List Type_Parameter) Bit [Text (List GenericType)]
(-> Primitive_Mode (List Type_Parameter) Bit GenericType Code)
Code)
- (case [name+params mode in_array?]
+ (when [name+params mode in_array?]
(^.multi [[prim {.#End}] {#ManualPrM} .false]
[(manual_primitive_type prim)
{.#Some output}])
@@ -346,9 +346,9 @@
(def (class_type' mode type_params in_array? class)
(-> Primitive_Mode (List Type_Parameter) Bit GenericType Code)
- (case class
+ (when class
{#GenericTypeVar name}
- (case (list.example (function (_ [pname pbounds])
+ (when (list.example (function (_ [pname pbounds])
(and (text#= name pname)
(not (list.empty? pbounds))))
type_params)
@@ -386,7 +386,7 @@
(-> Class_Declaration Code)
(let [=params (list#each (.is (-> Type_Parameter Code)
(function (_ [pname pbounds])
- (case pbounds
+ (when pbounds
{.#End}
(code.symbol ["" pname])
@@ -400,9 +400,9 @@
(def (simple_class$ env class)
(-> (List Type_Parameter) GenericType Text)
- (case class
+ (when class
{#GenericTypeVar name}
- (case (list.example (function (_ [pname pbounds])
+ (when (list.example (function (_ [pname pbounds])
(and (text#= name pname)
(not (list.empty? pbounds))))
env)
@@ -423,7 +423,7 @@
(safe name)
{#GenericArray param'}
- (case param'
+ (when param'
{#GenericArray param}
(format "[" (simple_class$ env param))
@@ -467,7 +467,7 @@
(def (pre_walk_replace f input)
(-> (-> Code Code) Code Code)
- (case (f input)
+ (when (f input)
(^.with_template [<tag>]
[[meta {<tag> parts}]
[meta {<tag> (list#each (pre_walk_replace f) parts)}]])
@@ -480,7 +480,7 @@
(def (parser_replacer p ast)
(-> (Parser Code) (-> Code Code))
- (case (<>.result p (list ast))
+ (when (<>.result p (list ast))
{.#Right [{.#End} ast']}
ast'
@@ -490,7 +490,7 @@
(def (field_parser class_name [[field_name _ _] field])
(-> Text [Member_Declaration FieldDecl] (Parser Code))
- (case field
+ (when field
{#ConstantField _}
(get_const_parser class_name field_name)
@@ -537,7 +537,7 @@
(def (method_parser params class_name [[method_name _ _] meth_def])
(-> (List Type_Parameter) Text [Member_Declaration Method_Definition] (Parser Code))
- (case meth_def
+ (when meth_def
{#ConstructorMethod strict? type_vars args constructor_args return_expr exs}
(constructor_parser params class_name args)
@@ -603,7 +603,7 @@
(in {#GenericClass name (list)})))
(<code>.tuple (do <>.monad
[component again^]
- (case component
+ (when component
(^.with_template [<class> <name>]
[{#GenericClass <name> {.#End}}
(in {#GenericClass <class> (list)})])
@@ -988,7 +988,7 @@
(def (privacy_modifier$ pm)
(-> Privacy JVM_Code)
- (case pm
+ (when pm
{#PublicP} "public"
{#PrivateP} "private"
{#ProtectedP} "protected"
@@ -996,7 +996,7 @@
(def (inheritance_modifier$ im)
(-> Inheritance JVM_Code)
- (case im
+ (when im
{#FinalI} "final"
{#AbstractI} "abstract"
{#DefaultI} "default"))
@@ -1011,13 +1011,13 @@
(def (bound_kind$ kind)
(-> BoundKind JVM_Code)
- (case kind
+ (when kind
{#UpperBound} "<"
{#LowerBound} ">"))
(def (generic_type$ gtype)
(-> GenericType JVM_Code)
- (case gtype
+ (when gtype
{#GenericTypeVar name}
name
@@ -1061,14 +1061,14 @@
(def (state_modifier$ sm)
(-> State JVM_Code)
- (case sm
+ (when sm
{#VolatileS} "volatile"
{#FinalS} "final"
{#DefaultS} "default"))
(def (field_decl$ [[name pm anns] field])
(-> [Member_Declaration FieldDecl] JVM_Code)
- (case field
+ (when field
{#ConstantField class value}
(with_parens
(spaced (list "constant" name
@@ -1099,7 +1099,7 @@
(def (method_def$ replacer super_class [[name pm anns] method_def])
(-> (-> Code Code) Super_Class_Decl [Member_Declaration Method_Definition] JVM_Code)
- (case method_def
+ (when method_def
{#ConstructorMethod strict_fp? type_vars arg_decls constructor_args body exs}
(with_parens
(spaced (list "init"
@@ -1280,7 +1280,7 @@
(def .public !!!
(syntax (_ [expr <code>.any])
(with_symbols [g!value]
- (in (list (` (.case (, expr)
+ (in (list (` (.when (, expr)
{.#Some (, g!value)}
(, g!value)
@@ -1298,7 +1298,7 @@
{.#Some (.as (, class_type)
(, g!unchecked))}
{.#None}))]
- (case unchecked
+ (when unchecked
{.#Some unchecked}
(in (list (` (.is (, check_type)
(let [(, g!unchecked) (, unchecked)]
@@ -1335,12 +1335,12 @@
(def (member_type_vars class_tvars member)
(-> (List Type_Parameter) Import_Member_Declaration (List Type_Parameter))
- (case member
+ (when member
{#ConstructorDecl [commons _]}
(list#composite class_tvars (the #import_member_tvars commons))
{#MethodDecl [commons _]}
- (case (the #import_member_kind commons)
+ (when (the #import_member_kind commons)
{#StaticIMK}
(the #import_member_tvars commons)
@@ -1352,7 +1352,7 @@
(def (member_def_arg_bindings type_params class member)
(-> (List Type_Parameter) Class_Declaration Import_Member_Declaration (Meta [(List [Bit Code]) (List Text) (List Code)]))
- (case member
+ (when member
(^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
(let [(open "[0]") commons]
(do [! meta.monad]
@@ -1379,7 +1379,7 @@
(def (decorate_return_maybe class member return_term)
(-> Class_Declaration Import_Member_Declaration Code Code)
- (case member
+ (when member
(^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
(if (the #import_member_maybe? commons)
(` (??? (, return_term)))
@@ -1398,7 +1398,7 @@
(with_template [<name> <tag> <term_trans>]
[(def (<name> member return_term)
(-> Import_Member_Declaration Code Code)
- (case member
+ (when member
(^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
(if (the <tag> commons)
<term_trans>
@@ -1413,7 +1413,7 @@
(def (free_type_param? [name bounds])
(-> Type_Parameter Bit)
- (case bounds
+ (when bounds
{.#End}
true
@@ -1427,7 +1427,7 @@
(with_template [<name> <byte> <short> <int> <float>]
[(def (<name> mode [class expression])
(-> Primitive_Mode [Text Code] Code)
- (case mode
+ (when mode
{#ManualPrM}
expression
@@ -1471,12 +1471,12 @@
all_params (|> (member_type_vars class_tvars member)
(list.only free_type_param?)
(list#each lux_type_parameter))]
- (case member
+ (when member
{#EnumDecl enum_members}
(macro.with_symbols [g!_]
(do [! meta.monad]
[.let [enum_type (.is Code
- (case class_tvars
+ (when class_tvars
{.#End}
(` (Primitive (, (code.text full_name))))
@@ -1513,13 +1513,13 @@
(open "[0]") commons
(open "[0]") method
[jvm_op object_ast] (.is [Text (List Code)]
- (case #import_member_kind
+ (when #import_member_kind
{#StaticIMK}
["invokestatic"
(list)]
{#VirtualIMK}
- (case kind
+ (when kind
{#Class}
["invokevirtual"
(list g!obj)]
@@ -1621,7 +1621,7 @@
(def (class_kind [class_name _])
(-> Class_Declaration (Meta Class_Kind))
(let [class_name (..safe class_name)]
- (case (..load_class class_name)
+ (when (..load_class class_name)
{try.#Success class}
(at meta.monad in (if (interface? class)
{#Interface}
@@ -1645,7 +1645,7 @@
(def .public array
(syntax (_ [type (..generic_type^ (list))
size <code>.any])
- (case type
+ (when type
(^.with_template [<type> <array_op>]
[{#GenericClass <type> (list)}
(in (list (` (<array_op> (, size)))))])
@@ -1669,12 +1669,12 @@
(-> Type (Meta Text))
(if (type#= Any type)
(at meta.monad in "java.lang.Object")
- (case type
+ (when type
{.#Primitive name params}
(at meta.monad in name)
{.#Apply A F}
- (case (type.applied (list A) F)
+ (when (type.applied (list A) F)
{.#None}
(meta.failure (format "Cannot apply type: " (type.format F) " to " (type.format A)))
@@ -1690,12 +1690,12 @@
(def .public read!
(syntax (_ [idx <code>.any
array <code>.any])
- (case array
+ (when array
[_ {.#Symbol array_name}]
(do meta.monad
[array_type (meta.type array_name)
array_jvm_type (type_class_name array_type)]
- (case array_jvm_type
+ (when array_jvm_type
(^.with_template [<type> <array_op>]
[<type>
(in (list (` (<array_op> (, array) (, idx)))))])
@@ -1720,12 +1720,12 @@
(syntax (_ [idx <code>.any
value <code>.any
array <code>.any])
- (case array
+ (when array
[_ {.#Symbol array_name}]
(do meta.monad
[array_type (meta.type array_name)
array_jvm_type (type_class_name array_type)]
- (case array_jvm_type
+ (when array_jvm_type
(^.with_template [<type> <array_op>]
[<type>
(in (list (` (<array_op> (, array) (, idx) (, value)))))])