aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/lux.lux4
-rw-r--r--stdlib/source/test/lux/abstract/comonad.lux44
-rw-r--r--stdlib/source/test/lux/abstract/comonad/free.lux6
-rw-r--r--stdlib/source/test/lux/abstract/monad.lux63
-rw-r--r--stdlib/source/test/lux/abstract/monad/free.lux13
-rw-r--r--stdlib/source/test/lux/control/concurrency/async.lux9
-rw-r--r--stdlib/source/test/lux/control/concurrency/csp.lux9
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux9
-rw-r--r--stdlib/source/test/lux/control/concurrency/incremental.lux4
-rw-r--r--stdlib/source/test/lux/control/concurrency/stm.lux9
-rw-r--r--stdlib/source/test/lux/control/concurrency/structured.lux9
-rw-r--r--stdlib/source/test/lux/control/continuation.lux9
-rw-r--r--stdlib/source/test/lux/control/function/trampoline.lux9
-rw-r--r--stdlib/source/test/lux/control/io.lux9
-rw-r--r--stdlib/source/test/lux/control/lazy.lux6
-rw-r--r--stdlib/source/test/lux/control/maybe.lux8
-rw-r--r--stdlib/source/test/lux/control/parser.lux9
-rw-r--r--stdlib/source/test/lux/control/reader.lux9
-rw-r--r--stdlib/source/test/lux/control/region.lux9
-rw-r--r--stdlib/source/test/lux/control/security/policy.lux9
-rw-r--r--stdlib/source/test/lux/control/state.lux12
-rw-r--r--stdlib/source/test/lux/control/thread.lux9
-rw-r--r--stdlib/source/test/lux/control/try.lux6
-rw-r--r--stdlib/source/test/lux/control/writer.lux9
-rw-r--r--stdlib/source/test/lux/data/collection/list.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/sequence.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/stream.lux6
-rw-r--r--stdlib/source/test/lux/data/collection/tree/zipper.lux7
-rw-r--r--stdlib/source/test/lux/data/color/cmyk.lux15
-rw-r--r--stdlib/source/test/lux/data/color/hsb.lux15
-rw-r--r--stdlib/source/test/lux/data/color/hsl.lux15
-rw-r--r--stdlib/source/test/lux/data/identity.lux12
-rw-r--r--stdlib/source/test/lux/math/random.lux9
-rw-r--r--stdlib/source/test/lux/meta.lux284
-rw-r--r--stdlib/source/test/lux/meta/compiler/language/lux.lux15
-rw-r--r--stdlib/source/test/lux/meta/compiler/language/lux/phase.lux (renamed from stdlib/source/test/lux/meta/compiler/phase.lux)18
-rw-r--r--stdlib/source/test/lux/meta/compiler/language/lux/translation.lux76
-rw-r--r--stdlib/source/test/lux/meta/type/check.lux9
-rw-r--r--stdlib/source/test/lux/world.lux4
-rw-r--r--stdlib/source/test/lux/world/finance/market/analysis/accumulation_distribution.lux2
-rw-r--r--stdlib/source/test/lux/world/finance/market/analysis/pivot_point.lux40
-rw-r--r--stdlib/source/test/lux/world/finance/money.lux19
-rw-r--r--stdlib/source/test/lux/world/finance/trade/session.lux18
43 files changed, 538 insertions, 334 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index 068727e9f..bda6c17fc 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -6,6 +6,7 @@
[monad (.only do)]]
[control
["[0]" io]
+ ["[0]" try]
["[0]" maybe (.use "[1]#[0]" functor)]
[concurrency
["[0]" atom (.only Atom)]]]
@@ -567,7 +568,8 @@
.let [existential_type (of ! each (|>> {.#Ex}) random.nat)]
expected/0 existential_type
expected/1 existential_type]
- (<| (_.for [/.Type])
+ (<| (_.for [/.Type
+ /.#Nominal /.#Sum /.#Product /.#Function /.#Parameter /.#Var /.#Ex /.#UnivQ /.#ExQ /.#Apply /.#Named])
(all _.and
(_.coverage [/.is]
(|> expected
diff --git a/stdlib/source/test/lux/abstract/comonad.lux b/stdlib/source/test/lux/abstract/comonad.lux
index 1ffb461c8..69a5699f7 100644
--- a/stdlib/source/test/lux/abstract/comonad.lux
+++ b/stdlib/source/test/lux/abstract/comonad.lux
@@ -2,7 +2,9 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]]
+ [monad (.only do)]
+ ["[0]" functor
+ ["[1]T" \\test (.only Injection Comparison)]]]
[data
["[0]" identity (.only Identity)]]
[math
@@ -27,3 +29,43 @@
[value (out sample)]
(out (++ value))))))
))))
+
+(def .public (spec injection comparison it)
+ (All (_ !)
+ (-> (Injection !) (Comparison !) (/.CoMonad !)
+ Test))
+ (<| (_.for [/.CoMonad])
+ (do [! random.monad]
+ [.let [(open "/#[0]") it]
+ sample random.nat
+ increase (of ! each (function (_ diff)
+ (|>> /#out (n.+ diff)))
+ random.nat)
+ decrease (of ! each (function (_ diff)
+ (|>> /#out (n.- diff)))
+ random.nat)
+ morphism (of ! each (function (_ diff)
+ (|>> /#out (n.+ diff)))
+ random.nat)
+ .let [start (injection sample)
+ == (comparison n.=)]])
+ (all _.and
+ (_.for [/.functor]
+ (functorT.spec injection comparison (the /.functor it)))
+
+ (_.coverage [/.disjoint /.out]
+ (let [left_identity!
+ (n.= (morphism start)
+ (|> start /#disjoint (/#each morphism) /#out))
+
+ right_identity!
+ (== start
+ (|> start /#disjoint (/#each /#out)))
+
+ associativity!
+ (== (|> start /#disjoint (/#each (|>> /#disjoint (/#each increase) decrease)))
+ (|> start /#disjoint (/#each increase) /#disjoint (/#each decrease)))]
+ (and left_identity!
+ right_identity!
+ associativity!)))
+ )))
diff --git a/stdlib/source/test/lux/abstract/comonad/free.lux b/stdlib/source/test/lux/abstract/comonad/free.lux
index 8e9d67122..10cd3ac24 100644
--- a/stdlib/source/test/lux/abstract/comonad/free.lux
+++ b/stdlib/source/test/lux/abstract/comonad/free.lux
@@ -5,8 +5,8 @@
[comonad (.only CoMonad)]
["[0]" functor (.only Functor)
["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" comonad]]]
+ ["[0]" comonad
+ ["[1]T" \\test]]]
[control
["//" continuation]]
[data
@@ -47,6 +47,6 @@
(functorT.spec ..injection ..comparison (is (Functor (/.Free Stream))
(/.functor stream.functor))))
(_.for [/.comonad]
- ($comonad.spec ..injection ..comparison (is (CoMonad (/.Free Stream))
+ (comonadT.spec ..injection ..comparison (is (CoMonad (/.Free Stream))
(/.comonad stream.functor))))
)))
diff --git a/stdlib/source/test/lux/abstract/monad.lux b/stdlib/source/test/lux/abstract/monad.lux
index e35a07a2a..5cf985999 100644
--- a/stdlib/source/test/lux/abstract/monad.lux
+++ b/stdlib/source/test/lux/abstract/monad.lux
@@ -1,6 +1,9 @@
(.require
[library
[lux (.except)
+ [abstract
+ [functor
+ [\\test (.only Injection Comparison)]]]
[data
["[0]" identity (.only Identity)]
[collection
@@ -12,11 +15,65 @@
[test
["_" property (.only Test)]]]]
[\\library
- ["[0]" / (.only Monad do)]]
+ ["[0]" / (.only do)
+ ["[0]" free]]]
["[0]" /
["[1][0]" free]
["[1][0]" indexed]])
+(def (left_identity injection comparison (open "_//[0]"))
+ (All (_ !)
+ (-> (Injection !) (Comparison !) (/.Monad !)
+ Test))
+ (do [! random.monad]
+ [sample random.nat
+ morphism (of ! each (function (_ diff)
+ (|>> (n.+ diff) _//in))
+ random.nat)]
+ (_.test "Left identity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each morphism) _//conjoint)
+ (morphism sample)))))
+
+(def (right_identity injection comparison (open "_//[0]"))
+ (All (_ !)
+ (-> (Injection !) (Comparison !) (/.Monad !)
+ Test))
+ (do random.monad
+ [sample random.nat]
+ (_.test "Right identity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each _//in) _//conjoint)
+ (injection sample)))))
+
+(def (associativity injection comparison (open "_//[0]"))
+ (All (_ !)
+ (-> (Injection !) (Comparison !) (/.Monad !)
+ Test))
+ (do [! random.monad]
+ [sample random.nat
+ increase (of ! each (function (_ diff)
+ (|>> (n.+ diff) _//in))
+ random.nat)
+ decrease (of ! each (function (_ diff)
+ (|>> (n.- diff) _//in))
+ random.nat)]
+ (_.test "Associativity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint)
+ (|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint)))))
+
+(def .public (spec injection comparison monad)
+ (All (_ !)
+ (-> (Injection !) (Comparison !) (/.Monad !)
+ Test))
+ (<| (_.for [/.Monad])
+ (all _.and
+ (..left_identity injection comparison monad)
+ (..right_identity injection comparison monad)
+ (..associativity injection comparison monad)
+ )))
+
(def .public test
Test
(do random.monad
@@ -67,5 +124,9 @@
(is (Identity Nat)))))
/free.test
+ (_.for [free.monad]
+ (..spec /free.injection /free.comparison (is (/.Monad (free.Free List))
+ (free.monad list.functor))))
+
/indexed.test
))))
diff --git a/stdlib/source/test/lux/abstract/monad/free.lux b/stdlib/source/test/lux/abstract/monad/free.lux
index 5d786ae19..760acc2aa 100644
--- a/stdlib/source/test/lux/abstract/monad/free.lux
+++ b/stdlib/source/test/lux/abstract/monad/free.lux
@@ -4,13 +4,11 @@
[abstract
[functor (.only Functor)]
[apply (.only Apply)]
- [monad (.only Monad do)]
+ ["[0]" monad (.only do)]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[data
[collection
["[0]" list (.use "[1]#[0]" functor)]]]
@@ -21,7 +19,7 @@
[\\library
["[0]" /]])
-(def injection
+(def .public injection
(Injection (/.Free List))
(|>> {/.#Pure}))
@@ -36,7 +34,7 @@
(list#each interpret)
list.together)))
-(def comparison
+(def .public comparison
(Comparison (/.Free List))
(function (_ == left right)
(of (list.equivalence ==) =
@@ -54,7 +52,4 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison (is (Apply (/.Free List))
(/.apply list.functor))))
- (_.for [/.monad]
- ($monad.spec ..injection ..comparison (is (Monad (/.Free List))
- (/.monad list.functor))))
)))
diff --git a/stdlib/source/test/lux/control/concurrency/async.lux b/stdlib/source/test/lux/control/concurrency/async.lux
index 64bc1e119..efa1e26dc 100644
--- a/stdlib/source/test/lux/control/concurrency/async.lux
+++ b/stdlib/source/test/lux/control/concurrency/async.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" io]]
[math
@@ -70,7 +69,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(in (do /.monad
[.let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)]
diff --git a/stdlib/source/test/lux/control/concurrency/csp.lux b/stdlib/source/test/lux/control/concurrency/csp.lux
index 057ff60c8..682f36f73 100644
--- a/stdlib/source/test/lux/control/concurrency/csp.lux
+++ b/stdlib/source/test/lux/control/concurrency/csp.lux
@@ -2,11 +2,10 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
- ["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test (.only Injection Comparison)]]]
[control
["[0]" io]
["[0]" try]
@@ -51,7 +50,7 @@
(_.for [/.functor]
(functorT.spec ..injection ..comparison /.functor))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
))
(_.coverage [/.Channel /.Channel' /.Sink /.channel]
... This is already been tested for the FRP module.
diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux
index d2d43363c..92b484fbb 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" try]
["[0]" exception]
@@ -85,7 +84,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.Channel /.Sink /.channel]
(when (io.run!
diff --git a/stdlib/source/test/lux/control/concurrency/incremental.lux b/stdlib/source/test/lux/control/concurrency/incremental.lux
index 380da6f50..f66b872b3 100644
--- a/stdlib/source/test/lux/control/concurrency/incremental.lux
+++ b/stdlib/source/test/lux/control/concurrency/incremental.lux
@@ -4,9 +4,7 @@
[abstract
[monad (.only do)]
["[0]" functor
- ["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test (.only Injection Comparison)]]]
[control
["[0]" io]
["[0]" try]
diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux
index 1db0c216d..e3a4a6e81 100644
--- a/stdlib/source/test/lux/control/concurrency/stm.lux
+++ b/stdlib/source/test/lux/control/concurrency/stm.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- ["[0]" monad (.only Monad do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" io (.only IO)]]
[data
@@ -52,7 +51,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(in (do async.monad
[actual (/.commit! (of /.monad in expected))]
diff --git a/stdlib/source/test/lux/control/concurrency/structured.lux b/stdlib/source/test/lux/control/concurrency/structured.lux
index 93b62c414..206448d2f 100644
--- a/stdlib/source/test/lux/control/concurrency/structured.lux
+++ b/stdlib/source/test/lux/control/concurrency/structured.lux
@@ -2,11 +2,10 @@
[library
[lux (.except)
[abstract
- ["[0]" monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
- ["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test (.only Injection Comparison)]]]
[control
["[0]" maybe (.use "[1]#[0]" functor)]
["[0]" try]
@@ -75,7 +74,7 @@
(_.for [/.functor]
(functorT.spec ..injection ..comparison /.functor))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(in (do async.monad
[leftA (<| /.async
diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux
index 28f834949..1aea88eb9 100644
--- a/stdlib/source/test/lux/control/continuation.lux
+++ b/stdlib/source/test/lux/control/continuation.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[data
[collection
["[0]" list]]]
@@ -45,7 +44,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.result]
(n.= sample (/.result (_#in sample))))
diff --git a/stdlib/source/test/lux/control/function/trampoline.lux b/stdlib/source/test/lux/control/function/trampoline.lux
index c9ab584a4..23cc63862 100644
--- a/stdlib/source/test/lux/control/function/trampoline.lux
+++ b/stdlib/source/test/lux/control/function/trampoline.lux
@@ -2,11 +2,10 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
- ["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test (.only Injection Comparison)]]]
[math
["[0]" random]
[number
@@ -37,7 +36,7 @@
(_.for [/.functor]
(functorT.spec ..injection ..comparison /.functor))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.for [/.result]
(all _.and
diff --git a/stdlib/source/test/lux/control/io.lux b/stdlib/source/test/lux/control/io.lux
index b280ca903..28cf8b92c 100644
--- a/stdlib/source/test/lux/control/io.lux
+++ b/stdlib/source/test/lux/control/io.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[math
["[0]" random]
[number
@@ -42,7 +41,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.run! /.io]
(n.= sample
diff --git a/stdlib/source/test/lux/control/lazy.lux b/stdlib/source/test/lux/control/lazy.lux
index 9bb545a40..58ce73b97 100644
--- a/stdlib/source/test/lux/control/lazy.lux
+++ b/stdlib/source/test/lux/control/lazy.lux
@@ -2,13 +2,13 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
["[1]T" \\test]]
[\\specification
- ["$[0]" monad]
["$[0]" equivalence]]]
[data
["[0]" product]]
@@ -53,7 +53,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.lazy]
(let [lazy (/.lazy <eager>)
diff --git a/stdlib/source/test/lux/control/maybe.lux b/stdlib/source/test/lux/control/maybe.lux
index 0782a7ad2..afa6200aa 100644
--- a/stdlib/source/test/lux/control/maybe.lux
+++ b/stdlib/source/test/lux/control/maybe.lux
@@ -2,15 +2,15 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test]]
["[0]" apply
["[1]T" \\test]]
[\\specification
["$[0]" equivalence]
- ["$[0]" hash]
- ["$[0]" monad]]
+ ["$[0]" hash]]
["[0]" monoid
["[1]T" \\test]]]
[control
@@ -48,7 +48,7 @@
(_.for [/.apply]
(applyT.spec /#in /.equivalence /.apply))
(_.for [/.monad]
- ($monad.spec /#in /.equivalence /.monad))
+ (monadT.spec /#in /.equivalence /.monad))
(do random.monad
[left random.nat
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index 3b145cec8..83755d702 100644
--- a/stdlib/source/test/lux/control/parser.lux
+++ b/stdlib/source/test/lux/control/parser.lux
@@ -2,14 +2,13 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
[equivalence (.only Equivalence)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" try (.only Try)]]
[data
@@ -350,7 +349,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.result]
(|> (/.result (of /.monad in expected) (list))
diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux
index 7213c78aa..fddf9d51c 100644
--- a/stdlib/source/test/lux/control/reader.lux
+++ b/stdlib/source/test/lux/control/reader.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[math
["[0]" random]
[number
@@ -43,7 +42,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.result /.read]
(n.= sample
diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux
index 32eed407b..70d3873a1 100644
--- a/stdlib/source/test/lux/control/region.lux
+++ b/stdlib/source/test/lux/control/region.lux
@@ -5,14 +5,13 @@
[equivalence (.only Equivalence)]
[functor (.only Functor)]
[apply (.only Apply)]
- ["[0]" monad (.only Monad do)]
["[0]" enum]
+ ["[0]" monad (.only Monad do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" try (.only Try)]]
[data
@@ -94,7 +93,7 @@
(Apply (Region r (thread.Thread !))))
(/.apply thread.monad))))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison (is (All (_ ! r)
+ (monadT.spec ..injection ..comparison (is (All (_ ! r)
(Monad (Region r (thread.Thread !))))
(/.monad thread.monad))))
diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux
index 014ec5104..59f6968e3 100644
--- a/stdlib/source/test/lux/control/security/policy.lux
+++ b/stdlib/source/test/lux/control/security/policy.lux
@@ -3,13 +3,12 @@
[lux (.except)
[abstract
[hash (.only Hash)]
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[data
["[0]" text (.use "[1]#[0]" equivalence)]]
[math
@@ -91,7 +90,7 @@
(_.for [/.apply]
(applyT.spec (..injection (of policy_0 #can_upgrade)) (..comparison (of policy_0 #can_downgrade)) /.apply))
(_.for [/.monad]
- ($monad.spec (..injection (of policy_0 #can_upgrade)) (..comparison (of policy_0 #can_downgrade)) /.monad))))
+ (monadT.spec (..injection (of policy_0 #can_upgrade)) (..comparison (of policy_0 #can_downgrade)) /.monad))))
(_.coverage [/.Privilege /.Context /.with_policy]
(and (of policy_0 = password password)
diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux
index e66466eb0..90bcd3fef 100644
--- a/stdlib/source/test/lux/control/state.lux
+++ b/stdlib/source/test/lux/control/state.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" pipe]
["[0]" io]]
@@ -78,7 +77,7 @@
(_.for [/.apply]
(applyT.spec ..injection (..comparison state) /.apply))
(_.for [/.monad]
- ($monad.spec ..injection (..comparison state) /.monad))
+ (monadT.spec ..injection (..comparison state) /.monad))
)))
(def loops
@@ -130,4 +129,5 @@
..basics
..structures
..loops
- ..monad_transformer)))
+ ..monad_transformer
+ )))
diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux
index ac265c742..f396fd025 100644
--- a/stdlib/source/test/lux/control/thread.lux
+++ b/stdlib/source/test/lux/control/thread.lux
@@ -2,13 +2,12 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[math
["[0]" random]
[number
@@ -55,7 +54,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
))
(_.for [/.Box /.box]
diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux
index 159fcfd7f..c46699836 100644
--- a/stdlib/source/test/lux/control/try.lux
+++ b/stdlib/source/test/lux/control/try.lux
@@ -2,13 +2,13 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
["[1]T" \\test]]
[\\specification
- ["$[0]" monad]
["$[0]" equivalence]]]
[control
["[0]" pipe]
@@ -57,7 +57,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.coverage [/.trusted]
(n.= expected
diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux
index 288859d4a..43186db74 100644
--- a/stdlib/source/test/lux/control/writer.lux
+++ b/stdlib/source/test/lux/control/writer.lux
@@ -4,13 +4,12 @@
[abstract
[equivalence (.only Equivalence)]
[monoid (.only Monoid)]
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" io]]
[data
@@ -48,7 +47,7 @@
(_.for [/.apply]
(applyT.spec (..injection text.monoid) ..comparison (/.apply text.monoid)))
(_.for [/.monad]
- ($monad.spec (..injection text.monoid) ..comparison (/.monad text.monoid)))
+ (monadT.spec (..injection text.monoid) ..comparison (/.monad text.monoid)))
(_.coverage [/.write]
(text#= log
diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux
index cbcc11c3d..b73b76016 100644
--- a/stdlib/source/test/lux/data/collection/list.lux
+++ b/stdlib/source/test/lux/data/collection/list.lux
@@ -2,8 +2,9 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
["[0]" enum]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test]]
["[0]" apply
@@ -13,8 +14,7 @@
[\\specification
["$[0]" equivalence]
["$[0]" hash]
- ["$[0]" mix]
- ["$[0]" monad]]]
+ ["$[0]" mix]]]
[control
["[0]" pipe]
["[0]" io]
@@ -67,7 +67,7 @@
(_.for [/.apply]
(applyT.spec /#in /.equivalence /.apply))
(_.for [/.monad]
- ($monad.spec /#in /.equivalence /.monad))
+ (monadT.spec /#in /.equivalence /.monad))
(do [! random.monad]
[parameter random.nat
diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux
index b2033b46f..ee463e2f7 100644
--- a/stdlib/source/test/lux/data/collection/sequence.lux
+++ b/stdlib/source/test/lux/data/collection/sequence.lux
@@ -2,7 +2,8 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection)]]
["[0]" apply
@@ -11,8 +12,7 @@
["[1]T" \\test]]
[\\specification
["$[0]" equivalence]
- ["$[0]" mix]
- ["$[0]" monad]]]
+ ["$[0]" mix]]]
[control
["[0]" try (.only Try)]
["[0]" exception]]
@@ -47,7 +47,7 @@
(_.for [/.apply]
(applyT.spec /#in /.equivalence /.apply))
(_.for [/.monad]
- ($monad.spec /#in /.equivalence /.monad))
+ (monadT.spec /#in /.equivalence /.monad))
)))
(def whole
diff --git a/stdlib/source/test/lux/data/collection/stream.lux b/stdlib/source/test/lux/data/collection/stream.lux
index 75c03aa36..902ce58b8 100644
--- a/stdlib/source/test/lux/data/collection/stream.lux
+++ b/stdlib/source/test/lux/data/collection/stream.lux
@@ -7,8 +7,8 @@
["[0]" enum]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" comonad]]]
+ ["[0]" comonad
+ ["[1]T" \\test]]]
[data
["[0]" text (.only)
["%" \\format (.only format)]]
@@ -56,7 +56,7 @@
(_.for [/.functor]
(functorT.spec /.repeated ..equivalence /.functor))
(_.for [/.comonad]
- ($comonad.spec /.repeated ..equivalence /.comonad))
+ (comonadT.spec /.repeated ..equivalence /.comonad))
(_.coverage [/.item]
(n.= (n.+ offset index)
diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux
index 577862dc9..77d9209d8 100644
--- a/stdlib/source/test/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux
@@ -5,9 +5,10 @@
[monad (.only do)]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
+ ["[0]" comonad
+ ["[1]T" \\test]]
[\\specification
- ["$[0]" equivalence]
- ["$[0]" comonad]]]
+ ["$[0]" equivalence]]]
[control
["[0]" pipe]
["[0]" maybe (.use "[1]#[0]" functor)]]
@@ -170,7 +171,7 @@
(_.for [/.functor]
(functorT.spec (|>> tree.leaf /.zipper) /.equivalence /.functor))
(_.for [/.comonad]
- ($comonad.spec (|>> tree.leaf /.zipper) /.equivalence /.comonad))
+ (comonadT.spec (|>> tree.leaf /.zipper) /.equivalence /.comonad))
(_.coverage [/.zipper /.tree]
(|> sample /.zipper /.tree (tree#= sample)))
diff --git a/stdlib/source/test/lux/data/color/cmyk.lux b/stdlib/source/test/lux/data/color/cmyk.lux
index 8c852cd4c..2eda4d6a8 100644
--- a/stdlib/source/test/lux/data/color/cmyk.lux
+++ b/stdlib/source/test/lux/data/color/cmyk.lux
@@ -45,14 +45,15 @@
expected_rgb rgbT.random
expected_cmyk ..random
- possible_value random.frac])
+ possible_value random.frac
+ .let [delta +0.000000001]])
(all _.and
(_.for [/.Value]
(all _.and
(_.coverage [/.value?]
(and (/.value? expected_value)
- (not (/.value? (f.+ f.smallest /.most)))
- (not (/.value? (f.- f.smallest /.least)))))
+ (not (/.value? (f.+ delta /.most)))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.value]
(if (/.value? possible_value)
(|> possible_value
@@ -64,14 +65,14 @@
(and (f.< /.most
/.least)
(/.value? /.least)
- (/.value? (f.+ f.smallest /.least))
- (not (/.value? (f.- f.smallest /.least)))))
+ (/.value? (f.+ delta /.least))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.most]
(and (f.> /.least
/.most)
(/.value? /.most)
- (/.value? (f.- f.smallest /.most))
- (not (/.value? (f.+ f.smallest /.most)))))
+ (/.value? (f.- delta /.most))
+ (not (/.value? (f.+ delta /.most)))))
))
(_.for [/.CMYK
/.#cyan /.#magenta /.#yellow /.#key]
diff --git a/stdlib/source/test/lux/data/color/hsb.lux b/stdlib/source/test/lux/data/color/hsb.lux
index 2cb41fe7c..ee8d5f18a 100644
--- a/stdlib/source/test/lux/data/color/hsb.lux
+++ b/stdlib/source/test/lux/data/color/hsb.lux
@@ -38,14 +38,15 @@
expected_rgb rgbT.random
expected_hsb ..random
- possible_value random.frac])
+ possible_value random.frac
+ .let [delta +0.000000001]])
(all _.and
(_.for [/.Value]
(all _.and
(_.coverage [/.value?]
(and (/.value? expected_value)
- (not (/.value? (f.+ f.smallest /.most)))
- (not (/.value? (f.- f.smallest /.least)))))
+ (not (/.value? (f.+ delta /.most)))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.value]
(if (/.value? possible_value)
(|> possible_value
@@ -57,14 +58,14 @@
(and (f.< /.most
/.least)
(/.value? /.least)
- (/.value? (f.+ f.smallest /.least))
- (not (/.value? (f.- f.smallest /.least)))))
+ (/.value? (f.+ delta /.least))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.most]
(and (f.> /.least
/.most)
(/.value? /.most)
- (/.value? (f.- f.smallest /.most))
- (not (/.value? (f.+ f.smallest /.most)))))
+ (/.value? (f.- delta /.most))
+ (not (/.value? (f.+ delta /.most)))))
))
(_.for [/.HSB]
(all _.and
diff --git a/stdlib/source/test/lux/data/color/hsl.lux b/stdlib/source/test/lux/data/color/hsl.lux
index 8563aa77b..bbfd8f8da 100644
--- a/stdlib/source/test/lux/data/color/hsl.lux
+++ b/stdlib/source/test/lux/data/color/hsl.lux
@@ -49,14 +49,15 @@
((function (_ it)
(and (f.>= +0.25 it)
(f.<= +0.75 it)))))))
- ratio (|> random.safe_frac (random.only (f.>= +0.5)))])
+ ratio (|> random.safe_frac (random.only (f.>= +0.5)))
+ .let [delta +0.000000001]])
(all _.and
(_.for [/.Value]
(all _.and
(_.coverage [/.value?]
(and (/.value? expected_value)
- (not (/.value? (f.+ f.smallest /.most)))
- (not (/.value? (f.- f.smallest /.least)))))
+ (not (/.value? (f.+ delta /.most)))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.value]
(if (/.value? possible_value)
(|> possible_value
@@ -68,14 +69,14 @@
(and (f.< /.most
/.least)
(/.value? /.least)
- (/.value? (f.+ f.smallest /.least))
- (not (/.value? (f.- f.smallest /.least)))))
+ (/.value? (f.+ delta /.least))
+ (not (/.value? (f.- delta /.least)))))
(_.coverage [/.most]
(and (f.> /.least
/.most)
(/.value? /.most)
- (/.value? (f.- f.smallest /.most))
- (not (/.value? (f.+ f.smallest /.most)))))
+ (/.value? (f.- delta /.most))
+ (not (/.value? (f.+ delta /.most)))))
))
(_.for [/.HSL
/.#hue /.#saturation /.#luminance]
diff --git a/stdlib/source/test/lux/data/identity.lux b/stdlib/source/test/lux/data/identity.lux
index f18f69c41..5513d67d2 100644
--- a/stdlib/source/test/lux/data/identity.lux
+++ b/stdlib/source/test/lux/data/identity.lux
@@ -2,14 +2,14 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]
- ["$[0]" comonad]]]
+ ["[0]" comonad
+ ["[1]T" \\test]]]
[test
["_" property (.only Test)]]]]
[\\library
@@ -34,7 +34,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
(_.for [/.comonad]
- ($comonad.spec ..injection ..comparison /.comonad))
+ (comonadT.spec ..injection ..comparison /.comonad))
)))
diff --git a/stdlib/source/test/lux/math/random.lux b/stdlib/source/test/lux/math/random.lux
index 8f125bd7e..881e73235 100644
--- a/stdlib/source/test/lux/math/random.lux
+++ b/stdlib/source/test/lux/math/random.lux
@@ -3,13 +3,12 @@
[lux (.except)
[abstract
[equivalence (.only Equivalence)]
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" maybe]]
[data
@@ -86,7 +85,7 @@
(_.for [/.apply]
(applyT.spec ..injection (..comparison increase,seed) /.apply))
(_.for [/.monad]
- ($monad.spec ..injection (..comparison increase,seed) /.monad))
+ (monadT.spec ..injection (..comparison increase,seed) /.monad))
(_.coverage [/.result]
(|> (in true)
diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux
index 80f9231cf..8f693d82c 100644
--- a/stdlib/source/test/lux/meta.lux
+++ b/stdlib/source/test/lux/meta.lux
@@ -3,13 +3,12 @@
[lux (.except)
[abstract
[equivalence (.only Equivalence)]
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" maybe]
["[0]" try (.only Try) (.use "[1]#[0]" functor)]]
@@ -38,7 +37,7 @@
["[0]" type (.use "[1]#[0]" equivalence)]]]
["[0]" /
["[1][0]" code]
- ... ["[1][0]" location]
+ ["[1][0]" location]
... ["[1][0]" symbol]
... ["[1][0]" configuration]
... ["[1][0]" version]
@@ -59,16 +58,6 @@
... ["[1]/[0]" version]
... ["[1]/[0]" reference]
... ["[1]/[0]" phase]
- ... [language
- ... [lux
- ... ... ["[1]/[0]" syntax]
- ... ["[1]/[0]" analysis]
- ... ["[1]/[0]" synthesis]
- ... ["[1]/[0]" phase
- ... ["[1]/[0]" extension]
- ... ["[1]/[0]" analysis]
- ... ... ["[1]/[0]" synthesis]
- ... ]]]
... ["[1]/[0]" meta
... ["[1]/[0]" archive]
... ["[1]/[0]" cli]
@@ -703,6 +692,132 @@
alias!)))
)))
+(def locals_related
+ Test
+ (do [! random.monad]
+ [current_module (random.upper_cased 1)
+ [name_0 name_1 name_2 name_3 name_4] (|> (random.upper_cased 1)
+ (random.set text.hash 5)
+ (of ! each set.list)
+ (random.one (function (_ values)
+ (when values
+ (list name_0 name_1 name_2 name_3 name_4)
+ {.#Some [name_0 name_1 name_2 name_3 name_4]}
+
+ _
+ {.#None}))))
+ .let [type_0 {.#Nominal name_0 (list)}
+ type_1 {.#Nominal name_1 (list)}
+ type_2 {.#Nominal name_2 (list)}
+ type_3 {.#Nominal name_3 (list)}
+ type_4 {.#Nominal name_4 (list)}
+
+ globals (is (List [Text [Bit .Global]])
+ (list [name_4
+ [false {.#Definition [type_4 []]}]]))
+
+ scopes (list [.#scope_name (list)
+ .#inner_scopes 0
+ .#locals [.#counter 1
+ .#mappings (list [name_3 [type_3 3]])]
+ .#captured [.#counter 0
+ .#mappings (list)]]
+ [.#scope_name (list)
+ .#inner_scopes 0
+ .#locals [.#counter 2
+ .#mappings (list [name_1 [type_1 1]]
+ [name_2 [type_2 2]])]
+ .#captured [.#counter 0
+ .#mappings (list)]]
+ [.#scope_name (list)
+ .#inner_scopes 0
+ .#locals [.#counter 1
+ .#mappings (list [name_0 [type_0 0]])]
+ .#captured [.#counter 0
+ .#mappings (list)]])]
+ .let [expected_lux
+ (is Lux
+ [.#info [.#target ""
+ .#version ""
+ .#mode {.#Build}
+ .#configuration (list)]
+ .#source [location.dummy 0 ""]
+ .#location location.dummy
+ .#current_module {.#Some current_module}
+ .#modules (list [current_module
+ [.#module_hash 0
+ .#module_aliases (list)
+ .#definitions globals
+ .#imports (list)
+ .#module_state {.#Active}]])
+ .#scopes scopes
+ .#type_context [.#ex_counter 0
+ .#var_counter 0
+ .#var_bindings (list)]
+ .#expected {.#None}
+ .#seed 0
+ .#scope_type_vars (list)
+ .#extensions []
+ .#eval (as (-> Type Code (Meta Any)) [])
+ .#host []])]]
+ (all _.and
+ (_.coverage [.Scope /.locals]
+ (let [equivalence (is (Equivalence (List (List [Text Type])))
+ (list.equivalence
+ (list.equivalence
+ (product.equivalence
+ text.equivalence
+ type.equivalence))))]
+ (|> /.locals
+ (/.result expected_lux)
+ (try#each (of equivalence = (list (list [name_3 type_3])
+ (list [name_1 type_1]
+ [name_2 type_2]))))
+ (try.else false))))
+ (_.coverage [/.var_type]
+ (and (|> (/.var_type name_0)
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_0))
+ (try.else false))
+ (|> (/.var_type name_1)
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_1))
+ (try.else false))
+ (|> (/.var_type name_2)
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_2))
+ (try.else false))
+ (|> (/.var_type name_3)
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_3))
+ (try.else false))))
+ (_.coverage [/.type]
+ (and (|> (/.type ["" name_0])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_0))
+ (try.else false))
+ (|> (/.type ["" name_1])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_1))
+ (try.else false))
+ (|> (/.type ["" name_2])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_2))
+ (try.else false))
+ (|> (/.type ["" name_3])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_3))
+ (try.else false))
+ (|> (/.type [current_module name_4])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_4))
+ (try.else false))
+ (|> (/.type ["" name_4])
+ (/.result expected_lux)
+ (try#each (of type.equivalence = type_4))
+ (try.else false))))
+ )))
+
... (def label_related
... Test
... (do [! random.monad]
@@ -842,132 +957,6 @@
... ... )))))
... )))
-... (def locals_related
-... Test
-... (do [! random.monad]
-... [current_module (random.upper_cased 1)
-... [name_0 name_1 name_2 name_3 name_4] (|> (random.upper_cased 1)
-... (random.set text.hash 5)
-... (of ! each set.list)
-... (random.one (function (_ values)
-... (when values
-... (list name_0 name_1 name_2 name_3 name_4)
-... {.#Some [name_0 name_1 name_2 name_3 name_4]}
-
-... _
-... {.#None}))))
-... .let [type_0 {.#Nominal name_0 (list)}
-... type_1 {.#Nominal name_1 (list)}
-... type_2 {.#Nominal name_2 (list)}
-... type_3 {.#Nominal name_3 (list)}
-... type_4 {.#Nominal name_4 (list)}
-
-... globals (is (List [Text .Global])
-... (list [name_4
-... {.#Definition [false type_4 []]}]))
-
-... scopes (list [.#scope_name (list)
-... .#inner_scopes 0
-... .#locals [.#counter 1
-... .#mappings (list [name_3 [type_3 3]])]
-... .#captured [.#counter 0
-... .#mappings (list)]]
-... [.#scope_name (list)
-... .#inner_scopes 0
-... .#locals [.#counter 2
-... .#mappings (list [name_1 [type_1 1]]
-... [name_2 [type_2 2]])]
-... .#captured [.#counter 0
-... .#mappings (list)]]
-... [.#scope_name (list)
-... .#inner_scopes 0
-... .#locals [.#counter 1
-... .#mappings (list [name_0 [type_0 0]])]
-... .#captured [.#counter 0
-... .#mappings (list)]])]
-... .let [expected_lux
-... (is Lux
-... [.#info [.#target ""
-... .#version ""
-... .#mode {.#Build}
-... .#configuration (list)]
-... .#source [location.dummy 0 ""]
-... .#location location.dummy
-... .#current_module {.#Some current_module}
-... .#modules (list [current_module
-... [.#module_hash 0
-... .#module_aliases (list)
-... .#definitions globals
-... .#imports (list)
-... .#module_state {.#Active}]])
-... .#scopes scopes
-... .#type_context [.#ex_counter 0
-... .#var_counter 0
-... .#var_bindings (list)]
-... .#expected {.#None}
-... .#seed 0
-... .#scope_type_vars (list)
-... .#extensions []
-... .#eval (as (-> Type Code (Meta Any)) [])
-... .#host []])]]
-... (all _.and
-... (_.coverage [.Scope /.locals]
-... (let [equivalence (is (Equivalence (List (List [Text Type])))
-... (list.equivalence
-... (list.equivalence
-... (product.equivalence
-... text.equivalence
-... type.equivalence))))]
-... (|> /.locals
-... (/.result expected_lux)
-... (try#each (of equivalence = (list (list [name_3 type_3])
-... (list [name_1 type_1]
-... [name_2 type_2]))))
-... (try.else false))))
-... (_.coverage [/.var_type]
-... (and (|> (/.var_type name_0)
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_0))
-... (try.else false))
-... (|> (/.var_type name_1)
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_1))
-... (try.else false))
-... (|> (/.var_type name_2)
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_2))
-... (try.else false))
-... (|> (/.var_type name_3)
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_3))
-... (try.else false))))
-... (_.coverage [/.type]
-... (and (|> (/.type ["" name_0])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_0))
-... (try.else false))
-... (|> (/.type ["" name_1])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_1))
-... (try.else false))
-... (|> (/.type ["" name_2])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_2))
-... (try.else false))
-... (|> (/.type ["" name_3])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_3))
-... (try.else false))
-... (|> (/.type [current_module name_4])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_4))
-... (try.else false))
-... (|> (/.type ["" name_4])
-... (/.result expected_lux)
-... (try#each (of type.equivalence = type_4))
-... (try.else false))))
-... )))
-
(def injection
(Injection Meta)
(of /.monad in))
@@ -1028,7 +1017,7 @@
(_.for [/.apply]
(applyT.spec ..injection (..comparison expected_lux) /.apply))
(_.for [/.monad]
- ($monad.spec ..injection (..comparison expected_lux) /.monad))
+ (monadT.spec ..injection (..comparison expected_lux) /.monad))
(do random.monad
[expected_value random.nat
@@ -1056,13 +1045,13 @@
..context_related
..definition_related
..search_related
- ... ..locals_related
+ ..locals_related
... (_.for [.Label]
... ..label_related)
))
/code.test
- ... /location.test
+ /location.test
... /symbol.test
... /configuration.test
... /version.test
@@ -1083,17 +1072,10 @@
/compiler.test
... /compiler/version.test
... /compiler/reference.test
- ... /compiler/phase.test
- ... /compiler/analysis.test
- ... /compiler/synthesis.test
... /compiler/meta/archive.test
... /compiler/meta/cli.test
... /compiler/meta/export.test
... /compiler/meta/import.test
... /compiler/meta/context.test
... /compiler/meta/cache.test
- ... /compiler/phase/extension.test
- ... /compiler/phase/analysis.test
- ... ... /compiler/syntax.test
- ... ... /compiler/synthesis.test
)))))
diff --git a/stdlib/source/test/lux/meta/compiler/language/lux.lux b/stdlib/source/test/lux/meta/compiler/language/lux.lux
index ed26027df..0ff6e0b28 100644
--- a/stdlib/source/test/lux/meta/compiler/language/lux.lux
+++ b/stdlib/source/test/lux/meta/compiler/language/lux.lux
@@ -34,7 +34,17 @@
[test
["_" property (.only Test)]]]]
[\\library
- ["[0]" /]])
+ ["[0]" /]]
+ ["[0]" /
+ ... ["[1][0]" syntax]
+ ... ["[1][0]" analysis]
+ ... ["[1][0]" synthesis]
+ ["[1][0]" phase
+ ... ["[1][0]" extension]
+ ... ["[1][0]" analysis]
+ ... ["[1][0]" synthesis]
+ ]
+ ["[1][0]" translation]])
(def any_equivalence
(Equivalence Any)
@@ -125,4 +135,7 @@
[actual_module actual_short] (the signature.#name it)]
(and (text#= expected_module actual_module)))
(same? version.latest (the signature.#version it)))))
+
+ /phase.test
+ /translation.test
)))
diff --git a/stdlib/source/test/lux/meta/compiler/phase.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux
index 692058872..faf76b112 100644
--- a/stdlib/source/test/lux/meta/compiler/phase.lux
+++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux
@@ -2,11 +2,10 @@
[library
[lux (.except)
[abstract
- [monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
- ["[1]T" \\test (.only Injection Comparison)]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test (.only Injection Comparison)]]]
[control
["[0]" pipe]
["[0]" try (.use "[1]#[0]" functor)]
@@ -23,17 +22,20 @@
["_" property (.only Test)]]]]
[\\library
["[0]" / (.only)
- [//
+ [////
[meta
["[0]" archive]]]]])
(def (injection value)
- (All (_ s) (Injection (/.Operation s)))
+ (All (_ of)
+ (Injection (/.Operation of)))
(function (_ state)
{try.#Success [state value]}))
(def (comparison init)
- (All (_ s) (-> s (Comparison (/.Operation s))))
+ (All (_ of)
+ (-> of
+ (Comparison (/.Operation of))))
(function (_ == left right)
(when [(/.result init left)
(/.result init right)]
@@ -144,7 +146,7 @@
(_.for [/.functor]
(functorT.spec ..injection (..comparison state) /.functor))
(_.for [/.monad]
- ($monad.spec ..injection (..comparison state) /.monad))
+ (monadT.spec ..injection (..comparison state) /.monad))
(_.coverage [/.result]
(|> (of /.monad in expected)
diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux b/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux
new file mode 100644
index 000000000..8df8dbcbe
--- /dev/null
+++ b/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux
@@ -0,0 +1,76 @@
+(.require
+ [library
+ [lux (.except)
+ [abstract
+ [monad (.only do)]]
+ [control
+ ["[0]" try]]
+ [data
+ [collection
+ ["[0]" list]
+ ["[0]" sequence]]]
+ [math
+ ["[0]" random (.only Random)]
+ [number
+ ["n" nat]]]
+ [test
+ ["_" property (.only Test)]]]]
+ [\\library
+ ["[0]" / (.only)
+ [////
+ [meta
+ [archive
+ ["[0]" registry]]]]]])
+
+(def dummy_host
+ (/.Host Any Any)
+ (implementation
+ (def (evaluate _ _)
+ {try.#Failure ""})
+ (def (execute _)
+ {try.#Failure ""})
+ (def (define _ _ _)
+ {try.#Failure ""})
+
+ (def (ingest _ _)
+ [])
+ (def (re_learn _ _ _)
+ {try.#Failure ""})
+ (def (re_load _ _ _)
+ {try.#Failure ""})))
+
+(def .public test
+ Test
+ (<| (_.covering /._)
+ (do [! random.monad]
+ [expected_module (random.lower_cased 1)])
+ (all _.and
+ (_.coverage [/.Host]
+ true)
+ (_.coverage [/.Operation /.Phase]
+ true)
+ (_.for [/.State
+ /.#module /.#anchor /.#host /.#buffer
+ /.#registry /.#registry_shift
+ /.#counter /.#context /.#log /.#interim_artifacts]
+ (all _.and
+ (_.coverage [/.state]
+ (let [it (is (/.State Any Any Any)
+ (/.state ..dummy_host expected_module))]
+ (and (same? expected_module (the /.#module it))
+ (when (the /.#anchor it) {.#None} true _ false)
+ (same? ..dummy_host (the /.#host it))
+ (when (the /.#buffer it) {.#None} true _ false)
+ (same? registry.empty (the /.#registry it))
+ (n.= 0 (the /.#registry_shift it))
+ (n.= 0 (the /.#counter it))
+ (when (the /.#context it) {.#None} true _ false)
+ (sequence.empty? (the /.#log it))
+ (list.empty? (the /.#interim_artifacts it)))))
+ ))
+ (_.for [/.Buffer]
+ (all _.and
+ (_.coverage [/.empty_buffer]
+ (sequence.empty? /.empty_buffer))
+ ))
+ )))
diff --git a/stdlib/source/test/lux/meta/type/check.lux b/stdlib/source/test/lux/meta/type/check.lux
index 18aef928a..bd41c0de7 100644
--- a/stdlib/source/test/lux/meta/type/check.lux
+++ b/stdlib/source/test/lux/meta/type/check.lux
@@ -2,13 +2,12 @@
[library
[lux (.except symbol type)
[abstract
- ["[0]" monad (.only do)]
+ ["[0]" monad (.only do)
+ ["[1]T" \\test]]
["[0]" functor
["[1]T" \\test (.only Injection Comparison)]]
["[0]" apply
- ["[1]T" \\test]]
- [\\specification
- ["$[0]" monad]]]
+ ["[1]T" \\test]]]
[control
["[0]" pipe]
["[0]" function]
@@ -117,7 +116,7 @@
(_.for [/.apply]
(applyT.spec ..injection ..comparison /.apply))
(_.for [/.monad]
- ($monad.spec ..injection ..comparison /.monad))
+ (monadT.spec ..injection ..comparison /.monad))
))
(def (nominal_type parameters)
diff --git a/stdlib/source/test/lux/world.lux b/stdlib/source/test/lux/world.lux
index e4f9f5cec..2832e94be 100644
--- a/stdlib/source/test/lux/world.lux
+++ b/stdlib/source/test/lux/world.lux
@@ -20,7 +20,8 @@
["[1]/[0]" market
["[1]/[0]" price]
["[1]/[0]" analysis
- ["[1]/[0]" accumulation_distribution]]]]
+ ["[1]/[0]" accumulation_distribution]
+ ["[1]/[0]" pivot_point]]]]
["[1][0]" net]
["[1][0]" time]
["[1][0]" locale]
@@ -41,6 +42,7 @@
/finance/trade/session.test
/finance/market/price.test
/finance/market/analysis/accumulation_distribution.test
+ /finance/market/analysis/pivot_point.test
/net.test
/time.test
diff --git a/stdlib/source/test/lux/world/finance/market/analysis/accumulation_distribution.lux b/stdlib/source/test/lux/world/finance/market/analysis/accumulation_distribution.lux
index 74b502140..15b8fa6a6 100644
--- a/stdlib/source/test/lux/world/finance/market/analysis/accumulation_distribution.lux
+++ b/stdlib/source/test/lux/world/finance/market/analysis/accumulation_distribution.lux
@@ -22,7 +22,7 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [session (sessionT.random currency.usd)])
+ [session (sessionT.random currency.usd 1000,00)])
(all _.and
(_.coverage [/.oscillation]
(let [it (/.oscillation session)]
diff --git a/stdlib/source/test/lux/world/finance/market/analysis/pivot_point.lux b/stdlib/source/test/lux/world/finance/market/analysis/pivot_point.lux
new file mode 100644
index 000000000..bb7cd12b3
--- /dev/null
+++ b/stdlib/source/test/lux/world/finance/market/analysis/pivot_point.lux
@@ -0,0 +1,40 @@
+(.require
+ [library
+ [lux (.except)
+ [abstract
+ [monad (.only do)]]
+ [math
+ ["[0]" random (.only Random)]]
+ [test
+ ["_" property (.only Test)]]]]
+ [\\library
+ ["[0]" / (.only)
+ [////
+ ["[0]" money (.only)
+ ["[0]" currency]]
+ [trade
+ ["[0]" session (.only)
+ ["[1]T" \\test]]]]]])
+
+(def .public test
+ Test
+ (<| (_.covering /._)
+ (do [! random.monad]
+ [session (sessionT.random currency.usd 1000,00)])
+ (all _.and
+ (_.coverage [/.typical_price]
+ (let [it (/.typical_price session)]
+ (and (money.<= (the session.#high session)
+ it)
+ (money.>= (the session.#low session)
+ it))))
+ (_.coverage [/.Central_Pivot_Range /.central_pivot_range
+ /.#pivot_point /.#top_central /.#bottom_central]
+ (let [it (/.central_pivot_range session)]
+ (and (money.= (/.typical_price session)
+ (the /.#pivot_point it))
+ (money.< (the /.#top_central it)
+ (the /.#pivot_point it))
+ (money.> (the /.#bottom_central it)
+ (the /.#pivot_point it)))))
+ )))
diff --git a/stdlib/source/test/lux/world/finance/money.lux b/stdlib/source/test/lux/world/finance/money.lux
index 073f19f34..dd5108cac 100644
--- a/stdlib/source/test/lux/world/finance/money.lux
+++ b/stdlib/source/test/lux/world/finance/money.lux
@@ -14,7 +14,7 @@
["[0]" text (.only)
["%" \\format]]]
[math
- ["[0]" random (.only Random) (.use "[1]#[0]" functor)]
+ ["[0]" random (.only Random) (.use "[1]#[0]" monad)]
[number
["n" nat]]]
[test
@@ -25,12 +25,15 @@
["[0]" /
["[1][0]" currency]])
-(def .public (random $)
+(def .public (random $ max_sub_units)
(All (_ $)
- (-> (Currency $)
+ (-> (Currency $) Nat
(Random (/.Money $))))
- (random#each (/.money $)
- random.nat))
+ (when max_sub_units
+ 0 (random#in (/.money $ max_sub_units))
+ _ (random#each (|>> (n.% max_sub_units)
+ (/.money $))
+ random.nat)))
(def .public test
Test
@@ -43,9 +46,9 @@
(_.for [/.Money])
(all _.and
(_.for [/.equivalence /.=]
- (equivalenceS.spec /.equivalence (..random currency.usd)))
+ (equivalenceS.spec /.equivalence (..random currency.usd 1000,00)))
(_.for [/.order /.<]
- (orderT.spec /.order (..random currency.usd)))
+ (orderT.spec /.order (..random currency.usd 1000,00)))
(_.coverage [/.money /.currency /.amount]
(let [it (/.money currency.usd expected_amount)]
@@ -98,7 +101,7 @@
(/.of_sub_units currency.usd (/.sub_units expected)))]
(/.= expected actual)))
(do !
- [it (..random currency.usd)]
+ [it (..random currency.usd 1000,00)]
(_.coverage [/.format]
(and (text.starts_with? (%.nat (/.amount it))
(text.replaced_once "." "" (/.format it)))
diff --git a/stdlib/source/test/lux/world/finance/trade/session.lux b/stdlib/source/test/lux/world/finance/trade/session.lux
index 7519d63e3..70dde1b44 100644
--- a/stdlib/source/test/lux/world/finance/trade/session.lux
+++ b/stdlib/source/test/lux/world/finance/trade/session.lux
@@ -24,15 +24,15 @@
[///
["[0]T" money]])
-(def .public (random $)
+(def .public (random $ max_sub_units)
(All (_ $)
- (-> (Currency $)
+ (-> (Currency $) Nat
(Random (/.Session $))))
(do random.monad
- [p0 (moneyT.random $)
- p1 (moneyT.random $)
- p2 (moneyT.random $)
- p3 (moneyT.random $)
+ [p0 (moneyT.random $ max_sub_units)
+ p1 (moneyT.random $ max_sub_units)
+ p2 (moneyT.random $ max_sub_units)
+ p3 (moneyT.random $ max_sub_units)
bullish? random.bit
volume random.nat]
(when (list.sorted money.< (list p0 p1 p2 p3))
@@ -54,13 +54,13 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [before (..random currency.usd)
- after (..random currency.usd)])
+ [before (..random currency.usd 1000,00)
+ after (..random currency.usd 1000,00)])
(_.for [/.Session /.Volume
/.#open /.#high /.#low /.#close /.#volume])
(all _.and
(_.for [/.equivalence]
- (equivalenceS.spec /.equivalence (..random currency.usd)))
+ (equivalenceS.spec /.equivalence (..random currency.usd 1000,00)))
(_.coverage [/.composite]
(let [both (/.composite before after)]