aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/target
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/meta/target')
-rw-r--r--stdlib/source/library/lux/meta/target/c++.lux284
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type.lux47
-rw-r--r--stdlib/source/library/lux/meta/target/python.lux18
3 files changed, 293 insertions, 56 deletions
diff --git a/stdlib/source/library/lux/meta/target/c++.lux b/stdlib/source/library/lux/meta/target/c++.lux
index b8c2414f4..952cc0c0b 100644
--- a/stdlib/source/library/lux/meta/target/c++.lux
+++ b/stdlib/source/library/lux/meta/target/c++.lux
@@ -1,10 +1,12 @@
(.require
[library
- [lux (.except Code Type int)
+ [lux (.except Code Type Global Declaration int as function template local global type)
+ [abstract
+ [equivalence (.only Equivalence)]]
[control
["|" pipe]]
[data
- ["[0]" text (.only)
+ ["[0]" text (.only \n \t) (.use "[1]#[0]" equivalence)
["%" \\format]]
[collection
["[0]" list (.use "[1]#[0]" functor)]]]
@@ -17,32 +19,60 @@
[type
["[0]" nominal]]]]])
+(def parameter_separator ", ")
+(def term_delimiters ["(" ")"])
+(def type_delimiters ["<" ">"])
+
(nominal.def .public (Code of)
Text
+ (def .public equivalence
+ (All (_ of)
+ (Equivalence (Code of)))
+ (implementation
+ (def (= refererence it)
+ (text#= (nominal.representation refererence)
+ (nominal.representation it)))))
+
(def .public code
(-> (Code Any)
Text)
(|>> nominal.representation))
- (with_template [<type> <super>+]
- [(with_expansions [<of> (template.symbol [<type> "'"])]
- (nominal.def (<of> of)
- Any)
- (`` (type .public <type>
- (|> Any <of> (,, (template.spliced <super>+))))))]
+ (with_template [<super> <type>+]
+ [(`` (with_template [<type> <parameter>*']
+ [(with_expansions [<parameter>* (template.spliced <parameter>*')
+ <brand> (template.symbol [<type> "'"])]
+ (nominal.def (<brand> <parameter>*)
+ Any)
+
+ (.type .public <type>
+ (Ex (_ <parameter>*)
+ (<super> (<brand> <parameter>*)))))]
- [Type [Code]]
- [Expression [Code]]
- [Computation [Expression' Code]]
- )
+ (,, (template.spliced <type>+))))]
+
+ [Code
+ [[Type [of]]
+ [Expression [of]]
+ [Statement [of]]]]
+
+ [Expression
+ [[Computation [of]]
+ [Reference [of]]]]
+
+ [Type
+ [[Type_Name []]]]
- (with_template [<type> <super>+]
- [(with_expansions [<brand> (template.symbol [<type> "'"])]
- (nominal.def <brand> Any)
- (`` (type .public <type> (|> <brand> (,, (template.spliced <super>+))))))]
+ [Computation
+ [[Literal []]]]
- [Literal [Computation' Expression' Code]]
+ [Reference
+ [[Local []]
+ [Global []]]]
+
+ [Statement
+ [[Declaration []]]]
)
(def .public bool
@@ -69,7 +99,74 @@
[%.frac])
nominal.abstraction))
- (def .public (cast type term)
+ (.type .public Namespace
+ Text)
+
+ (def .public standard
+ Namespace
+ "std")
+
+ (def .public local
+ (-> Text
+ Local)
+ (|>> nominal.abstraction))
+
+ (def instantiation
+ (-> (List Type)
+ Text)
+ (|>> (|.when
+ (list)
+ ""
+
+ it
+ (|> it
+ (list#each ..code)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..type_delimiters)))))
+
+ (def .public (global [ns name] parameters)
+ (-> [Namespace Text] (List Type)
+ Global)
+ (nominal.abstraction
+ (let [instance (%.format name (instantiation parameters))]
+ (when ns
+ "" instance
+ _ (%.format ns "::" instance)))))
+
+ (def .public (type name parameters)
+ (-> [Namespace Text] (List Type)
+ Type)
+ (|> (..global name parameters)
+ nominal.transmutation))
+
+ (def .public type_name
+ (-> Text
+ Type_Name)
+ (|>> nominal.abstraction))
+
+ (with_template [<ns> <name>]
+ [(def .public <name>
+ Type
+ (..type [<ns> (template.text [<name>])] (list)))]
+
+ ["" void]
+ )
+
+ (def .public *
+ (-> Type
+ Type)
+ (|>> nominal.representation
+ (text.suffix "*")
+ nominal.abstraction))
+
+ (def .public deref
+ (-> Expression
+ Expression)
+ (|>> nominal.representation
+ (text.prefix "*")
+ nominal.abstraction))
+
+ (def .public (as type term)
(-> Type Expression
Computation)
(nominal.abstraction
@@ -82,16 +179,135 @@
(|>> %.int
nominal.abstraction))
+ (def application
+ (-> (List Expression)
+ Text)
+ (|>> (list#each ..code)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..term_delimiters)))
+
(def .public (on parameters function)
(-> (List Expression) Expression
Expression)
(nominal.abstraction
(%.format (nominal.representation function)
- "("
- (|> parameters
- (list#each (|>> nominal.representation))
- (text.interposed ", "))
- ")")))
+ (application parameters))))
+
+ (def .public (new of parameters)
+ (-> Type (List Expression)
+ Expression)
+ (nominal.abstraction
+ (%.format "new "
+ (nominal.representation of)
+ (application parameters))))
+
+ (def .public (do method types parameters object)
+ (-> Text (List Type) (List Expression) Expression
+ Expression)
+ (nominal.abstraction
+ (%.format (nominal.representation object)
+ "." method
+ (instantiation types)
+ (application parameters))))
+
+ (def .public (<< it to)
+ (-> Expression Expression
+ Expression)
+ (nominal.abstraction
+ (%.format (nominal.representation to)
+ " << "
+ (nominal.representation it))))
+
+ (def .public (include it)
+ (-> Text
+ Declaration)
+ (nominal.abstraction
+ (%.format "#include <" it ">")))
+
+ (def .public (then before after)
+ (All (_ of)
+ (-> (Statement of) (Statement of)
+ (Statement of)))
+ (nominal.abstraction
+ (%.format (nominal.representation before)
+ \n (nominal.representation after))))
+
+ (def statement
+ (-> Text
+ Statement)
+ (|>> (text.suffix ";")
+ nominal.abstraction))
+
+ (def .public ;
+ (-> Expression
+ Statement)
+ (|>> nominal.representation
+ ..statement))
+
+ (def .public delete
+ (-> Expression
+ Statement)
+ (|>> nominal.representation
+ (%.format "delete ")
+ ..statement))
+
+ (def template
+ (-> (List Type_Name)
+ Text)
+ (|>> (|.when
+ (list)
+ ""
+
+ it
+ (%.format "template"
+ " " (|> it
+ (list#each (|>> nominal.representation (%.format "typename ")))
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..type_delimiters))
+ " "))))
+
+ (.type Argument
+ [Type Local])
+
+ (def (argument [type it])
+ (-> Argument
+ Text)
+ (%.format (nominal.representation type)
+ " " (nominal.representation it)))
+
+ (def arguments
+ (-> (List Argument)
+ Text)
+ (|>> (list#each ..argument)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..term_delimiters)))
+
+ (def block
+ (-> Statement
+ Text)
+ (let [\n\t (%.format \n \t)
+ <| (%.format "{" \n)
+ |> (%.format \n "}")]
+ (|>> nominal.representation
+ (text.replaced \n \n\t)
+ (text.enclosed [<| |>]))))
+
+ (def .public (function name types inputs output body)
+ (-> Local (List Type_Name) (List Argument) Type Statement
+ Declaration)
+ (nominal.abstraction
+ (%.format (..template types) (nominal.representation output)
+ " " (nominal.representation name)
+ (..arguments inputs)
+ " " (..block body))))
+
+ (def .public (namespace it body)
+ (-> Namespace Declaration
+ Declaration)
+ (nominal.abstraction
+ (%.format "namespace"
+ " " it
+ " " (..block body))))
... https://en.cppreference.com/w/cpp/types/integer
(with_template [<name>]
@@ -104,11 +320,31 @@
[int64_t]
)
+ (def safe
+ (-> Text
+ Text)
+ (let [\\'' (%.format "\" text.\'')]
+ (`` (|>> (,, (with_template [<find> <replace>]
+ [(text.replaced <find> <replace>)]
+
+ ["\" "\\"]
+ [text.\t "\t"]
+ [text.\v "\v"]
+ [text.\0 "\0"]
+ [text.\b "\b"]
+ [text.\f "\f"]
+ [text.\n "\n"]
+ [text.\r "\r"]
+ [text.\'' \\'']
+ ))
+ ))))
+
... https://en.cppreference.com/w/cpp/string/basic_string
(def .public u32string
(-> Text
Literal)
- (|>> %.text
+ (|>> ..safe
+ %.text
(%.format "U")
nominal.abstraction))
)
diff --git a/stdlib/source/library/lux/meta/target/jvm/type.lux b/stdlib/source/library/lux/meta/target/jvm/type.lux
index 0eff5b048..e1cbb4374 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type.lux
@@ -45,7 +45,9 @@
(with_template [<name> <style>]
[(def .public (<name> type)
- (All (_ category) (-> (Type category) (<style> category)))
+ (All (_ category)
+ (-> (Type category)
+ (<style> category)))
(let [[signature descriptor reflection] (representation type)]
<name>))]
@@ -77,28 +79,32 @@
)
(def .public (array type)
- (-> (Type Value) (Type Array))
+ (-> (Type Value)
+ (Type Array))
(abstraction
[(/signature.array (..signature type))
(/descriptor.array (..descriptor type))
(/reflection.array (..reflection type))]))
(def .public (class name parameters)
- (-> External (List (Type Parameter)) (Type Class))
+ (-> External (List (Type Parameter))
+ (Type Class))
(abstraction
[(/signature.class name (list#each ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
(def .public (declaration name variables)
- (-> External (List (Type Var)) (Type Declaration))
+ (-> External (List (Type Var))
+ (Type Declaration))
(abstraction
[(/signature.declaration name (list#each ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
(def .public (as_class type)
- (-> (Type Declaration) (Type Class))
+ (-> (Type Declaration)
+ (Type Class))
(abstraction
(let [[signature descriptor reflection] (representation type)]
[(/signature.as_class signature)
@@ -113,14 +119,16 @@
/reflection.wildcard]))
(def .public (var name)
- (-> Text (Type Var))
+ (-> Text
+ (Type Var))
(abstraction
[(/signature.var name)
/descriptor.var
/reflection.var]))
(def .public (lower bound)
- (-> (Type Parameter) (Type Parameter))
+ (-> (Type Parameter)
+ (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
[(/signature.lower signature)
@@ -128,7 +136,8 @@
(/reflection.lower reflection)])))
(def .public (upper bound)
- (-> (Type Parameter) (Type Parameter))
+ (-> (Type Parameter)
+ (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
[(/signature.upper signature)
@@ -151,7 +160,8 @@
(as_expected ..void)]))
(def .public equivalence
- (All (_ category) (Equivalence (Type category)))
+ (All (_ category)
+ (Equivalence (Type category)))
(implementation
(def (= parameter subject)
(of /signature.equivalence =
@@ -159,14 +169,16 @@
(..signature subject)))))
(def .public hash
- (All (_ category) (Hash (Type category)))
+ (All (_ category)
+ (Hash (Type category)))
(implementation
(def equivalence ..equivalence)
(def hash (|>> ..signature (of /signature.hash hash)))))
(def .public (primitive? type)
- (-> (Type Value) (Either (Type Object)
- (Type Primitive)))
+ (-> (Type Value)
+ (Either (Type Object)
+ (Type Primitive)))
(if (`` (or (,, (with_template [<type>]
[(of ..equivalence = (is (Type Value) <type>) type)]
@@ -182,8 +194,9 @@
(|> type (as (Type Object)) {.#Left})))
(def .public (void? type)
- (-> (Type Return) (Either (Type Value)
- (Type Void)))
+ (-> (Type Return)
+ (Either (Type Value)
+ (Type Void)))
(if (`` (or (,, (with_template [<type>]
[(of ..equivalence = (is (Type Return) <type>) type)]
@@ -193,7 +206,8 @@
)
(def .public (class? type)
- (-> (Type Value) (Maybe External))
+ (-> (Type Value)
+ (Maybe External))
(let [repr (|> type ..descriptor /descriptor.descriptor)]
(if (and (text.starts_with? /descriptor.class_prefix repr)
(text.ends_with? /descriptor.class_suffix repr))
@@ -208,5 +222,6 @@
{.#None})))
(def .public format
- (All (_ a) (Format (Type a)))
+ (All (_ of)
+ (Format (Type of)))
(|>> ..signature /signature.signature))
diff --git a/stdlib/source/library/lux/meta/target/python.lux b/stdlib/source/library/lux/meta/target/python.lux
index a6d0968c5..c1c8fe105 100644
--- a/stdlib/source/library/lux/meta/target/python.lux
+++ b/stdlib/source/library/lux/meta/target/python.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except Location Code not or and list if int comment exec try the is def when)
- ["[0]" ffi]
[abstract
[equivalence (.only Equivalence)]
[hash (.only Hash)]
@@ -18,7 +17,6 @@
["n" nat]
["f" frac]]]
[meta
- ["@" target]
["[0]" code (.only)
["<[1]>" \\parser]]
[macro
@@ -34,14 +32,6 @@
(-> Text Text)
(text.enclosed ["(" ")"]))
-(for @.old (these (ffi.import java/lang/CharSequence
- "[1]::[0]")
-
- (ffi.import java/lang/String
- "[1]::[0]"
- (replace [java/lang/CharSequence java/lang/CharSequence] java/lang/String)))
- (these))
-
... Added the carriage return for better Windows compatibility.
(.def \n+
Text
@@ -50,12 +40,8 @@
(.def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
- (for @.old (|>> (format \n+)
- (as java/lang/String)
- (java/lang/String::replace (as java/lang/CharSequence text.new_line)
- (as java/lang/CharSequence nested_new_line)))
- (|>> (format \n+)
- (text.replaced text.new_line nested_new_line)))))
+ (|>> (format \n+)
+ (text.replaced text.new_line nested_new_line))))
(nominal.def .public (Code brand)
Text