aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/ffi.lux
diff options
context:
space:
mode:
authorEduardo Julian2022-07-02 05:38:27 -0400
committerEduardo Julian2022-07-02 05:38:27 -0400
commitb96beb587c11fcfbce86ce2d62351600cf6cad1b (patch)
treec9a558ab1391ac97cb11e8777ea78299f1ab5555 /stdlib/source/library/lux/ffi.lux
parent104130efba46a875eba566384578f8aa8593ad37 (diff)
More traditional names for unquoting macros.
Diffstat (limited to 'stdlib/source/library/lux/ffi.lux')
-rw-r--r--stdlib/source/library/lux/ffi.lux210
1 files changed, 105 insertions, 105 deletions
diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux
index 90681746d..3dd10ebe6 100644
--- a/stdlib/source/library/lux/ffi.lux
+++ b/stdlib/source/library/lux/ffi.lux
@@ -234,8 +234,8 @@
(`` (`` (type Sub
(Variant
- (~~ (for @.lua (~~ (these))
- @.ruby (~~ (these))
+ (,, (for @.lua (,, (these))
+ @.ruby (,, (these))
{#Constructor Constructor}))
{#Field Field}
{#Method Method}))))
@@ -243,8 +243,8 @@
(`` (`` (def sub
(Parser Sub)
(all <>.or
- (~~ (for @.lua (~~ (these))
- @.ruby (~~ (these))
+ (,, (for @.lua (,, (these))
+ @.ruby (,, (these))
..constructor))
..field
..method
@@ -260,7 +260,7 @@
(def (output_type it)
(-> Optional Code)
(if (the #optional? it)
- (` (.Maybe (~ (the #mandatory it))))
+ (` (.Maybe (, (the #mandatory it))))
(the #mandatory it)))
(`` (with_template [<lux_it> <host_it>
@@ -278,9 +278,9 @@
(def (host_optional it)
(-> Optional Code)
(.if (.the #optional? it)
- (` (.case (~ (the #mandatory it))
- {.#Some (~ g!it')}
- (~ g!it')
+ (` (.case (, (the #mandatory it))
+ {.#Some (, g!it')}
+ (, g!it')
{.#None}
(<host_it>)))
@@ -288,16 +288,16 @@
(def (lux_optional it output)
(-> Optional Code Code)
- (` (.let [(~ g!it') (~ output)]
- (~ (if (the #optional? it)
- (` (.if (<host_?> (~ g!it'))
+ (` (.let [(, g!it') (, output)]
+ (, (if (the #optional? it)
+ (` (.if (<host_?> (, g!it'))
{.#None}
- {.#Some (~ g!it')}))
- (` (.if (.not (<host_?> (~ g!it')))
- (~ g!it')
+ {.#Some (, g!it')}))
+ (` (.if (.not (<host_?> (, g!it')))
+ (, g!it')
(.panic! "Invalid output."))))))))))]
- (~~ (for @.js [null "js object null"
+ (,, (for @.js [null "js object null"
null? "js object null?"]
@.python [none "python object none"
none? "python object none?"]
@@ -347,19 +347,19 @@
(def (input_type input :it:)
(-> Input Code Code)
(let [:it: (if (the #try? input)
- (` (.Either .Text (~ :it:)))
+ (` (.Either .Text (, :it:)))
:it:)]
(if (the #io? input)
- (` ((~! io.IO) (~ :it:)))
+ (` ((,! io.IO) (, :it:)))
:it:)))
(def (input_term input term)
(-> Input Code Code)
(let [term (if (the #try? input)
- (` (.try (~ term)))
+ (` (.try (, term)))
term)]
(if (the #io? input)
- (` ((~! io.io) (~ term)))
+ (` ((,! io.io) (, term)))
term)))
(def (procedure_definition import! source it)
@@ -378,21 +378,21 @@
parameters
(list#each ..output_type :parameters:))]
- (` (.def ((~ g!it) (~+ (case g!parameters
+ (` (.def ((, g!it) (,* (case g!parameters
{.#End} (list g!it)
_ (list#each (the #mandatory) g!parameters))))
- (.All ((~ g!it) (~+ g!variables))
- (-> (~+ :input:/*)
- (~ (|> :output:
+ (.All ((, g!it) (,* g!variables))
+ (-> (,* :input:/*)
+ (, (|> :output:
..output_type
(..input_type input)))))
(.exec
- (~+ import!)
+ (,* import!)
(.as_expected
- (~ (<| (..input_term input)
+ (, (<| (..input_term input)
(..lux_optional :output:)
- (` (<apply> (.as_expected (~ source))
- [(~+ (list#each ..host_optional g!parameters))]))))))))))
+ (` (<apply> (.as_expected (, source))
+ [(,* (list#each ..host_optional g!parameters))]))))))))))
(def (namespaced namespace class alias member)
(-> Namespace Text Alias Text Text)
@@ -411,14 +411,14 @@
(case (text.all_split_by .module_separator class)
{.#Item head tail}
(list#mix (.function (_ sub super)
- (` (<get> (~ (code.text sub))
+ (` (<get> (, (code.text sub))
(.as (..Object .Any)
- (~ super)))))
- (` (<import> (~ (code.text head))))
+ (, super)))))
+ (` (<import> (, (code.text head))))
tail)
{.#End}
- (` (<import> (~ (code.text class)))))))
+ (` (<import> (, (code.text class)))))))
(def (global_definition import! it)
(-> (List Code) Global Code)
@@ -426,13 +426,13 @@
(maybe.else (the #name it))
code.local)
:output: (the #anonymous it)]
- (` (.def (~ g!name)
- (~ (..output_type :output:))
+ (` (.def (, g!name)
+ (, (..output_type :output:))
(.exec
- (~+ import!)
+ (,* import!)
(.as_expected
- (~ (<| (lux_optional :output:)
- (` (<constant> (~ (code.text (..host_path (the #name it))))))))))))))
+ (, (<| (lux_optional :output:)
+ (` (<constant> (, (code.text (..host_path (the #name it))))))))))))))
(for @.lua (these)
@.ruby (these)
@@ -448,23 +448,23 @@
:parameters: (the #parameters input)
g!parameters (..parameters :parameters:)
g!class_variables (list#each code.local class_parameters)
- g!class (` ((~ (code.local (maybe.else class_name alias))) (~+ g!class_variables)))
+ g!class (` ((, (code.local (maybe.else class_name alias))) (,* g!class_variables)))
:output: [#optional? false #mandatory g!class]]
- (` (.def ((~ g!it) (~+ (case g!parameters
+ (` (.def ((, g!it) (,* (case g!parameters
{.#End} (list g!it)
_ (list#each (the #mandatory) g!parameters))))
- (.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables))
- (.-> (~+ (list#each ..output_type :parameters:))
- (~ (|> :output:
+ (.All ((, g!it) (,* g!class_variables) (,* g!input_variables))
+ (.-> (,* (list#each ..output_type :parameters:))
+ (, (|> :output:
..output_type
(..input_type input)))))
(.as_expected
- (~ (<| (..input_term input)
+ (, (<| (..input_term input)
(..lux_optional :output:)
- (` (<new> (~ (for @.js (` (<constant> (~ (code.text (..host_path class_name)))))
+ (` (<new> (, (for @.js (` (<constant> (, (code.text (..host_path class_name)))))
@.python (` (.as ..Function
- (~ (..imported class_name))))))
- [(~+ (list#each ..host_optional g!parameters))]))))))))))
+ (, (..imported class_name))))))
+ [(,* (list#each ..host_optional g!parameters))]))))))))))
(def (static_field_definition import! [class_name class_parameters] alias namespace it)
(-> (List Code) Declaration Alias Namespace (Named Output) Code)
@@ -474,17 +474,17 @@
(..namespaced namespace class_name alias)
code.local)
:field: (the #anonymous it)]
- (` (def (~ g!it)
- ((~! syntax) ((~ g!it) [])
- (.at (~! meta.monad) (~' in)
+ (` (def (, g!it)
+ ((,! syntax) ((, g!it) [])
+ (.at (,! meta.monad) (,' in)
(.list (`' (.exec
- (~+ import!)
- (.as (~ (..output_type :field:))
- (~ (<| (lux_optional :field:)
- (for @.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." field)))))
- @.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" field)))))
- (` (<get> (~ (code.text field))
- (~ (..imported class_name)))))))))))))))))
+ (,* import!)
+ (.as (, (..output_type :field:))
+ (, (<| (lux_optional :field:)
+ (for @.js (` (<constant> (, (code.text (%.format (..host_path class_name) "." field)))))
+ @.ruby (` (<constant> (, (code.text (%.format (..host_path class_name) "::" field)))))
+ (` (<get> (, (code.text field))
+ (, (..imported class_name)))))))))))))))))
(def (virtual_field_definition [class_name class_parameters] alias namespace it)
(-> Declaration Alias Namespace (Named Output) Code)
@@ -496,14 +496,14 @@
path (%.format (..host_path class_name) "." name)
:field: (the #anonymous it)
g!variables (list#each code.local class_parameters)
- g!class (` ((~ (code.local (maybe.else class_name alias))) (~+ g!variables)))]
- (` (.def ((~ g!it) (~ g!it))
- (.All ((~ g!it) (~+ g!variables))
- (.-> (~ g!class)
- (~ (..output_type :field:))))
+ g!class (` ((, (code.local (maybe.else class_name alias))) (,* g!variables)))]
+ (` (.def ((, g!it) (, g!it))
+ (.All ((, g!it) (,* g!variables))
+ (.-> (, g!class)
+ (, (..output_type :field:))))
(.as_expected
- (~ (<| (lux_optional :field:)
- (` (<get> (~ (code.text name)) (~ g!it))))))))))
+ (, (<| (lux_optional :field:)
+ (` (<get> (, (code.text name)) (, g!it))))))))))
(def (field_definition import! class alias namespace it)
(-> (List Code) Declaration Alias Namespace Field Code)
@@ -520,11 +520,11 @@
(|> it
(has #alias {.#Some name})
(..procedure_definition import!
- (for @.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." method)))))
- @.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" method)))))
- (` (<get> (~ (code.text method))
+ (for @.js (` (<constant> (, (code.text (%.format (..host_path class_name) "." method)))))
+ @.ruby (` (<constant> (, (code.text (%.format (..host_path class_name) "::" method)))))
+ (` (<get> (, (code.text method))
(.as (..Object .Any)
- (~ (..imported class_name))))))))))
+ (, (..imported class_name))))))))))
(def (virtual_method_definition [class_name class_parameters] alias namespace it)
(-> Declaration Alias Namespace (Named Procedure) Code)
@@ -539,21 +539,21 @@
:parameters: (the #parameters input)
g!parameters (..parameters :parameters:)
g!class_variables (list#each code.local class_parameters)
- g!class (` ((~ (code.local (maybe.else class_name alias))) (~+ g!class_variables)))
+ g!class (` ((, (code.local (maybe.else class_name alias))) (,* g!class_variables)))
:output: (the #output procedure)]
- (` (.def ((~ g!it) (~+ (list#each (the #mandatory) g!parameters)) (~ g!it))
- (.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables))
- (.-> (~+ (list#each ..output_type :parameters:))
- (~ g!class)
- (~ (|> :output:
+ (` (.def ((, g!it) (,* (list#each (the #mandatory) g!parameters)) (, g!it))
+ (.All ((, g!it) (,* g!class_variables) (,* g!input_variables))
+ (.-> (,* (list#each ..output_type :parameters:))
+ (, g!class)
+ (, (|> :output:
..output_type
(..input_type input)))))
(.as_expected
- (~ (<| (..input_term input)
+ (, (<| (..input_term input)
(..lux_optional :output:)
- (` (<do> (~ (code.text method))
- (~ g!it)
- [(~+ (list#each ..host_optional g!parameters))])))))))))
+ (` (<do> (, (code.text method))
+ (, g!it)
+ [(,* (list#each ..host_optional g!parameters))])))))))))
(def (method_definition import! class alias namespace it)
(-> (List Code) Declaration Alias Namespace Method Code)
@@ -567,7 +567,7 @@
(let [host_module_import! (is (List Code)
(case host_module
{.#Some host_module}
- (list (` (<import> (~ (code.text host_module)))))
+ (list (` (<import> (, (code.text host_module)))))
{.#None}
(list)))]
@@ -577,7 +577,7 @@
{#Procedure it}
(in (list (..procedure_definition host_module_import!
- (` (<constant> (~ (code.text (..host_path (the #name it))))))
+ (` (<constant> (, (code.text (..host_path (the #name it))))))
it)))
{#Class it}
@@ -586,16 +586,16 @@
[class_name class_parameters] class
namespace (the #namespace it)
g!class_variables (list#each code.local class_parameters)
- declaration (` ((~ (code.local (maybe.else class_name alias)))
- (~+ g!class_variables)))]
- (in (list.partial (` (.type (~ declaration)
- (..Object (.Primitive (~ (code.text (..host_path class_name)))
- [(~+ g!class_variables)]))))
+ declaration (` ((, (code.local (maybe.else class_name alias)))
+ (,* g!class_variables)))]
+ (in (list.partial (` (.type (, declaration)
+ (..Object (.Primitive (, (code.text (..host_path class_name)))
+ [(,* g!class_variables)]))))
(list#each (.function (_ member)
(`` (`` (case member
- (~~ (for @.lua (~~ (these))
- @.ruby (~~ (these))
- (~~ (these {#Constructor it}
+ (,, (for @.lua (,, (these))
+ @.ruby (,, (these))
+ (,, (these {#Constructor it}
(..constructor_definition class alias namespace it)))))
{#Field it}
@@ -615,13 +615,13 @@
type <code>.any
term <code>.any])
(in (list (` (.<| (.as ..Function)
- (<function> (~ (code.nat (list.size inputs))))
- (.as (.-> [(~+ (list.repeated (list.size inputs) (` .Any)))]
+ (<function> (, (code.nat (list.size inputs))))
+ (.as (.-> [(,* (list.repeated (list.size inputs) (` .Any)))]
.Any))
- (.is (.-> [(~+ (list#each product.right inputs))]
- (~ type)))
- (.function ((~ (code.local self)) [(~+ (list#each product.left inputs))])
- (~ term)))))))))
+ (.is (.-> [(,* (list#each product.right inputs))]
+ (, type)))
+ (.function ((, (code.local self)) [(,* (list#each product.left inputs))])
+ (, term)))))))))
(for @.js (these (def .public type_of
(template (type_of object)
@@ -631,27 +631,27 @@
(syntax (_ [type <code>.any
[head tail] (<code>.tuple (<>.and <code>.local (<>.some <code>.local)))])
(with_symbols [g!_]
- (let [global (` ("js constant" (~ (code.text head))))]
+ (let [global (` ("js constant" (, (code.text head))))]
(case tail
{.#End}
- (in (list (` (is (.Maybe (~ type))
- (case (..type_of (~ global))
+ (in (list (` (is (.Maybe (, type))
+ (case (..type_of (, global))
"undefined"
{.#None}
- (~ g!_)
- {.#Some (as (~ type) (~ global))})))))
+ (, g!_)
+ {.#Some (as (, type) (, global))})))))
{.#Item [next tail]}
(let [separator "."]
- (in (list (` (is (.Maybe (~ type))
- (case (..type_of (~ global))
+ (in (list (` (is (.Maybe (, type))
+ (case (..type_of (, global))
"undefined"
{.#None}
- (~ g!_)
- (..global (~ type) [(~ (code.local (%.format head "." next)))
- (~+ (list#each code.local tail))]))))))))))))
+ (, g!_)
+ (..global (, type) [(, (code.local (%.format head "." next)))
+ (,* (list#each code.local tail))]))))))))))))
(def !defined?
(template (_ <global>)
@@ -748,7 +748,7 @@
<code>.any
it
(do try.monad
- [[state it] (phase archive (` (.is .Any (~ it))) state)]
+ [[state it] (phase archive (` (.is .Any (, it))) state)]
(in [state (extension_analysis name (list it))])))
(generation <undefined?>
@@ -769,7 +769,7 @@
(do [! try.monad]
[[state output] (monad.mix ! (.function (_ [key value] [state output])
(do !
- [[state value] (phase archive (` (.is .Any (~ value))) state)]
+ [[state value] (phase archive (` (.is .Any (, value))) state)]
(in [state (list.partial value (text_analysis key) output)])))
[state (list)]
it)]
@@ -812,7 +812,7 @@
(def .public object
(syntax (_ [it (<>.some <code>.any)])
(in (list (` (.as (..Object .Any)
- (<object> (~+ it))))))))
+ (<object> (,* it))))))))
)))
(these))
)