aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/lux.lux9
-rw-r--r--stdlib/source/test/lux/control/exception.lux4
-rw-r--r--stdlib/source/test/lux/control/parser.lux6
-rw-r--r--stdlib/source/test/lux/data/text/regex.lux24
-rw-r--r--stdlib/source/test/lux/data/text/unicode/block.lux57
-rw-r--r--stdlib/source/test/lux/data/text/unicode/set.lux44
-rw-r--r--stdlib/source/test/lux/math.lux8
-rw-r--r--stdlib/source/test/lux/math/number/complex.lux10
-rw-r--r--stdlib/source/test/lux/math/number/frac.lux8
-rw-r--r--stdlib/source/test/lux/math/number/int.lux8
-rw-r--r--stdlib/source/test/lux/meta.lux6
-rw-r--r--stdlib/source/test/lux/test.lux24
-rw-r--r--stdlib/source/test/lux/type/check.lux14
13 files changed, 122 insertions, 100 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index 04f6bea3f..793fd23b3 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -409,6 +409,13 @@
(/.macro: (identity_macro tokens)
(\ meta.monad in tokens))
+(def: crosshair
+ "This is an arbitrary text whose only purpose is to be found, somewhere, in the source-code.")
+
+(/.macro: (found_crosshair? tokens lux)
+ (let [[_ _ source_code] (get@ #.source lux)]
+ (#.Right [lux (list (code.bit (text.contains? ..crosshair source_code)))])))
+
(def: for_macro
Test
(let [macro (: /.Macro'
@@ -429,6 +436,8 @@
(is? (: Any macro))))
(_.cover [/.macro:]
(is? expected (..identity_macro expected)))
+ (_.cover [/.Source]
+ (..found_crosshair?))
))))
(/.type: for_type/variant
diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux
index 1ab4cf0e5..7b1643b79 100644
--- a/stdlib/source/test/lux/control/exception.lux
+++ b/stdlib/source/test/lux/control/exception.lux
@@ -55,8 +55,8 @@
(_.cover [/.match?]
(/.match? ..an_exception
(/.construct ..an_exception [])))
- (_.cover [/.assert]
- (case (/.assert ..an_exception [] assertion_succeeded?)
+ (_.cover [/.assertion]
+ (case (/.assertion ..an_exception [] assertion_succeeded?)
(#try.Success _)
assertion_succeeded?
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index 209944969..717202488 100644
--- a/stdlib/source/test/lux/control/parser.lux
+++ b/stdlib/source/test/lux/control/parser.lux
@@ -373,12 +373,12 @@
(|> (list)
(/.run (/.lift (#try.Failure failure)))
(should_fail failure))))
- (_.cover [/.assert]
+ (_.cover [/.assertion]
(and (|> (list (code.bit #1) (code.int +123))
- (/.run (/.assert assertion #1))
+ (/.run (/.assertion assertion #1))
(match [] true))
(|> (list (code.bit #1) (code.int +123))
- (/.run (/.assert assertion #0))
+ (/.run (/.assertion assertion #0))
fails?)))
..combinators_0
..combinators_1
diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux
index 52053f108..ea81e2c77 100644
--- a/stdlib/source/test/lux/data/text/regex.lux
+++ b/stdlib/source/test/lux/data/text/regex.lux
@@ -7,17 +7,17 @@
[control
pipe
["." try]
- ["p" parser
- ["<.>" text (#+ Parser)]
- ["s" code]]]
+ [parser
+ ["<.>" text (#+ Parser)]]]
[data
["." text ("#\." equivalence)
["%" format (#+ format)]]]
+ ["." macro
+ [syntax (#+ syntax:)]
+ ["." code]]
[math
[number (#+ hex)]
- ["." random]]
- ["." macro
- [syntax (#+ syntax:)]]]]
+ ["." random]]]]
[\\library
["." /]])
@@ -269,6 +269,15 @@
"123-456-7890")))
))
+(syntax: (expands? form)
+ (function (_ lux)
+ (#try.Success [lux (list (code.bit (case (macro.single_expansion form lux)
+ (#try.Success _)
+ true
+
+ (#try.Failure error)
+ false)))])))
+
(def: #export test
Test
(<| (_.covering /._)
@@ -299,4 +308,7 @@
_
false)))
+ (_.cover [/.incorrect_quantification]
+ (and (expands? (/.regex "a{1,2}"))
+ (not (expands? (/.regex "a{2,1}")))))
)))
diff --git a/stdlib/source/test/lux/data/text/unicode/block.lux b/stdlib/source/test/lux/data/text/unicode/block.lux
index d08f41fa8..9588ce6ce 100644
--- a/stdlib/source/test/lux/data/text/unicode/block.lux
+++ b/stdlib/source/test/lux/data/text/unicode/block.lux
@@ -24,10 +24,10 @@
(def: #export random
(Random /.Block)
- (do random.monad
- [start random.nat
- end random.nat]
- (in (/.block start end))))
+ (do {! random.monad}
+ [start (\ ! map (n.% 1,000,000) random.nat)
+ additional (\ ! map (n.% 1,000,000) random.nat)]
+ (in (/.block start additional))))
(with_expansions [<blocks> (as_is [blocks/0
[/.basic_latin
@@ -171,10 +171,12 @@
(_.for [/.Block])
(do {! random.monad}
[#let [top_start (hex "AC00")
- top_end (hex "D7AF")]
+ top_end (hex "D7AF")
+ end_range (n.- top_start top_end)]
start (\ ! map (|>> (n.% top_start) inc) random.nat)
- end (\ ! map (|>> (n.% top_end) inc) random.nat)
- #let [sample (/.block start end)
+ end (\ ! map (|>> (n.% end_range) (n.+ top_start)) random.nat)
+ #let [additional (n.- start end)
+ sample (/.block start additional)
size (/.size sample)]
inside (\ ! map
(|>> (n.% size)
@@ -188,27 +190,24 @@
(_.for [/.monoid]
($monoid.spec /.equivalence /.monoid ..random))
- (_.cover [/.block]
- (\ /.equivalence =
- (/.block start end)
- (/.block end start)))
- (_.cover [/.start]
- (n.= (n.min start end)
- (/.start (/.block start end))))
- (_.cover [/.end]
- (n.= (n.max start end)
- (/.end (/.block start end))))
- (_.cover [/.size]
- (n.= (inc (n.- (n.min start end)
- (n.max start end)))
- (/.size (/.block start end))))
- (_.cover [/.within?]
- (and (/.within? sample inside)
- (not (/.within? sample (dec (/.start sample))))
- (not (/.within? sample (inc (/.end sample))))))
- (~~ (template [<definition> <part>]
- [<definition>]
-
- <blocks>))
+ (_.for [/.block]
+ ($_ _.and
+ (_.cover [/.start]
+ (n.= start
+ (/.start sample)))
+ (_.cover [/.end]
+ (n.= end
+ (/.end sample)))
+ (_.cover [/.size]
+ (n.= (inc additional)
+ (/.size sample)))
+ (_.cover [/.within?]
+ (and (/.within? sample inside)
+ (not (/.within? sample (dec (/.start sample))))
+ (not (/.within? sample (inc (/.end sample))))))
+ (~~ (template [<definition> <part>]
+ [<definition>]
+
+ <blocks>))))
)))))
)
diff --git a/stdlib/source/test/lux/data/text/unicode/set.lux b/stdlib/source/test/lux/data/text/unicode/set.lux
index 054c6c6f7..cd74a038c 100644
--- a/stdlib/source/test/lux/data/text/unicode/set.lux
+++ b/stdlib/source/test/lux/data/text/unicode/set.lux
@@ -48,34 +48,36 @@
(_.for [/.equivalence]
($equivalence.spec /.equivalence ..random))
- (_.cover [/.range]
- (let [[start end] (/.range (/.set [left (list right)]))]
- (and (n.= (n.min (block.start left)
- (block.start right))
- start)
- (n.= (n.max (block.end left)
- (block.end right))
- end))))
+ (_.cover [/.set]
+ (and (n.= (block.start left)
+ (/.start (/.set [left (list)])))
+ (n.= (block.end left)
+ (/.end (/.set [left (list)])))))
+ (_.cover [/.start]
+ (n.= (n.min (block.start left)
+ (block.start right))
+ (/.start (/.set [left (list right)]))))
+ (_.cover [/.end]
+ (n.= (n.max (block.end left)
+ (block.end right))
+ (/.end (/.set [left (list right)]))))
(_.cover [/.member?]
(bit\= (block.within? block inside)
(/.member? (/.set [block (list)]) inside)))
(_.cover [/.compose]
- (\ equivalence =
- [(n.min (block.start left)
- (block.start right))
- (n.max (block.end left)
- (block.end right))]
- (/.range (/.compose (/.set [left (list)])
- (/.set [right (list)])))))
- (_.cover [/.set]
- (\ equivalence =
- (/.range (/.compose (/.set [left (list)])
- (/.set [right (list)])))
- (/.range (/.set [left (list right)]))))
+ (let [composed (/.compose (/.set [left (list)])
+ (/.set [right (list)]))]
+ (and (n.= (n.min (block.start left)
+ (block.start right))
+ (/.start composed))
+ (n.= (n.max (block.end left)
+ (block.end right))
+ (/.end composed)))))
(~~ (template [<set>]
[(do random.monad
[char (random.char <set>)
- #let [[start end] (/.range <set>)]]
+ #let [start (/.start <set>)
+ end (/.end <set>)]]
(_.cover [<set>]
(and (/.member? <set> char)
(not (/.member? <set> (dec start)))
diff --git a/stdlib/source/test/lux/math.lux b/stdlib/source/test/lux/math.lux
index db314f400..96ba96e35 100644
--- a/stdlib/source/test/lux/math.lux
+++ b/stdlib/source/test/lux/math.lux
@@ -112,13 +112,13 @@
big (\ ! map (f.* +1,000,000,000.00) random.safe_frac)]
(template.let [(odd! <function>)
[(_.cover [<function>]
- (~= (f.negate (<function> angle))
- (<function> (f.negate angle))))]
+ (~= (f.opposite (<function> angle))
+ (<function> (f.opposite angle))))]
(even! <function>)
[(_.cover [<function>]
(~= (<function> angle)
- (<function> (f.negate angle))))]
+ (<function> (f.opposite angle))))]
(inverse! <left> <right> <input>)
[(_.cover [<left> <right>]
@@ -157,7 +157,7 @@
(f.+ /.pi (/.atan (f./ x y)))))]
(and (~= expected actual)
(~= tau/4 (/.atan/2 +0.0 (f.abs y)))
- (~= (f.negate tau/4) (/.atan/2 +0.0 (f.negate (f.abs y))))
+ (~= (f.opposite tau/4) (/.atan/2 +0.0 (f.opposite (f.abs y))))
(f.not_a_number? (/.atan/2 +0.0 +0.0))))))
(do {! random.monad}
[of (\ ! map (|>> (n.% 10) inc) random.nat)]
diff --git a/stdlib/source/test/lux/math/number/complex.lux b/stdlib/source/test/lux/math/number/complex.lux
index e5f43c47d..ddeb53c2f 100644
--- a/stdlib/source/test/lux/math/number/complex.lux
+++ b/stdlib/source/test/lux/math/number/complex.lux
@@ -177,7 +177,7 @@
(let [cx (/.conjugate x)]
(and (f.= (get@ #/.real x)
(get@ #/.real cx))
- (f.= (f.negate (get@ #/.imaginary x))
+ (f.= (f.opposite (get@ #/.imaginary x))
(get@ #/.imaginary cx)))))
(_.cover [/.reciprocal]
(let [reciprocal!
@@ -193,16 +193,16 @@
(or (f.= +0.0 signum_abs)
(f.= +1.0 signum_abs)
(f.= (math.pow +0.5 +2.0) signum_abs))))
- (_.cover [/.negate]
+ (_.cover [/.opposite]
(let [own_inverse!
- (let [there (/.negate x)
- back_again (/.negate there)]
+ (let [there (/.opposite x)
+ back_again (/.opposite there)]
(and (not (/.= there x))
(/.= back_again x)))
absolute!
(f.= (/.abs x)
- (/.abs (/.negate x)))]
+ (/.abs (/.opposite x)))]
(and own_inverse!
absolute!)))
)))
diff --git a/stdlib/source/test/lux/math/number/frac.lux b/stdlib/source/test/lux/math/number/frac.lux
index 41f1bc29c..2a8e65062 100644
--- a/stdlib/source/test/lux/math/number/frac.lux
+++ b/stdlib/source/test/lux/math/number/frac.lux
@@ -148,7 +148,7 @@
(_.cover [/.-]
(and (/.= +0.0 (/.- sample sample))
(/.= sample (/.- +0.0 sample))
- (/.= (/.negate sample)
+ (/.= (/.opposite sample)
(/.- sample +0.0))))
(_.cover [/./]
(and (/.= +1.0 (/./ sample sample))
@@ -229,12 +229,12 @@
(test /.negative_infinity)))))))
(do random.monad
[expected random.safe_frac]
- (_.cover [/.negate]
+ (_.cover [/.opposite]
(let [subtraction!
- (/.= +0.0 (/.+ (/.negate expected) expected))
+ (/.= +0.0 (/.+ (/.opposite expected) expected))
inverse!
- (|> expected /.negate /.negate (/.= expected))]
+ (|> expected /.opposite /.opposite (/.= expected))]
(and subtraction!
inverse!))))
diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux
index d7d3d6122..18f46233a 100644
--- a/stdlib/source/test/lux/math/number/int.lux
+++ b/stdlib/source/test/lux/math/number/int.lux
@@ -84,7 +84,7 @@
(_.cover [/.-]
(and (/.= +0 (/.- sample sample))
(/.= sample (/.- +0 sample))
- (/.= (/.negate sample)
+ (/.= (/.opposite sample)
(/.- sample +0))))
(_.cover [/./]
(and (/.= +1 (/./ sample sample))
@@ -168,12 +168,12 @@
))
(do random.monad
[expected random.int]
- (_.cover [/.negate]
+ (_.cover [/.opposite]
(let [subtraction!
- (/.= +0 (/.+ (/.negate expected) expected))
+ (/.= +0 (/.+ (/.opposite expected) expected))
inverse!
- (|> expected /.negate /.negate (/.= expected))]
+ (|> expected /.opposite /.opposite (/.= expected))]
(and subtraction!
inverse!))))
(do {! random.monad}
diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux
index 2356772ec..92f88dfc6 100644
--- a/stdlib/source/test/lux/meta.lux
+++ b/stdlib/source/test/lux/meta.lux
@@ -121,12 +121,12 @@
(!expect (^multi (#try.Failure actual_error)
(text\= (location.with location.dummy expected_error)
actual_error)))))
- (_.cover [/.assert]
- (and (|> (/.assert expected_error true)
+ (_.cover [/.assertion]
+ (and (|> (/.assertion expected_error true)
(: (Meta Any))
(/.run expected_lux)
(!expect (#try.Success [])))
- (|> (/.assert expected_error false)
+ (|> (/.assertion expected_error false)
(/.run expected_lux)
(!expect (^multi (#try.Failure actual_error)
(text\= expected_error actual_error))))))
diff --git a/stdlib/source/test/lux/test.lux b/stdlib/source/test/lux/test.lux
index e938dafd6..04a4d0734 100644
--- a/stdlib/source/test/lux/test.lux
+++ b/stdlib/source/test/lux/test.lux
@@ -36,9 +36,9 @@
(random.ascii/lower 5))]
($_ /.and
(in (do async.monad
- [[success_tally success_message] (/.assert expected_message/0 true)
- [failure_tally failure_message] (/.assert expected_message/0 false)]
- (/.cover' [/.assert /.Tally]
+ [[success_tally success_message] (/.assertion expected_message/0 true)
+ [failure_tally failure_message] (/.assertion expected_message/0 false)]
+ (/.cover' [/.assertion /.Tally]
(and (text.ends_with? expected_message/0 success_message)
(text.ends_with? expected_message/0 failure_message)
(and (n.= 1 (get@ #/.successes success_tally))
@@ -46,14 +46,14 @@
(and (n.= 0 (get@ #/.successes failure_tally))
(n.= 1 (get@ #/.failures failure_tally)))))))
(in (do async.monad
- [tt (/.and' (/.assert expected_message/0 true)
- (/.assert expected_message/1 true))
- ff (/.and' (/.assert expected_message/0 false)
- (/.assert expected_message/1 false))
- tf (/.and' (/.assert expected_message/0 true)
- (/.assert expected_message/1 false))
- ft (/.and' (/.assert expected_message/0 false)
- (/.assert expected_message/1 true))]
+ [tt (/.and' (/.assertion expected_message/0 true)
+ (/.assertion expected_message/1 true))
+ ff (/.and' (/.assertion expected_message/0 false)
+ (/.assertion expected_message/1 false))
+ tf (/.and' (/.assertion expected_message/0 true)
+ (/.assertion expected_message/1 false))
+ ft (/.and' (/.assertion expected_message/0 false)
+ (/.assertion expected_message/1 true))]
(/.cover' [/.and']
(and (..verify expected_message/0 expected_message/1 2 0 tt)
(..verify expected_message/0 expected_message/1 0 2 ff)
@@ -77,7 +77,7 @@
[actual random.nat]
(in (do async.monad
[expected read]
- (/.assert "" (n.= expected actual))))))]
+ (/.assertion "" (n.= expected actual))))))]
(in (do async.monad
[[pre_tally pre_message] pre
[post_tally post_message] post]
diff --git a/stdlib/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux
index a7cac630c..6172608b3 100644
--- a/stdlib/source/test/lux/type/check.lux
+++ b/stdlib/source/test/lux/type/check.lux
@@ -129,13 +129,13 @@
(#try.Failure actual) (is? expected actual))))
(do random.monad
[expected (random.ascii/upper 10)]
- (_.cover [/.assert]
+ (_.cover [/.assertion]
(and (case (/.run /.fresh_context
(: (/.Check Any)
- (/.assert expected true)))
+ (/.assertion expected true)))
(#try.Success _) true
(#try.Failure actual) false)
- (case (/.run /.fresh_context (/.assert expected false))
+ (case (/.run /.fresh_context (/.assertion expected false))
(#try.Success _) false
(#try.Failure actual) (is? expected actual)))))
(_.cover [/.except]
@@ -442,8 +442,8 @@
_ (/.check var/head nominal/0)
failures (monad.map ! (|>> (/.check nominal/1) ..verdict) (list& var/head var/tail+))
successes (monad.map ! (|>> (/.check nominal/0) ..verdict) (list& var/head var/tail+))]
- (/.assert "" (and (list.every? (bit\= false) failures)
- (list.every? (bit\= true) successes)))))
+ (/.assertion "" (and (list.every? (bit\= false) failures)
+ (list.every? (bit\= true) successes)))))
can_merge_multiple_rings_of_variables!
(succeeds? (do {! /.monad}
@@ -455,8 +455,8 @@
(list& var/head/1 var/tail+/1))]
failures (monad.map ! (|>> (/.check nominal/1) ..verdict) all_variables)
successes (monad.map ! (|>> (/.check nominal/0) ..verdict) all_variables)]
- (/.assert "" (and (list.every? (bit\= false) failures)
- (list.every? (bit\= true) successes)))))]
+ (/.assertion "" (and (list.every? (bit\= false) failures)
+ (list.every? (bit\= true) successes)))))]
(and can_create_rings_of_variables!
can_bind_rings_of_variables!
can_merge_multiple_rings_of_variables!)))