aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-12-12 18:55:00 -0400
committerEduardo Julian2022-12-12 18:55:00 -0400
commit549cb9623c560fec165b9e88f112a406614f598e (patch)
treed085b6dddf0a7ff5078c19e0f13b48d82bee55d0 /stdlib/source/library
parentfe9a58dfcd5732ef0c5e5c4b7e85370cdc0db45a (diff)
Added accumulation/distribution oscillator.
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux/control/aspect.lux2
-rw-r--r--stdlib/source/library/lux/data/color.lux86
-rw-r--r--stdlib/source/library/lux/data/color/hsl.lux36
-rw-r--r--stdlib/source/library/lux/data/color/scheme.lux98
-rw-r--r--stdlib/source/library/lux/data/color/terminal.lux24
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/function.lux6
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/loop.lux10
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux6
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/structure.lux15
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/when.lux54
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/new.lux4
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/loop.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux8
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux10
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/structure.lux5
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/when.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/function.lux6
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/loop.lux12
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/runtime.lux4
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/structure.lux15
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/when.lux50
-rw-r--r--stdlib/source/library/lux/world/finance/market/analysis/accumulation_distribution.lux23
23 files changed, 238 insertions, 242 deletions
diff --git a/stdlib/source/library/lux/control/aspect.lux b/stdlib/source/library/lux/control/aspect.lux
index f117ded5e..e730f03bd 100644
--- a/stdlib/source/library/lux/control/aspect.lux
+++ b/stdlib/source/library/lux/control/aspect.lux
@@ -24,9 +24,9 @@
[type
["[0]" check]]
[compiler
- ["[0]" phase]
[language
[lux
+ ["[0]" phase]
["[0]" declaration]
["[0]" analysis (.only)
["[0]" module]
diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux
deleted file mode 100644
index b65249c33..000000000
--- a/stdlib/source/library/lux/data/color.lux
+++ /dev/null
@@ -1,86 +0,0 @@
-(.require
- [library
- [lux (.except)
- [abstract
- [monoid (.only Monoid)]
- ["[0]" equivalence (.only Equivalence)]
- ["[0]" hash (.only Hash)]]
- [data
- [collection
- ["[0]" list (.use "[1]#[0]" functor)]]]
- [math
- [number
- ["n" nat]
- ["f" frac]
- ["[0]" int]
- ["[0]" rev (.use "[1]#[0]" interval)]
- ["[0]" i64]]]
- [meta
- [type
- ["[0]" nominal]]]]]
- [/
- ["[0]" rgb (.only RGB)]
- ["[0]" hsl]
- ["[0]" hsb]])
-
-(nominal.def .public Color
- RGB
-
- (def .public of_rgb
- (-> RGB Color)
- (|>> nominal.abstraction))
-
- (def .public rgb
- (-> Color RGB)
- (|>> nominal.representation))
- )
-
-(def (ratio it)
- (-> Frac
- Frac)
- (cond (f.> +1.0 it)
- (f.% +1.0 it)
-
- (f.< +0.0 it)
- (|> it (f.% +1.0) (f.+ +1.0))
-
- ... else
- it))
-
-(type .public Spread
- Frac)
-
-... https://en.wikipedia.org/wiki/Color_scheme
-(type .public Palette
- (-> Spread Nat Color (List Color)))
-
-(def .public (analogous spread variations it)
- Palette
- (let [it (hsl.of_rgb (..rgb it))
- hue (the hsl.#hue it)
- saturation (the hsl.#saturation it)
- luminance (the hsl.#luminance it)
- spread (..ratio spread)]
- (list#each (function (_ idx)
- (|> (hsl.hsl (|> idx ++ .int int.frac (f.* spread) (f.+ hue) ..ratio)
- saturation
- luminance)
- hsl.rgb
- ..of_rgb))
- (list.indices variations))))
-
-(def .public (monochromatic spread variations it)
- Palette
- (let [it (hsb.of_rgb (..rgb it))
- hue (hsb.hue it)
- saturation (hsb.saturation it)
- brightness (hsb.brightness it)
- spread (..ratio spread)]
- (|> (list.indices variations)
- (list#each (|>> ++ .int int.frac
- (f.* spread)
- (f.+ brightness)
- ..ratio
- (hsb.hsb hue saturation)
- hsb.rgb
- ..of_rgb)))))
diff --git a/stdlib/source/library/lux/data/color/hsl.lux b/stdlib/source/library/lux/data/color/hsl.lux
index 835864b26..df8fb8a82 100644
--- a/stdlib/source/library/lux/data/color/hsl.lux
+++ b/stdlib/source/library/lux/data/color/hsl.lux
@@ -184,39 +184,3 @@
(|>> (the #luminance)
(..hsl +0.0
+0.0)))
-
-(with_template [<name> <1> <2>]
- [(`` (def .public (<name> it)
- (-> HSL
- [HSL HSL HSL])
- (let [(open "/[0]") it]
- [it
- (..hsl (|> /#hue (f.+ <1>) ..ratio)
- /#saturation
- /#luminance)
- (..hsl (|> /#hue (f.+ <2>) ..ratio)
- /#saturation
- /#luminance)])))]
-
- [triad (|> +1.0 (f./ +3.0)) (|> +2.0 (f./ +3.0))]
- [clash (|> +1.0 (f./ +4.0)) (|> +3.0 (f./ +4.0))]
- [split_complement (|> +1.0 (f./ +5.0)) (|> +3.0 (f./ +5.0))]
- )
-
-(with_template [<name> <1> <2> <3>]
- [(`` (def .public (<name> it)
- (-> HSL
- [HSL HSL HSL HSL])
- (let [(open "/[0]") it
- of_hue (is (-> Value
- HSL)
- (function (_ hue)
- (..hsl hue /#saturation /#luminance)))]
- [it
- (|> /#hue (f.+ <1>) ..ratio of_hue)
- (|> /#hue (f.+ <2>) ..ratio of_hue)
- (|> /#hue (f.+ <3>) ..ratio of_hue)])))]
-
- [square (|> +1.0 (f./ +4.0)) (|> +2.0 (f./ +4.0)) (|> +3.0 (f./ +4.0))]
- [tetradic (|> +2.0 (f./ +12.0)) (|> +6.0 (f./ +12.0)) (|> +8.0 (f./ +12.0))]
- )
diff --git a/stdlib/source/library/lux/data/color/scheme.lux b/stdlib/source/library/lux/data/color/scheme.lux
new file mode 100644
index 000000000..380502eb3
--- /dev/null
+++ b/stdlib/source/library/lux/data/color/scheme.lux
@@ -0,0 +1,98 @@
+(.require
+ [library
+ [lux (.except)
+ [data
+ [collection
+ ["[0]" list (.use "[1]#[0]" functor)]]]
+ [math
+ [number
+ ["i" int]
+ ["f" frac]]]]]
+ [//
+ [rgb (.only RGB)]
+ ["[0]" hsl]
+ ["[0]" hsb]])
+
+(def (ratio it)
+ (-> Frac
+ Frac)
+ (cond (f.> +1.0 it)
+ (f.% +1.0 it)
+
+ (f.< +0.0 it)
+ (|> it (f.% +1.0) (f.+ +1.0))
+
+ ... else
+ it))
+
+(with_template [<name> <1> <2>]
+ [(`` (def .public (<name> it)
+ (-> RGB
+ [RGB RGB RGB])
+ (let [(open "/[0]") (hsl.of_rgb it)]
+ [it
+ (hsl.rgb (hsl.hsl (|> /#hue (f.+ <1>) ..ratio)
+ /#saturation
+ /#luminance))
+ (hsl.rgb (hsl.hsl (|> /#hue (f.+ <2>) ..ratio)
+ /#saturation
+ /#luminance))])))]
+
+ [triad (|> +1.0 (f./ +3.0)) (|> +2.0 (f./ +3.0))]
+ [clash (|> +1.0 (f./ +4.0)) (|> +3.0 (f./ +4.0))]
+ [split_complement (|> +1.0 (f./ +5.0)) (|> +3.0 (f./ +5.0))]
+ )
+
+(with_template [<name> <1> <2> <3>]
+ [(`` (def .public (<name> it)
+ (-> RGB
+ [RGB RGB RGB RGB])
+ (let [(open "/[0]") (hsl.of_rgb it)
+ of_hue (is (-> hsl.Value
+ RGB)
+ (function (_ hue)
+ (hsl.rgb (hsl.hsl hue /#saturation /#luminance))))]
+ [it
+ (|> /#hue (f.+ <1>) ..ratio of_hue)
+ (|> /#hue (f.+ <2>) ..ratio of_hue)
+ (|> /#hue (f.+ <3>) ..ratio of_hue)])))]
+
+ [square (|> +1.0 (f./ +4.0)) (|> +2.0 (f./ +4.0)) (|> +3.0 (f./ +4.0))]
+ [tetradic (|> +2.0 (f./ +12.0)) (|> +6.0 (f./ +12.0)) (|> +8.0 (f./ +12.0))]
+ )
+
+(type .public Spread
+ Frac)
+
+... https://en.wikipedia.org/wiki/Color_scheme
+(type .public Scheme
+ (-> Spread Nat RGB
+ (List RGB)))
+
+(def .public (analogous spread variations it)
+ Scheme
+ (let [it (hsl.of_rgb it)
+ hue (the hsl.#hue it)
+ saturation (the hsl.#saturation it)
+ luminance (the hsl.#luminance it)
+ spread (..ratio spread)]
+ (list#each (function (_ idx)
+ (hsl.rgb (hsl.hsl (|> idx ++ .int i.frac (f.* spread) (f.+ hue) ..ratio)
+ saturation
+ luminance)))
+ (list.indices variations))))
+
+(def .public (monochromatic spread variations it)
+ Scheme
+ (let [it (hsb.of_rgb it)
+ hue (hsb.hue it)
+ saturation (hsb.saturation it)
+ brightness (hsb.brightness it)
+ spread (..ratio spread)]
+ (|> (list.indices variations)
+ (list#each (|>> ++ .int i.frac
+ (f.* spread)
+ (f.+ brightness)
+ ..ratio
+ (hsb.hsb hue saturation)
+ hsb.rgb)))))
diff --git a/stdlib/source/library/lux/data/color/terminal.lux b/stdlib/source/library/lux/data/color/terminal.lux
index 06c23c6b3..715e30961 100644
--- a/stdlib/source/library/lux/data/color/terminal.lux
+++ b/stdlib/source/library/lux/data/color/terminal.lux
@@ -16,8 +16,8 @@
["[0]" template]]
[type
["[0]" nominal]]]]]
- ["[0]" // (.only Color)
- ["[0]" rgb]])
+ [//
+ ["[0]" rgb (.only RGB)]])
(nominal.def .public Command
[Text Text]
@@ -86,16 +86,16 @@
(with_template [<command> <name> <reset>]
[(def .public (<name> it)
- (-> Color Command)
- (let [it (//.rgb it)]
- (|> [(%.format ..command
- <command>
- ";" (%.nat (the rgb.#red it))
- ";" (%.nat (the rgb.#green it))
- ";" (%.nat (the rgb.#blue it))
- "m")
- <reset>]
- (nominal.abstraction Command))))]
+ (-> RGB
+ Command)
+ (|> [(%.format ..command
+ <command>
+ ";" (%.nat (the rgb.#red it))
+ ";" (%.nat (the rgb.#green it))
+ ";" (%.nat (the rgb.#blue it))
+ "m")
+ <reset>]
+ (nominal.abstraction Command)))]
["38;2" foreground ..default_foreground_color]
["48;2" background ..default_background_color]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/function.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/function.lux
index 7d1d3434b..dadd86f24 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/function.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/function.lux
@@ -21,10 +21,10 @@
["//[1]" ///
[analysis (.only Abstraction Reification Analysis)]
[synthesis (.only Synthesis)]
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[1][0]" translation]
["//[1]" ///
[arity (.only Arity)]
- ["[1][0]" phase (.use "[1]#[0]" monad)]
[reference
[variable (.only Register Variable)]]
[meta
@@ -36,7 +36,7 @@
(def .public (apply expression archive [functionS argsS+])
(Translator (Reification Synthesis))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[functionO (expression archive functionS)
argsO+ (monad.each ! (expression archive) argsS+)]
(in (_.apply functionO argsO+))))
@@ -74,7 +74,7 @@
(def .public (function statement expression archive [environment arity bodyS])
(-> Phase! (Translator (Abstraction Synthesis)))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[dependencies (cache.dependencies archive bodyS)
[function_name body!] (/////translation.with_new_context archive dependencies
(do !
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/loop.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/loop.lux
index 6bb799c5e..012c47d7e 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/loop.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/loop.lux
@@ -20,9 +20,9 @@
["[1][0]" when]
["///[1]" ////
[synthesis (.only Scope Synthesis)]
+ ["[0]" phase]
["[1][0]" translation]
- ["//[1]" ///
- ["[1][0]" phase]
+ [///
[reference
[variable (.only Register)]]]]])
@@ -70,7 +70,7 @@
... true loop
_
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[@scope (of ! each ..@scope /////translation.next)
initsO+ (monad.each ! (expression archive) initsS+)
body! (/////translation.with_anchor [start @scope]
@@ -92,7 +92,7 @@
... true loop
_
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[loop! (scope! statement expression archive [start initsS+ bodyS])]
(in (_.apply (_.closure (list) loop!) (list))))))
@@ -101,7 +101,7 @@
(def .public (again! statement expression archive argsS+)
(Translator! (List Synthesis))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[[offset @scope] /////translation.anchor
argsO+ (monad.each ! (expression archive) argsS+)
$iteration (of ! each ..$iteration /////translation.next)]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
index 30ce82b9d..dbd9f5c45 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
@@ -28,10 +28,10 @@
["[0]" ///
["[1][0]" reference]
["//[1]" ///
+ ["[0]" phase]
["[1][0]" synthesis (.only Synthesis)]
["[1][0]" translation]
- ["//[1]" /// (.only)
- ["[1][0]" phase]
+ [///
[reference
[variable (.only Register)]]
[meta
@@ -825,7 +825,7 @@
(def .public translate
(Operation [Registry Output])
- (do ///////phase.monad
+ (do phase.monad
[_ (/////translation.execute! ..full)
_ (/////translation.save! ..module_id {.#None} ..full)]
(in [(|> registry.empty
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/structure.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/structure.lux
index 32e0a9034..081afea98 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/structure.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/structure.lux
@@ -10,28 +10,27 @@
["[1][0]" runtime (.only Operation Phase Translator)]
["[1][0]" primitive]
["///[1]" ////
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[1][0]" synthesis (.only Synthesis)]
[analysis
- [complex (.only Variant Tuple)]]
- ["//[1]" /// (.only)
- ["[1][0]" phase (.use "[1]#[0]" monad)]]]])
+ [complex (.only Variant Tuple)]]]])
(def .public (tuple translate archive elemsS+)
(Translator (Tuple Synthesis))
(when elemsS+
{.#End}
- (///////phase#in //runtime.unit)
+ (phase#in //runtime.unit)
{.#Item singletonS {.#End}}
(translate archive singletonS)
_
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[elemsT+ (monad.each ! (translate archive) elemsS+)]
(in (_.array elemsT+)))))
(def .public (variant translate archive [lefts right? valueS])
(Translator (Variant Synthesis))
- (///////phase#each (//runtime.variant (_.i32 (.int lefts))
- (//runtime.flag right?))
- (translate archive valueS)))
+ (phase#each (//runtime.variant (_.i32 (.int lefts))
+ (//runtime.flag right?))
+ (translate archive valueS)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/when.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/when.lux
index ff635a3de..a8fc6674f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/when.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/when.lux
@@ -27,13 +27,13 @@
["[1][0]" synthesis
["[1]/[0]" when]]
["/[1]" //
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[1][0]" synthesis (.only Synthesis Path)
[access
["[0]" member (.only Member)]]]
["//[1]" ///
[reference
[variable (.only Register)]]
- ["[1][0]" phase (.use "[1]#[0]" monad)]
[meta
[archive (.only Archive)]]]]]]])
@@ -43,7 +43,7 @@
(def .public (exec expression archive [this that])
(Translator [Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[this (expression archive this)
that (expression archive that)]
(in (|> (_.array (list this that))
@@ -51,7 +51,7 @@
(def .public (exec! statement expression archive [this that])
(Translator! [Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[this (expression archive this)
that (statement expression archive that)]
(in (all _.then
@@ -60,7 +60,7 @@
(def .public (let expression archive [valueS register bodyS])
(Translator [Synthesis Register Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)
bodyO (expression archive bodyS)]
... TODO: Find some way to do 'let' without paying the price of the closure.
@@ -70,7 +70,7 @@
(def .public (let! statement expression archive [valueS register bodyS])
(Translator! [Synthesis Register Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)
bodyO (statement expression archive bodyS)]
(in (all _.then
@@ -79,7 +79,7 @@
(def .public (if expression archive [testS thenS elseS])
(Translator [Synthesis Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[testO (expression archive testS)
thenO (expression archive thenS)
elseO (expression archive elseS)]
@@ -87,7 +87,7 @@
(def .public (if! statement expression archive [testS thenS elseS])
(Translator! [Synthesis Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[testO (expression archive testS)
thenO (statement expression archive thenS)
elseO (statement expression archive elseS)]
@@ -97,7 +97,7 @@
(def .public (get expression archive [pathP valueS])
(Translator [(List Member) Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
(.let [method (.if (the member.#right? side)
@@ -186,18 +186,18 @@
[(<simple> idx nextP)
(|> nextP
again
- (of ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))])
+ (of phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))])
([/////synthesis.simple_left_side ..left_choice]
[/////synthesis.simple_right_side ..right_choice])
(/////synthesis.member/left 0)
- (///////phase#in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))})
+ (phase#in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))})
... Extra optimization
(/////synthesis.path/seq
(/////synthesis.member/left 0)
(/////synthesis.!bind_top register thenP))
- (do ///////phase.monad
+ (do phase.monad
[then! (again thenP)]
(in {.#Some (all _.then
(_.define (..register register) (_.at (_.i32 +0) ..peek_cursor))
@@ -208,7 +208,7 @@
[(/////synthesis.path/seq
(<pm> lefts)
(/////synthesis.!bind_top register thenP))
- (do ///////phase.monad
+ (do phase.monad
[then! (again thenP)]
(in {.#Some (all _.then
(_.define (..register register) (<getter> (_.i32 (.int lefts)) ..peek_cursor))
@@ -217,7 +217,7 @@
[/////synthesis.member/right //runtime.tuple//right])
(/////synthesis.!bind_top register thenP)
- (do ///////phase.monad
+ (do phase.monad
[then! (again thenP)]
(in {.#Some (all _.then
(_.define (..register register) ..peek_and_pop_cursor)
@@ -225,20 +225,20 @@
(/////synthesis.!multi_pop nextP)
(.let [[extra_pops nextP'] (////synthesis/when.count_pops nextP)]
- (do ///////phase.monad
+ (do phase.monad
[next! (again nextP')]
(in {.#Some (all _.then
(multi_pop_cursor! (n.+ 2 extra_pops))
next!)})))
_
- (///////phase#in {.#None})))
+ (phase#in {.#None})))
(def (pattern_matching' statement expression archive)
(-> Phase! Phase Archive
(-> Path (Operation Statement)))
(function (again pathP)
- (do ///////phase.monad
+ (do phase.monad
[outcome (optimized_pattern_matching again pathP)]
(.when outcome
{.#Some outcome}
@@ -250,13 +250,13 @@
(statement expression archive bodyS)
{/////synthesis.#Pop}
- (///////phase#in pop_cursor!)
+ (phase#in pop_cursor!)
{/////synthesis.#Bind register}
- (///////phase#in (_.define (..register register) ..peek_cursor))
+ (phase#in (_.define (..register register) ..peek_cursor))
{/////synthesis.#Bit_Fork when thenP elseP}
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[then! (again thenP)
else! (.when elseP
{.#Some elseP}
@@ -273,7 +273,7 @@
then!))))
{/////synthesis.#I64_Fork item}
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
[then! (again then)]
@@ -288,7 +288,7 @@
(^.with_template [<tag> <format>]
[{<tag> item}
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[cases (monad.each ! (function (_ [match then])
(of ! each (|>> [(list (<format> match))]) (again then)))
{.#Item item})]
@@ -300,19 +300,19 @@
(^.with_template [<complex> <choice>]
[(<complex> idx)
- (///////phase#in (<choice> false idx))])
+ (phase#in (<choice> false idx))])
([/////synthesis.side/left ..left_choice]
[/////synthesis.side/right ..right_choice])
(^.with_template [<pm> <getter>]
[(<pm> lefts)
- (///////phase#in (push_cursor! (<getter> (_.i32 (.int lefts)) ..peek_cursor)))])
+ (phase#in (push_cursor! (<getter> (_.i32 (.int lefts)) ..peek_cursor)))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
(^.with_template [<tag> <combinator>]
[(<tag> leftP rightP)
- (do ///////phase.monad
+ (do phase.monad
[left! (again leftP)
right! (again rightP)]
(in (<combinator> left! right!)))])
@@ -321,7 +321,7 @@
(def (pattern_matching statement expression archive pathP)
(-> Phase! Phase Archive Path (Operation Statement))
- (do ///////phase.monad
+ (do phase.monad
[pattern_matching! (pattern_matching' statement expression archive pathP)]
(in (all _.then
(_.do_while (_.boolean false)
@@ -330,7 +330,7 @@
(def .public (when! statement expression archive [valueS pathP])
(Translator! [Synthesis Path])
- (do ///////phase.monad
+ (do phase.monad
[stack_init (expression archive valueS)
pattern_matching! (pattern_matching statement expression archive pathP)]
(in (all _.then
@@ -341,6 +341,6 @@
(def .public (when statement expression archive [valueS pathP])
(-> Phase! (Translator [Synthesis Path]))
- (do ///////phase.monad
+ (do phase.monad
[pattern_matching! (..when! statement expression archive [valueS pathP])]
(in (_.apply (_.closure (list) pattern_matching!) (list)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux
index 33135b11a..ec4ad62bf 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux
@@ -59,11 +59,11 @@
["[1][0]" reference]
[////
[analysis (.only Environment)]
+ ["[0]" phase]
["[0]" synthesis (.only Synthesis Abstraction Apply)]
["[0]" translation]
[///
["[0]" arity (.only Arity)]
- ["[0]" phase]
[meta
[archive
["[0]" unit]]]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/new.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/new.lux
index 822c3b9eb..5429d603f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/new.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/new.lux
@@ -39,9 +39,9 @@
[////
[analysis (.only Environment)]
[synthesis (.only Synthesis)]
+ ["[0]" phase]
[///
- ["[0]" arity (.only Arity)]
- ["[0]" phase]]]]]])
+ ["[0]" arity (.only Arity)]]]]]])
(def .public (instance' foreign_setup class environment arity)
(-> (List (Bytecode Any)) (Type Class) (Environment Synthesis) Arity (Bytecode Any))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/loop.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/loop.lux
index edfc2c7d7..98a58a08d 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/loop.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/loop.lux
@@ -20,10 +20,10 @@
["[1][0]" runtime (.only Operation Phase Translator)]
["[1][0]" value]
[////
+ ["[0]" phase]
["[0]" synthesis (.only Path Synthesis)]
["[0]" translation]
[///
- ["[0]" phase]
[reference
[variable (.only Register)]]]]])
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux
index beb60ebc4..ac72e04a1 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux
@@ -19,9 +19,9 @@
["[1][0]" type]
["//[1]" ///
[//
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[0]" translation]
[///
- ["[1]" phase (.use "operation#[0]" monad)]
[reference
["[0]" variable (.only Register Variable)]]
[meta
@@ -42,7 +42,7 @@
(def (foreign archive variable)
(-> Archive Register (Operation (Bytecode Any)))
- (do [! ////.monad]
+ (do [! phase.monad]
[bytecode_name (of ! each //runtime.class_name
(translation.context archive))]
(in (all _.composite
@@ -55,14 +55,14 @@
(-> Archive Variable (Operation (Bytecode Any)))
(when variable
{variable.#Local variable}
- (operation#in (_.aload variable))
+ (phase#in (_.aload variable))
{variable.#Foreign variable}
(..foreign archive variable)))
(def .public (constant archive name)
(-> Archive Symbol (Operation (Bytecode Any)))
- (do ////.monad
+ (do phase.monad
[[@definition |abstraction|] (translation.definition archive name)
.let [:definition: (type.class (//runtime.class_name @definition) (list))]]
(in (when |abstraction|
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 6e2414d50..b0273f3f3 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
@@ -49,10 +49,10 @@
["[1]/[0]" count]]]]
["//[1]" ///
[//
+ ["[0]" phase]
["[0]" synthesis]
["[0]" translation]
[///
- ["[1]" phase]
[arity (.only Arity)]
[reference
[variable (.only Register)]]
@@ -587,7 +587,7 @@
..try::method
..throw::method))
(list)))]
- (do ////.monad
+ (do phase.monad
[_ (translation.execute! [class bytecode])
_ (translation.save! ..artifact_id {.#None} [class bytecode])]
(in [..artifact_id {.#None} bytecode]))))
@@ -649,7 +649,7 @@
(list partial_count)
(list.partial <init>::method apply::method+)
(list)))]
- (do ////.monad
+ (do phase.monad
[_ (translation.execute! [class bytecode])
... _ (translation.save! //function.artifact_id {.#None} [class bytecode])
]
@@ -657,7 +657,7 @@
(def .public translate
(Operation [Registry Output])
- (do ////.monad
+ (do phase.monad
[runtime_payload ..translate_runtime
... _ ..translate_function
]
@@ -677,4 +677,4 @@
... This shift is done to avoid the possibility of forged labels
... to be in the range of the labels that are generated automatically
... during the evaluation of Bytecode expressions.
- (of ////.monad each (|>> ++ (i64.left_shifted shift)) translation.next)))
+ (of phase.monad each (|>> ++ (i64.left_shifted shift)) translation.next)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/structure.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/structure.lux
index 502fcdd3c..d9bca3484 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/structure.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/structure.lux
@@ -23,11 +23,10 @@
["[1][0]" runtime (.only Operation Phase Translator)]
["[1][0]" primitive]
["///[1]" ////
+ ["[0]" phase]
["[1][0]" synthesis (.only Synthesis)]
[analysis
- [complex (.only Variant Tuple)]]
- [///
- ["[0]" phase]]]])
+ [complex (.only Variant Tuple)]]]])
(def .public (tuple phase archive membersS)
(Translator (Tuple Synthesis))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/when.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/when.lux
index 9601f8751..4be90b358 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/when.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/when.lux
@@ -31,12 +31,12 @@
["[1][0]" value]
["[1][0]" structure]
[////
+ ["[0]" phase (.use "operation#[0]" monad)]
["[0]" translation]
["[0]" synthesis (.only Path Fork Synthesis)
[access
["[0]" member (.only Member)]]]
[///
- ["[0]" phase (.use "operation#[0]" monad)]
[reference
[variable (.only Register)]]]]])
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/function.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/function.lux
index 66e19f510..8a0b43ac5 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/function.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/function.lux
@@ -21,10 +21,10 @@
["//[1]" ///
[analysis (.only Abstraction Reification Analysis)]
[synthesis (.only Synthesis)]
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[1][0]" translation]
["//[1]" ///
[arity (.only Arity)]
- ["[1][0]" phase (.use "[1]#[0]" monad)]
[meta
[archive
["[0]" unit]]
@@ -36,7 +36,7 @@
(def .public (apply expression archive [functionS argsS+])
(Translator (Reification Synthesis))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[functionO (expression archive functionS)
argsO+ (monad.each ! (expression archive) argsS+)]
(in (_.apply argsO+ functionO))))
@@ -70,7 +70,7 @@
(def .public (function statement expression archive [environment arity bodyS])
(-> Phase! (Translator (Abstraction Synthesis)))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[dependencies (cache.dependencies archive bodyS)
[function_name body!] (/////translation.with_new_context archive dependencies
(do !
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/loop.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/loop.lux
index e5c201528..6b008d307 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/loop.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/loop.lux
@@ -22,10 +22,10 @@
["/[1]" //
["[1][0]" reference]
["//[1]" ///
- ["[0]"synthesis (.only Scope Synthesis)]
+ ["[0]" phase]
+ ["[0]" synthesis (.only Scope Synthesis)]
["[1][0]" translation]
["//[1]" ///
- ["[1][0]" phase]
[meta
[archive (.only Archive)]
["[0]" cache
@@ -60,11 +60,11 @@
{.#End}
(|> bodyS
(statement expression archive)
- (of ///////phase.monad each (|>> [(list)])))
+ (of phase.monad each (|>> [(list)])))
... true loop
_
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[@scope (of ! each ..@scope /////translation.next)
initsO+ (monad.each ! (expression archive) initsS+)
body! (/////translation.with_anchor [start @scope]
@@ -84,7 +84,7 @@
... true loop
_
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[dependencies (cache.dependencies archive bodyS)
[[artifact_module artifact_id] [initsO+ scope!]] (/////translation.with_new_context archive dependencies
(scope! statement expression archive true [start initsS+ bodyS]))
@@ -118,7 +118,7 @@
(def .public (again! statement expression archive argsS+)
(Translator! (List Synthesis))
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[[offset @scope] /////translation.anchor
argsO+ (monad.each ! (expression archive) argsS+)]
(in (..setup false offset argsO+ false (_.go_to @scope)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/runtime.lux
index f3089d34f..2ff224e3b 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/runtime.lux
@@ -28,10 +28,10 @@
["[0]" ///
["[1][0]" reference]
["//[1]" ///
+ ["[0]" phase]
["[1][0]" synthesis (.only Synthesis)]
["[1][0]" translation]
["//[1]" /// (.only)
- ["[1][0]" phase]
[reference
[variable (.only Register)]]
[meta
@@ -448,7 +448,7 @@
(def .public translate
(Operation [Registry Output])
- (do ///////phase.monad
+ (do phase.monad
[_ (/////translation.execute! ..full)
_ (/////translation.save! ..module_id {.#None} ..full)]
(in [(|> registry.empty
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/structure.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/structure.lux
index 9d8068bde..a15f0833a 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/structure.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/structure.lux
@@ -10,27 +10,26 @@
["[1][0]" runtime (.only Operation Phase Translator)]
["[1][0]" primitive]
["///[1]" ////
+ ["[0]" phase (.use "[1]#[0]" monad)]
["[1][0]" synthesis (.only Synthesis)]
[analysis
- [complex (.only Variant Tuple)]]
- ["//[1]" ///
- ["[1][0]" phase (.use "[1]#[0]" monad)]]]])
+ [complex (.only Variant Tuple)]]]])
(def .public (tuple phase archive elemsS+)
(Translator (Tuple Synthesis))
(when elemsS+
{.#End}
- (///////phase#in (//primitive.text /////synthesis.unit))
+ (phase#in (//primitive.text /////synthesis.unit))
{.#Item singletonS {.#End}}
(phase archive singletonS)
_
(|> elemsS+
- (monad.each ///////phase.monad (phase archive))
- (///////phase#each _.array))))
+ (monad.each phase.monad (phase archive))
+ (phase#each _.array))))
(def .public (variant phase archive [lefts right? valueS])
(Translator (Variant Synthesis))
- (///////phase#each (//runtime.variant lefts right?)
- (phase archive valueS)))
+ (phase#each (//runtime.variant lefts right?)
+ (phase archive valueS)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/when.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/when.lux
index 5d8f9546d..1bb6d979f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/when.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/lua/when.lux
@@ -24,14 +24,14 @@
["[1][0]" synthesis
["[1]/[0]" when]]
["/[1]" //
+ ["[0]" phase (.use "[1]#[0]" monad)]
+ ["[1][0]" translation]
["[1][0]" synthesis (.only Synthesis Path)
[access
["[0]" member (.only Member)]]]
- ["[1][0]" translation]
["//[1]" ///
[reference
["[1][0]" variable (.only Register)]]
- ["[1][0]" phase (.use "[1]#[0]" monad)]
[meta
[archive (.only Archive)]]]]]]])
@@ -45,7 +45,7 @@
(def .public (exec expression archive [this that])
(Translator [Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[this (expression archive this)
that (expression archive that)]
(in (|> (_.array (list this that))
@@ -53,7 +53,7 @@
(def .public (exec! statement expression archive [this that])
(Translator! [Synthesis Synthesis])
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[this (expression archive this)
that (statement expression archive that)
$dummy (of ! each _.var (/////translation.symbol "_exec"))]
@@ -63,7 +63,7 @@
(def .public (let expression archive [valueS register bodyS])
(Translator [Synthesis Register Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)
bodyO (expression archive bodyS)]
... TODO: Find some way to do 'let' without paying the price of the closure.
@@ -74,7 +74,7 @@
(def .public (let! statement expression archive [valueS register bodyS])
(Translator! [Synthesis Register Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)
bodyO (statement expression archive bodyS)]
(in (all _.then
@@ -83,7 +83,7 @@
(def .public (get expression archive [pathP valueS])
(Translator [(List Member) Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
(.let [method (.if (the member.#right? side)
@@ -95,7 +95,7 @@
(def .public (if expression archive [testS thenS elseS])
(Translator [Synthesis Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[testO (expression archive testS)
thenO (expression archive thenS)
elseO (expression archive elseS)]
@@ -107,7 +107,7 @@
(def .public (if! statement expression archive [testS thenS elseS])
(Translator! [Synthesis Synthesis Synthesis])
- (do ///////phase.monad
+ (do phase.monad
[testO (expression archive testS)
thenO (statement expression archive thenS)
elseO (statement expression archive elseS)]
@@ -188,13 +188,13 @@
(statement expression archive bodyS)
{/////synthesis.#Pop}
- (///////phase#in ..pop!)
+ (phase#in ..pop!)
{/////synthesis.#Bind register}
- (///////phase#in (_.local/1 (..register register) ..peek))
+ (phase#in (_.local/1 (..register register) ..peek))
{/////synthesis.#Bit_Fork when thenP elseP}
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[then! (again thenP)
else! (.when elseP
{.#Some elseP}
@@ -212,7 +212,7 @@
(^.with_template [<tag> <format>]
[{<tag> item}
- (do [! ///////phase.monad]
+ (do [! phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
[then! (again then)]
@@ -230,32 +230,32 @@
(^.with_template [<complex> <simple> <choice>]
[(<complex> idx)
- (///////phase#in (<choice> false idx))
+ (phase#in (<choice> false idx))
(<simple> idx nextP)
- (///////phase#each (_.then (<choice> true idx)) (again nextP))])
+ (phase#each (_.then (<choice> true idx)) (again nextP))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
(/////synthesis.member/left 0)
- (///////phase#in (|> ..peek (_.item (_.int +1)) ..push!))
+ (phase#in (|> ..peek (_.item (_.int +1)) ..push!))
(^.with_template [<pm> <getter>]
[(<pm> lefts)
- (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
+ (phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
(/////synthesis.!bind_top register thenP)
- (do ///////phase.monad
+ (do phase.monad
[then! (again thenP)]
- (///////phase#in (all _.then
- (_.local/1 (..register register) ..peek_and_pop)
- then!)))
+ (phase#in (all _.then
+ (_.local/1 (..register register) ..peek_and_pop)
+ then!)))
(^.with_template [<tag> <combinator>]
[(<tag> preP postP)
- (do ///////phase.monad
+ (do phase.monad
[pre! (again preP)
post! (again postP)]
(in (<combinator> pre! post!)))])
@@ -264,7 +264,7 @@
(def (pattern_matching statement expression archive pathP)
(-> Phase! Phase Archive Path (Operation Statement))
- (do ///////phase.monad
+ (do phase.monad
[pattern_matching! (pattern_matching' statement expression archive pathP)]
(in (all _.then
(_.while (_.boolean true)
@@ -286,7 +286,7 @@
(def .public (when! statement expression archive [valueS pathP])
(Translator! [Synthesis Path])
- (do ///////phase.monad
+ (do phase.monad
[stack_init (expression archive valueS)
pattern_matching! (pattern_matching statement expression archive pathP)]
(in (all _.then
@@ -299,6 +299,6 @@
(-> Phase! (Translator [Synthesis Path]))
(|> [valueS pathP]
(..when! statement expression archive)
- (of ///////phase.monad each
+ (of phase.monad each
(|>> (_.closure (list))
(_.apply (list))))))
diff --git a/stdlib/source/library/lux/world/finance/market/analysis/accumulation_distribution.lux b/stdlib/source/library/lux/world/finance/market/analysis/accumulation_distribution.lux
new file mode 100644
index 000000000..59fe58faf
--- /dev/null
+++ b/stdlib/source/library/lux/world/finance/market/analysis/accumulation_distribution.lux
@@ -0,0 +1,23 @@
+... https://en.wikipedia.org/wiki/Accumulation/distribution_index
+(.require
+ [library
+ [lux (.except)
+ [math
+ [number
+ ["n" nat]
+ ["f" frac]]]]]
+ [////
+ ["[0]" money]
+ [trade
+ ["[0]" session (.only Session)]]])
+
+(def .public (oscillation it)
+ (All (_ $)
+ (-> (Session $)
+ Frac))
+ (let [high (money.amount (the session.#high it))
+ low (money.amount (the session.#low it))
+ close (money.amount (the session.#close it))]
+ (f./ (n.frac (n.- low high))
+ (n.frac (n.- (n.- close high)
+ (n.- low close))))))