aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2023-01-13 16:14:20 -0400
committerEduardo Julian2023-01-13 16:14:20 -0400
commit913171900fd11272ca328ded6553a56423db1e13 (patch)
treee101c51aa5b4467eed4e7b956d2d941cd46f4b10 /stdlib/source/library
parent617069b3986e9271d6e73191b899aa914e430dd6 (diff)
Can now compile complex values (i.e. variants & tuples) in C++.
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux/meta.lux10
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/complex.lux39
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/primitive.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux131
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux25
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux3
-rw-r--r--stdlib/source/library/lux/meta/compiler/target/c++.lux246
-rw-r--r--stdlib/source/library/lux/meta/compiler/target/c++/type.lux92
-rw-r--r--stdlib/source/library/lux/meta/symbol.lux46
-rw-r--r--stdlib/source/library/lux/meta/type.lux4
-rw-r--r--stdlib/source/library/lux/world/time/series/average.lux19
11 files changed, 470 insertions, 147 deletions
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index 4219acd70..7b09f37c9 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -133,10 +133,10 @@
(def .public current_module
(Meta Module)
- (let [(open "#[0]") ..monad]
+ (let [(open "/#[0]") ..monad]
(|> ..current_module_name
- (#each ..module)
- #conjoint)))
+ (/#each ..module)
+ /#conjoint)))
(def (macro_type? type)
(-> Type Bit)
@@ -748,7 +748,9 @@
(eval type code)))
(def .public (try computation)
- (All (_ it) (-> (Meta it) (Meta (Try it))))
+ (All (_ of)
+ (-> (Meta of)
+ (Meta (Try of))))
(function (_ lux)
{try.#Success (when (computation lux)
{try.#Success [lux' output]}
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/complex.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/complex.lux
new file mode 100644
index 000000000..9741d67b0
--- /dev/null
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/complex.lux
@@ -0,0 +1,39 @@
+(.require
+ [library
+ [lux (.except Variant Tuple Synthesis Translation)
+ [abstract
+ ["[0]" monad (.only do)]]
+ [meta
+ [compiler
+ [target
+ ["_" c++]]]]]]
+ [//
+ ["[0]" runtime (.only Translation)]
+ [////
+ ["[0]" phase]
+ [synthesis (.only Synthesis)]
+ [analysis
+ [complex (.only Variant Tuple)]]]])
+
+(def .public (variant phase archive [lefts right? value])
+ (Translation (Variant Synthesis))
+ (do phase.monad
+ [value (phase archive value)]
+ (in (runtime.variant (_.int (.int lefts))
+ (_.bool right?)
+ value))))
+
+(def .public (tuple phase archive values)
+ (Translation (Tuple Synthesis))
+ (let [! phase.monad]
+ (when values
+ {.#End}
+ (of ! in runtime.unit)
+
+ {.#Item it {.#End}}
+ (phase archive it)
+
+ _
+ (|> values
+ (monad.each ! (phase archive))
+ (of ! each runtime.tuple)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/primitive.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/primitive.lux
index a3e90178d..b4935dd1f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/primitive.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/primitive.lux
@@ -26,4 +26,4 @@
(def .public text
(-> Text
Literal)
- _.u32string)
+ _.u32_string)
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux
index c03a1a813..57d354c5f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux
@@ -1,16 +1,49 @@
(.require
[library
- [lux (.except)
+ [lux (.except Declaration Translation)
[data
[text
- ["%" \\format]]]
+ ["%" \\format]]
+ [collection
+ ["[0]" list]]]
["[0]" meta (.use "[1]#[0]" functor)
["[0]" code]
[macro
[syntax (.only syntax)]]
[compiler
[target
- ["_" c++]]]]]])
+ ["_" c++ (.only)
+ ["[0]" type]]]]]]]
+ ["[0]" //
+ ["[1][0]" type]]
+ [/////
+ ["[0]" translation]
+ [///
+ [meta
+ [archive (.only Archive)]]]])
+
+(type .public Anchor
+ Any)
+
+(type .public Value
+ _.Expression)
+
+(type .public Declaration
+ _.Statement)
+
+(with_template [<name> <base>]
+ [(type .public <name>
+ (<base> Anchor Value Declaration))]
+
+ [Operation translation.Operation]
+ [Phase translation.Phase]
+ [Handler translation.Handler]
+ [Bundle translation.Bundle]
+ )
+
+(type .public (Translation of)
+ (-> Phase Archive of
+ (Operation Value)))
(def .public (host_value of it)
(-> _.Type _.Expression
@@ -31,7 +64,51 @@
code.text
list)))))
-(with_expansions [<clean_up> (..name)]
+(with_expansions [<clean_up> (..name)
+
+ <variant> (..name)
+ <lefts> (..name)
+ <right?> (..name)
+ <choice> (..name)
+
+ <tuple> (..name)
+ <arity> (..name)
+ <values> (..name)
+
+ <unit> (..name)]
+ (def .public clean_up
+ (-> _.Type
+ _.Expression)
+ (|>> (list)
+ (_.global [..namespace <clean_up>])))
+
+ (def .public (lux_value of it)
+ (-> _.Type _.Expression
+ _.Expression)
+ (_.on (list it (clean_up of))
+ (_.global [_.standard "shared_ptr"] (list type.void))))
+
+ (def .public (simple of it)
+ (-> _.Type _.Expression
+ _.Expression)
+ (lux_value of
+ (_.new (_.of (list it) of))))
+
+ (def .public (variant lefts right? choice)
+ (-> _.Expression _.Expression _.Expression
+ _.Expression)
+ (let [type (_.type (_.global [..namespace <variant>] (list)))]
+ (lux_value type
+ (_.new (_.structure type (list lefts right? choice))))))
+
+ (def .public (tuple values)
+ (-> (List _.Expression)
+ _.Expression)
+ (let [arity (_.int (.int (list.size values)))
+ type (_.type (_.global [..namespace <tuple>] (list)))]
+ (lux_value type
+ (_.new (_.structure type (list arity (_.new (_.array type arity values))))))))
+
(def .public declaration
_.Declaration
(let [clean_up (let [of (_.type_name "Of")
@@ -39,26 +116,40 @@
(_.function (_.local <clean_up>)
(list of)
(list [(_.* of) it])
- _.void
- (_.delete it)))]
- (all _.then
+ type.void
+ (_.delete it)))
+
+ $variant (_.local <variant>)
+ $tuple (_.local <tuple>)
+ $values (_.local <values>)
+
+ :variant (_.type $variant)
+ :tuple (_.type $tuple)]
+ (all _.also
(_.include "memory")
(<| (_.namespace ..namespace)
- (all _.then
+ (all _.also
clean_up
+
+ (_.constant (_.local <unit>)
+ //type.value
+ (..simple //type.text (_.u32_string "")))
+
+ (<| (_.structure_definition $variant)
+ [(list [(_.local <lefts>) //type.lefts]
+ [(_.local <right?>) //type.right?]
+ [(_.local <choice>) //type.value])
+ (list)])
+
+ (<| (_.structure_definition $tuple)
+ [(list [(_.local <arity>) //type.arity]
+ [$values (_.* //type.value)])
+ (list (<| (_.destructor $tuple)
+ (_.delete_array $values)))])
)))))
- (def .public clean_up
- (-> _.Type
- _.Expression)
- (|>> (list)
- (_.global [..namespace <clean_up>])))
+ (def .public unit
+ _.Expression
+ (_.global [..namespace <unit>] (list)))
)
-
-(def .public (lux_value of it)
- (-> _.Type _.Expression
- _.Expression)
- (_.on (list (_.new of (list it))
- (clean_up of))
- (_.global [_.standard "shared_ptr"] (list _.void))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux
index 9aac0541c..4e995e566 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux
@@ -4,24 +4,37 @@
[meta
[compiler
[target
- ["_" c++]]]]]])
+ ["_" c++ (.only)
+ ["[0]" type]]]]]]])
(def .public bit
_.Type
- (_.type ["" "bool"] (list)))
+ type.bool)
(def .public i64
_.Type
- (_.type ["" "int64_t"] (list)))
+ type.int_64)
(def .public f64
_.Type
- (_.type ["" "double"] (list)))
+ type.double)
(def .public text
_.Type
- (_.type [_.standard "u32string"] (list)))
+ type.u32_string)
(def .public value
_.Type
- (_.type [_.standard "shared_ptr"] (list (_.type ["" "void"] (list)))))
+ (type.shared_ptr type.void))
+
+(def .public lefts
+ _.Type
+ type.char)
+
+(def .public right?
+ _.Type
+ ..bit)
+
+(def .public arity
+ _.Type
+ ..lefts)
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
index cfdf7ac2a..3d25c9723 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
@@ -82,6 +82,7 @@
[(type .public <name>
(<base> Anchor Value Declaration))]
+ [State translation.State]
[Operation translation.Operation]
[Phase translation.Phase]
[Handler translation.Handler]
@@ -655,7 +656,7 @@
]
(in []))))
-(def .public translate
+(def .public translation
(Operation [Registry Output])
(do phase.monad
[runtime_payload ..translate_runtime
diff --git a/stdlib/source/library/lux/meta/compiler/target/c++.lux b/stdlib/source/library/lux/meta/compiler/target/c++.lux
index 952cc0c0b..c13ab7c0d 100644
--- a/stdlib/source/library/lux/meta/compiler/target/c++.lux
+++ b/stdlib/source/library/lux/meta/compiler/target/c++.lux
@@ -1,6 +1,7 @@
(.require
[library
- [lux (.except Code Type Global Declaration int as function template local global type)
+ [lux (.except Code Type Global Declaration Definition
+ int as function template local global type also of)
[abstract
[equivalence (.only Equivalence)]]
[control
@@ -9,7 +10,7 @@
["[0]" text (.only \n \t) (.use "[1]#[0]" equivalence)
["%" \\format]]
[collection
- ["[0]" list (.use "[1]#[0]" functor)]]]
+ ["[0]" list (.use "[1]#[0]" functor monoid)]]]
[math
[number
["f" frac]]]
@@ -19,9 +20,14 @@
[type
["[0]" nominal]]]]])
-(def parameter_separator ", ")
+(def <% nominal.abstraction)
+(def %> nominal.representation)
+
+(def statement_separator ";")
+(def parameter_separator (%.format "," " "))
(def term_delimiters ["(" ")"])
-(def type_delimiters ["<" ">"])
+(def template_delimiters ["<" ">"])
+(def initialization_delimiters ["{" "}"])
(nominal.def .public (Code of)
Text
@@ -31,13 +37,13 @@
(Equivalence (Code of)))
(implementation
(def (= refererence it)
- (text#= (nominal.representation refererence)
- (nominal.representation it)))))
+ (text#= (%> refererence)
+ (%> it)))))
(def .public code
(-> (Code Any)
Text)
- (|>> nominal.representation))
+ (|>> %>))
(with_template [<super> <type>+]
[(`` (with_template [<type> <parameter>*']
@@ -57,22 +63,29 @@
[Expression [of]]
[Statement [of]]]]
+ [Type
+ [[Type_Name []]]]
+
[Expression
[[Computation [of]]
[Reference [of]]]]
- [Type
- [[Type_Name []]]]
-
[Computation
- [[Literal []]]]
+ [[Literal []]
+ [Instantiation []]]]
[Reference
[[Local []]
[Global []]]]
[Statement
- [[Declaration []]]]
+ [[Declaration [of]]]]
+
+ [Declaration
+ [[Definition [of]]]]
+
+ [Definition
+ [[Method []]]]
)
(def .public bool
@@ -81,7 +94,7 @@
(|>> (|.when
.false "false"
.true "true")
- nominal.abstraction))
+ <%))
(def .public double
(-> Frac
@@ -97,7 +110,7 @@
... else
[%.frac])
- nominal.abstraction))
+ <%))
(.type .public Namespace
Text)
@@ -109,7 +122,7 @@
(def .public local
(-> Text
Local)
- (|>> nominal.abstraction))
+ (|>> <%))
(def instantiation
(-> (List Type)
@@ -122,62 +135,51 @@
(|> it
(list#each ..code)
(text.interposed ..parameter_separator)
- (text.enclosed ..type_delimiters)))))
+ (text.enclosed ..template_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)))))
+ (<% (let [instance (%.format name (instantiation parameters))]
+ (when ns
+ "" instance
+ _ (%.format ns "::" instance)))))
- (def .public (type name parameters)
- (-> [Namespace Text] (List Type)
+ (def .public type
+ (-> Reference
Type)
- (|> (..global name parameters)
- nominal.transmutation))
+ (|>> 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
- (%.format "(" (nominal.representation type) ")"
- " " (nominal.representation term))))
+ (<% (%.format "(" (%> type) ")"
+ " " (%> term))))
(def .public int
(-> Int
Literal)
(|>> %.int
- nominal.abstraction))
+ <%))
(def application
(-> (List Expression)
@@ -189,67 +191,85 @@
(def .public (on parameters function)
(-> (List Expression) Expression
Expression)
- (nominal.abstraction
- (%.format (nominal.representation function)
- (application parameters))))
+ (<% (%.format (%> function) (application parameters))))
+
+ (def .public (of parameters constructor)
+ (-> (List Expression) Type
+ Instantiation)
+ (<% (%.format (%> constructor) (application parameters))))
+
+ (def initialization
+ (-> (List Expression)
+ Text)
+ (|>> (list#each ..code)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..initialization_delimiters)))
- (def .public (new of parameters)
+ (def .public (structure name parameters)
(-> Type (List Expression)
+ Instantiation)
+ (<% (%.format (%> name) (initialization parameters))))
+
+ (def .public (array type arity initials)
+ (-> Type Expression (List Expression)
+ Instantiation)
+ (<% (%.format (%> type) "[" (%> arity) "]" " " (initialization initials))))
+
+ (def .public (new it)
+ (-> Instantiation
Expression)
- (nominal.abstraction
- (%.format "new "
- (nominal.representation of)
- (application parameters))))
+ (<% (%.format "new " (%> it))))
(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))))
+ (<% (%.format (%> object) "." method (instantiation types) (application parameters))))
(def .public (<< it to)
(-> Expression Expression
Expression)
- (nominal.abstraction
- (%.format (nominal.representation to)
- " << "
- (nominal.representation it))))
+ (<% (%.format (%> to) " << " (%> it))))
(def .public (include it)
(-> Text
Declaration)
- (nominal.abstraction
- (%.format "#include <" it ">")))
+ (<% (%.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))))
+ (with_template [<name> <type>]
+ [(def .public (<name> before after)
+ (-> <type> <type>
+ <type>)
+ (<% (%.format (%> before)
+ \n (%> after))))]
+
+ [then Statement]
+ [also Declaration]
+ )
(def statement
- (-> Text
- Statement)
- (|>> (text.suffix ";")
- nominal.abstraction))
+ (All (_ of)
+ (-> Text
+ (Statement of)))
+ (|>> (text.suffix ..statement_separator)
+ <%))
(def .public ;
(-> Expression
Statement)
- (|>> nominal.representation
+ (|>> %>
..statement))
- (def .public delete
- (-> Expression
- Statement)
- (|>> nominal.representation
- (%.format "delete ")
- ..statement))
+ (with_template [<name> <command>]
+ [(def .public <name>
+ (-> Expression
+ Statement)
+ (|>> %>
+ (%.format <command> " ")
+ ..statement))]
+
+ [delete "delete"]
+ [delete_array "delete[]"]
+ )
(def template
(-> (List Type_Name)
@@ -261,9 +281,9 @@
it
(%.format "template"
" " (|> it
- (list#each (|>> nominal.representation (%.format "typename ")))
+ (list#each (|>> %> (%.format "typename ")))
(text.interposed ..parameter_separator)
- (text.enclosed ..type_delimiters))
+ (text.enclosed ..template_delimiters))
" "))))
(.type Argument
@@ -272,8 +292,7 @@
(def (argument [type it])
(-> Argument
Text)
- (%.format (nominal.representation type)
- " " (nominal.representation it)))
+ (%.format (%> type) " " (%> it)))
(def arguments
(-> (List Argument)
@@ -283,31 +302,27 @@
(text.enclosed ..term_delimiters)))
(def block
- (-> Statement
+ (-> Text
Text)
(let [\n\t (%.format \n \t)
- <| (%.format "{" \n)
+ <| (%.format "{" \n\t)
|> (%.format \n "}")]
- (|>> nominal.representation
- (text.replaced \n \n\t)
+ (|>> (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))))
+ Definition)
+ (<% (%.format (..template types)
+ (%> output) " " (%> name) (..arguments inputs)
+ " " (..block (%> body)))))
(def .public (namespace it body)
(-> Namespace Declaration
Declaration)
- (nominal.abstraction
- (%.format "namespace"
- " " it
- " " (..block body))))
+ (<% (%.format "namespace"
+ " " it
+ " " (..block (%> body)))))
... https://en.cppreference.com/w/cpp/types/integer
(with_template [<name>]
@@ -315,7 +330,7 @@
(-> Expression
Expression)
(..on (list it)
- (nominal.abstraction (template.text [<name>]))))]
+ (<% (template.text [<name>]))))]
[int64_t]
)
@@ -340,11 +355,42 @@
))))
... https://en.cppreference.com/w/cpp/string/basic_string
- (def .public u32string
+ (def .public u32_string
(-> Text
Literal)
(|>> ..safe
%.text
(%.format "U")
- nominal.abstraction))
+ <%))
+
+ (def .public (destructor of body)
+ (-> Local Statement
+ Method)
+ (<% (%.format "~" (%> of) "()"
+ " " (block (%> body)))))
+
+ (def .public (var_declaration name type)
+ (-> Local Type
+ Declaration)
+ (|> (%.format (%> type) " " (%> name))
+ ..statement))
+
+ (def .public (constant name type value)
+ (-> Local Type Expression
+ Definition)
+ (..statement (%.format (%> type) " const " (%> name) " = " (%> value))))
+
+ (def .public (structure_definition name [fields methods])
+ (-> Local [(List [Local Type]) (List Method)]
+ Definition)
+ (..statement
+ (%.format "struct"
+ " " (%> name)
+ " " (block (|> (all list#composite
+ (list#each (.function (_ [name type])
+ (%> (var_declaration name type)))
+ fields)
+ (list#each ..code
+ methods))
+ (text.interposed \n))))))
)
diff --git a/stdlib/source/library/lux/meta/compiler/target/c++/type.lux b/stdlib/source/library/lux/meta/compiler/target/c++/type.lux
new file mode 100644
index 000000000..a5a296da3
--- /dev/null
+++ b/stdlib/source/library/lux/meta/compiler/target/c++/type.lux
@@ -0,0 +1,92 @@
+(.require
+ [library
+ [lux (.except char int)
+ [meta
+ [macro
+ ["[0]" template]]]]]
+ ["/" //])
+
+(with_template [<ns> <name>/*]
+ [(`` (with_template [<name>]
+ [(def .public <name>
+ /.Type
+ (/.type (/.global [<ns> (template.text [<name>])] (list))))]
+
+ (,, (template.spliced <name>/*))))]
+
+ [""
+ [[void]
+ [bool]
+ [char]
+ [short]
+ [int]
+ [long]
+ [float]
+ [double]]]
+ )
+
+(with_template [<ns> <name>/*]
+ [(`` (with_template [<lux> <c++>]
+ [(def .public <lux>
+ /.Type
+ (/.type (/.global [<ns> <c++>] (list))))]
+
+ (,, (template.spliced <name>/*))))]
+
+ ... https://en.cppreference.com/w/cpp/string/basic_string
+ [/.standard
+ [[string "string"]
+ [wide_string "wstring"]
+ [u08_string "u8string"]
+ [u16_string "u16string"]
+ [u32_string "u32string"]]]
+ )
+
+(with_template [<lux> <c++>]
+ [(def .public <lux>
+ /.Type
+ (/.type (/.global ["" <c++>] (list))))]
+
+ [int_08 "int8_t"]
+ [int_16 "int16_t"]
+ [int_32 "int32_t"]
+ [int_64 "int64_t"]
+
+ [int_fast_08 "int_fast8_t"]
+ [int_fast_16 "int_fast16_t"]
+ [int_fast_32 "int_fast32_t"]
+ [int_fast_64 "int_fast64_t"]
+
+ [int_least_08 "int_least8_t"]
+ [int_least_16 "int_least16_t"]
+ [int_least_32 "int_least32_t"]
+ [int_least_64 "int_least64_t"]
+
+ [int_max "intmax_t"]
+ [int_ptr "intptr_t"]
+
+ [uint_08 "uint8_t"]
+ [uint_16 "uint16_t"]
+ [uint_32 "uint32_t"]
+ [uint_64 "uint64_t"]
+
+ [uint_fast_08 "uint_fast8_t"]
+ [uint_fast_16 "uint_fast16_t"]
+ [uint_fast_32 "uint_fast32_t"]
+ [uint_fast_64 "uint_fast64_t"]
+
+ [uint_least_08 "uint_least8_t"]
+ [uint_least_16 "uint_least16_t"]
+ [uint_least_32 "uint_least32_t"]
+ [uint_least_64 "uint_least64_t"]
+
+ [uint_max "uintmax_t"]
+ [uint_ptr "uintptr_t"]
+ )
+
+(def .public shared_ptr
+ (-> /.Type
+ /.Type)
+ (|>> list
+ (/.global [/.standard "shared_ptr"])
+ /.type))
diff --git a/stdlib/source/library/lux/meta/symbol.lux b/stdlib/source/library/lux/meta/symbol.lux
index 36d4b4256..3ea717f65 100644
--- a/stdlib/source/library/lux/meta/symbol.lux
+++ b/stdlib/source/library/lux/meta/symbol.lux
@@ -15,7 +15,8 @@
(with_template [<name>]
[(def .public (<name> [module short])
- (-> Symbol Text)
+ (-> Symbol
+ Text)
<name>)]
[module]
@@ -47,8 +48,11 @@
(implementation
(def (encoded [module short])
(when module
- "" short
- _ (all text#composite module ..separator short)))
+ ""
+ short
+
+ _
+ (all text#composite module ..separator short)))
(def (decoded input)
(when (text.all_split_by ..separator input)
@@ -60,3 +64,39 @@
_
{.#Left (text#composite "Invalid format for Symbol: " input)}))))
+
+(def .public (relative_codec expected)
+ (-> Text
+ (Codec Text Symbol))
+ (implementation
+ (def (encoded [module short])
+ (when module
+ ""
+ short
+
+ .prelude
+ (all text#composite ..separator short)
+
+ _
+ (all text#composite
+ (if (text#= expected module)
+ ..separator
+ module)
+ ..separator short)))
+
+ (def (decoded input)
+ (when (text.all_split_by ..separator input)
+ (list short)
+ {.#Right ["" short]}
+
+ (list "" short)
+ {.#Right [.prelude short]}
+
+ (list module short)
+ {.#Right [module short]}
+
+ (list "" "" short)
+ {.#Right [expected short]}
+
+ _
+ {.#Left (text#composite "Invalid format for Symbol: " input)}))))
diff --git a/stdlib/source/library/lux/meta/type.lux b/stdlib/source/library/lux/meta/type.lux
index 68bfbb5bd..ff6862ace 100644
--- a/stdlib/source/library/lux/meta/type.lux
+++ b/stdlib/source/library/lux/meta/type.lux
@@ -133,8 +133,8 @@
[.#UnivQ "All"]
[.#ExQ "Ex"]))
- {.#Named [module name] type}
- (all text#composite module "." name)
+ {.#Named name type}
+ (symbol#encoded name)
)))
... https://en.wikipedia.org/wiki/Lambda_calculus#%CE%B2-reduction
diff --git a/stdlib/source/library/lux/world/time/series/average.lux b/stdlib/source/library/lux/world/time/series/average.lux
index 553cfee7f..bc791bb34 100644
--- a/stdlib/source/library/lux/world/time/series/average.lux
+++ b/stdlib/source/library/lux/world/time/series/average.lux
@@ -4,7 +4,7 @@
[abstract
[monad (.only do)]]
[control
- ["[0]" try (.only Try)]
+ ["[0]" try (.only Try) (.use "[1]#[0]" functor)]
["[0]" exception (.only Exception)]]
[data
["[0]" product]
@@ -40,11 +40,12 @@
(list ["Maximum" (%.nat maximum)]
["Actual" (%.nat actual)])))
-(def .public (windows size it)
+(def .public (windows additional it)
(All (_ of)
(-> Nat (Series of)
(Try (Series (Series of)))))
- (let [maximum (//.size it)]
+ (let [size (++ additional)
+ maximum (//.size it)]
(if (n.< size maximum)
(exception.except ..window_size_is_too_large [maximum size])
(let [limit (n.- size maximum)]
@@ -59,7 +60,9 @@
[current (//.window offset size it)]
(again (++ offset)
(sequence.suffix current output)))
- {try.#Success (has //.#data output it)}))))))
+ {try.#Success (|> it
+ (has //.#data output)
+ (has //.#start (//.at size it)))}))))))
(type .public (Average of)
(-> (Series of)
@@ -70,12 +73,8 @@
(All (_ of)
(-> (Average of) Nat (Series of)
(Try (Series of))))
- (do try.monad
- [.let [size (++ additional)]
- it (windows size it)]
- (in (|> it
- (revised //.#data (sequence#each average))
- (has //.#start (//.at size it))))))
+ (try#each (revised //.#data (sequence#each average))
+ (windows additional it)))
... https://en.wikipedia.org/wiki/Moving_average#Exponential_moving_average
... https://en.wikipedia.org/wiki/Exponential_smoothing