aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
authorEduardo Julian2019-07-24 23:50:16 -0400
committerEduardo Julian2019-07-24 23:50:16 -0400
commit6425e4cfe470b54d76bb316cbdb6fdb21dd63130 (patch)
tree67e0ca73e9f23b36293fbe896337c7a3a336b9bc /stdlib/source/test
parent30c19b40f5fd583d19aa7cf495a19c1b91f86320 (diff)
No more "r/"-prefixed functions.
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/lux.lux75
-rw-r--r--stdlib/source/test/lux/data/number/rev.lux6
-rw-r--r--stdlib/source/test/lux/math/logic/continuous.lux28
-rw-r--r--stdlib/source/test/lux/math/logic/fuzzy.lux85
4 files changed, 100 insertions, 94 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index e1039d506..597f6d83e 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -21,7 +21,7 @@
[number
["." i64]
["." int]
- ["." rev]
+ ["r" rev]
["f" frac]]]
["." math]
["_" test (#+ Test)]
@@ -32,7 +32,8 @@
[language (#+)]
[territory (#+)]]
["%" data/text/format (#+ format)]
- ["r" math/random (#+ Random) ("#@." functor)]
+ [math
+ ["." random (#+ Random) ("#@." functor)]]
## TODO: Test these modules
[data
[format
@@ -137,23 +138,23 @@
(def: identity
Test
- (do r.monad
- [self (r.unicode 1)]
+ (do random.monad
+ [self (random.unicode 1)]
($_ _.and
(_.test "Every value is identical to itself."
(is? self self))
(_.test "The identity function doesn't change values in any way."
(is? self (function.identity self)))
(do @
- [other (r.unicode 1)]
+ [other (random.unicode 1)]
(_.test "Values created separately can't be identical."
(not (is? self other))))
)))
(def: increment-and-decrement
Test
- (do r.monad
- [value r.i64]
+ (do random.monad
+ [value random.i64]
($_ _.and
(_.test "'inc' and 'dec' are opposites."
(and (|> value inc dec (n/= value))
@@ -169,7 +170,7 @@
(def: (even-or-odd rand-gen even? odd?)
(All [a] (-> (Random (I64 a)) (Predicate (I64 a)) (Predicate (I64 a)) Test))
- (do r.monad
+ (do random.monad
[value rand-gen]
($_ _.and
(_.test "Every number is either even or odd."
@@ -192,7 +193,7 @@
(def: (choice rand-gen = [< choose])
(All [a] (-> (Random a) (Equivalence a) [(Order a) (Choice a)] Test))
- (do r.monad
+ (do random.monad
[left rand-gen
right rand-gen
#let [choice (choose left right)]]
@@ -215,22 +216,22 @@
(def: (conversion rand-gen forward backward =)
(All [a b] (-> (Random a) (-> a b) (-> b a) (Equivalence a) Test))
- (do r.monad
+ (do random.monad
[value rand-gen]
(_.test "Can convert between types in a lossless way."
(|> value forward backward (= value)))))
(def: frac-rev
- (r.Random Rev)
+ (Random Rev)
(let [bits-to-ignore 11]
- (:: r.functor map (i64.left-shift bits-to-ignore) r.rev)))
+ (:: random.functor map (i64.left-shift bits-to-ignore) random.rev)))
(def: prelude-macros
Test
($_ _.and
- (do r.monad
- [factor (r@map (|>> (n/% 10) (n/max 1)) r.nat)
- iterations (r@map (n/% 100) r.nat)
+ (do random.monad
+ [factor (random@map (|>> (n/% 10) (n/max 1)) random.nat)
+ iterations (random@map (n/% 100) random.nat)
#let [expected (n/* factor iterations)]]
(_.test "Can write loops."
(n/= expected
@@ -240,10 +241,10 @@
(recur (inc counter) (n/+ factor value))
value)))))
- (do r.monad
- [first r.nat
- second r.nat
- third r.nat]
+ (do random.monad
+ [first random.nat
+ second random.nat
+ third random.nat]
(_.test "Can create lists easily through macros."
(and (case (list first second third)
(#.Cons first' (#.Cons second' (#.Cons third' #.Nil)))
@@ -276,19 +277,19 @@
(def: templates
Test
- (do r.monad
- [cat0 r.nat
- cat1 r.nat]
+ (do random.monad
+ [cat0 random.nat
+ cat1 random.nat]
(_.test "Template application is a stand-in for the templated code."
(n/= (n/+ (n/* cat0 cat0) (n/* cat1 cat1))
(quadrance cat0 cat1)))))
(def: cross-platform-support
Test
- (do r.monad
- [on-default r.nat
- on-fake-host r.nat
- on-valid-host r.nat]
+ (do random.monad
+ [on-default random.nat
+ on-fake-host random.nat
+ on-valid-host random.nat]
($_ _.and
(_.test "Can provide default in case there is no particular host/platform support."
(n/= on-default
@@ -311,19 +312,19 @@
(<| (_.context "Even or odd.")
($_ _.and
(<| (_.context "Natural numbers.")
- (..even-or-odd r.nat n/even? n/odd?))
+ (..even-or-odd random.nat n/even? n/odd?))
(<| (_.context "Integers.")
- (..even-or-odd r.int i/even? i/odd?))))
+ (..even-or-odd random.int i/even? i/odd?))))
(<| (_.context "Minimum and maximum.")
(`` ($_ _.and
(~~ (template [<=> <lt> <min> <gt> <max> <gen> <context>]
[(<| (_.context <context>)
(..minimum-and-maximum <gen> <=> [<lt> <min>] [<gt> <max>]))]
- [i/= i/< i/min i/> i/max r.int "Integers."]
- [n/= n/< n/min n/> n/max r.nat "Natural numbers."]
- [r/= r/< r/min r/> r/max r.rev "Revolutions."]
- [f.= f.< f.min f.> f.max r.safe-frac "Fractions."]
+ [i/= i/< i/min i/> i/max random.int "Integers."]
+ [n/= n/< n/min n/> n/max random.nat "Natural numbers."]
+ [r.= r.< r.min r.> r.max random.rev "Revolutions."]
+ [f.= f.< f.min f.> f.max random.safe-frac "Fractions."]
)))))
(<| (_.context "Conversion.")
(`` ($_ _.and
@@ -332,11 +333,11 @@
" " (%.name (name-of <backward>))))
(..conversion <gen> <forward> <backward> <=>))]
- [i/= .nat .int (r@map (i/% +1,000,000) r.int)]
- [n/= .int .nat (r@map (n/% 1,000,000) r.nat)]
- [i/= int.frac f.int (r@map (i/% +1,000,000) r.int)]
- [f.= f.int int.frac (r@map (|>> (i/% +1,000,000) int.frac) r.int)]
- [r/= rev.frac f.rev frac-rev]
+ [i/= .nat .int (random@map (i/% +1,000,000) random.int)]
+ [n/= .int .nat (random@map (n/% 1,000,000) random.nat)]
+ [i/= int.frac f.int (random@map (i/% +1,000,000) random.int)]
+ [f.= f.int int.frac (random@map (|>> (i/% +1,000,000) int.frac) random.int)]
+ [r.= r.frac f.rev frac-rev]
)))))
(<| (_.context "Prelude macros.")
..prelude-macros)
diff --git a/stdlib/source/test/lux/data/number/rev.lux b/stdlib/source/test/lux/data/number/rev.lux
index 1a0bc4571..b84943a14 100644
--- a/stdlib/source/test/lux/data/number/rev.lux
+++ b/stdlib/source/test/lux/data/number/rev.lux
@@ -42,10 +42,10 @@
[/.binary] [/.octal] [/.decimal] [/.hex]
))
(_.test "Alternate notations."
- (and (r/= (bin ".11001001")
+ (and (/.= (bin ".11001001")
(bin ".11,00,10,01"))
- (r/= (oct ".615243")
+ (/.= (oct ".615243")
(oct ".615,243"))
- (r/= (hex ".deadBEEF")
+ (/.= (hex ".deadBEEF")
(hex ".dead,BEEF"))))
))))
diff --git a/stdlib/source/test/lux/math/logic/continuous.lux b/stdlib/source/test/lux/math/logic/continuous.lux
index 6895060c1..6c4b8a721 100644
--- a/stdlib/source/test/lux/math/logic/continuous.lux
+++ b/stdlib/source/test/lux/math/logic/continuous.lux
@@ -2,31 +2,35 @@
[lux #*
["%" data/text/format (#+ format)]
[abstract/monad (#+ do)]
- ["r" math/random]
- ["_" test (#+ Test)]]
+ ["_" test (#+ Test)]
+ [math
+ ["." random]]
+ [data
+ [number
+ ["r" rev]]]]
{1
["." /]})
(def: #export test
Test
(<| (_.context (%.name (name-of /._)))
- (do r.monad
- [left r.rev
- right r.rev]
+ (do random.monad
+ [left random.rev
+ right random.rev]
($_ _.and
(_.test "AND is the minimum."
(let [result (/.and left right)]
- (and (r/<= left result)
- (r/<= right result))))
+ (and (r.<= left result)
+ (r.<= right result))))
(_.test "OR is the maximum."
(let [result (/.or left right)]
- (and (r/>= left result)
- (r/>= right result))))
+ (and (r.>= left result)
+ (r.>= right result))))
(_.test "Double negation results in the original value."
- (r/= left (/.not (/.not left))))
+ (r.= left (/.not (/.not left))))
(_.test "Every value is equivalent to itself."
- (and (r/>= left
+ (and (r.>= left
(/.= left left))
- (r/>= right
+ (r.>= right
(/.= right right))))
))))
diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux
index 3d21a1f21..35dff4a03 100644
--- a/stdlib/source/test/lux/math/logic/fuzzy.lux
+++ b/stdlib/source/test/lux/math/logic/fuzzy.lux
@@ -2,13 +2,14 @@
[lux #*
["%" data/text/format (#+ format)]
[abstract/monad (#+ do)]
- ["r" math/random (#+ Random)]
+ [math
+ ["." random (#+ Random)]]
["_" test (#+ Test)]
[data
["." bit ("#@." equivalence)]
[number
["." nat]
- ["." rev]]
+ ["r" rev]]
[collection
["." list]
["." set]]]]
@@ -21,8 +22,8 @@
[(def: <name>
Test
(<| (_.context (%.name (name-of <triangle>)))
- (do r.monad
- [values (r.set <hash> 3 <gen>)
+ (do random.monad
+ [values (random.set <hash> 3 <gen>)
#let [[x y z] (case (set.to-list values)
(^ (list x y z))
[x y z]
@@ -39,29 +40,29 @@
triangle (<triangle> x y z)]]
($_ _.and
(_.test "The middle value will always have maximum membership."
- (r/= //.true (/.membership middle triangle)))
+ (r.= //.true (/.membership middle triangle)))
(_.test "Boundary values will always have 0 membership."
- (and (r/= //.false (/.membership bottom triangle))
- (r/= //.false (/.membership top triangle))))
+ (and (r.= //.false (/.membership bottom triangle))
+ (r.= //.false (/.membership top triangle))))
(_.test "Values within range, will have membership > 0."
- (bit@= (r/> //.false (/.membership sample triangle))
+ (bit@= (r.> //.false (/.membership sample triangle))
(and (<gt> bottom sample)
(<lt> top sample))))
(_.test "Values outside of range, will have membership = 0."
- (bit@= (r/= //.false (/.membership sample triangle))
+ (bit@= (r.= //.false (/.membership sample triangle))
(or (<lte> bottom sample)
(<gte> top sample))))
))))]
- [rev-triangles "Rev" rev.hash r.rev /.triangle r/< r/<= r/> r/>=]
+ [rev-triangles "Rev" r.hash random.rev /.triangle r.< r.<= r.> r.>=]
)
(template [<name> <desc> <hash> <gen> <trapezoid> <lt> <lte> <gt> <gte>]
[(def: <name>
Test
(<| (_.context (%.name (name-of <trapezoid>)))
- (do r.monad
- [values (r.set <hash> 4 <gen>)
+ (do random.monad
+ [values (random.set <hash> 4 <gen>)
#let [[w x y z] (case (set.to-list values)
(^ (list w x y z))
[w x y z]
@@ -78,96 +79,96 @@
trapezoid (<trapezoid> w x y z)]]
($_ _.and
(_.test "The middle values will always have maximum membership."
- (and (r/= //.true (/.membership middle-bottom trapezoid))
- (r/= //.true (/.membership middle-top trapezoid))))
+ (and (r.= //.true (/.membership middle-bottom trapezoid))
+ (r.= //.true (/.membership middle-top trapezoid))))
(_.test "Boundary values will always have 0 membership."
- (and (r/= //.false (/.membership bottom trapezoid))
- (r/= //.false (/.membership top trapezoid))))
+ (and (r.= //.false (/.membership bottom trapezoid))
+ (r.= //.false (/.membership top trapezoid))))
(_.test "Values within inner range will have membership = 1"
- (bit@= (r/= //.true (/.membership sample trapezoid))
+ (bit@= (r.= //.true (/.membership sample trapezoid))
(and (<gte> middle-bottom sample)
(<lte> middle-top sample))))
(_.test "Values within range, will have membership > 0."
- (bit@= (r/> //.false (/.membership sample trapezoid))
+ (bit@= (r.> //.false (/.membership sample trapezoid))
(and (<gt> bottom sample)
(<lt> top sample))))
(_.test "Values outside of range, will have membership = 0."
- (bit@= (r/= //.false (/.membership sample trapezoid))
+ (bit@= (r.= //.false (/.membership sample trapezoid))
(or (<lte> bottom sample)
(<gte> top sample))))
))))]
- [rev-trapezoids "Rev" rev.hash r.rev /.trapezoid r/< r/<= r/> r/>=]
+ [rev-trapezoids "Rev" r.hash random.rev /.trapezoid r.< r.<= r.> r.>=]
)
(def: #export triangle
(Random (Fuzzy Rev))
- (do r.monad
- [x r.rev
- y r.rev
- z r.rev]
+ (do random.monad
+ [x random.rev
+ y random.rev
+ z random.rev]
(wrap (/.triangle x y z))))
(def: combinators
Test
(<| (_.context "Combinators")
- (do r.monad
+ (do random.monad
[left ..triangle
right ..triangle
- sample r.rev]
+ sample random.rev]
($_ _.and
(_.test (%.name (name-of /.union))
(let [combined (/.union left right)
combined-membership (/.membership sample combined)]
- (and (r/>= (/.membership sample left)
+ (and (r.>= (/.membership sample left)
combined-membership)
- (r/>= (/.membership sample right)
+ (r.>= (/.membership sample right)
combined-membership))))
(_.test (%.name (name-of /.intersection))
(let [combined (/.intersection left right)
combined-membership (/.membership sample combined)]
- (and (r/<= (/.membership sample left)
+ (and (r.<= (/.membership sample left)
combined-membership)
- (r/<= (/.membership sample right)
+ (r.<= (/.membership sample right)
combined-membership))))
(_.test (%.name (name-of /.complement))
- (r/= (/.membership sample left)
+ (r.= (/.membership sample left)
(//.not (/.membership sample (/.complement left)))))
(_.test (%.name (name-of /.difference))
- (r/<= (/.membership sample right)
+ (r.<= (/.membership sample right)
(/.membership sample (/.difference left right))))
))))
(def: predicates-and-sets
Test
- (do r.monad
+ (do random.monad
[#let [set-10 (set.from-list nat.hash (list.n/range 0 10))]
- sample (|> r.nat (:: @ map (n/% 20)))]
+ sample (|> random.nat (:: @ map (n/% 20)))]
($_ _.and
(_.test (%.name (name-of /.from-predicate))
- (bit@= (r/= //.true (/.membership sample (/.from-predicate n/even?)))
+ (bit@= (r.= //.true (/.membership sample (/.from-predicate n/even?)))
(n/even? sample)))
(_.test (%.name (name-of /.from-set))
- (bit@= (r/= //.true (/.membership sample (/.from-set set-10)))
+ (bit@= (r.= //.true (/.membership sample (/.from-set set-10)))
(set.member? set-10 sample)))
)))
(def: thresholds
Test
- (do r.monad
+ (do random.monad
[fuzzy ..triangle
- sample r.rev
- threshold r.rev
+ sample random.rev
+ threshold random.rev
#let [vip-fuzzy (/.cut threshold fuzzy)
member? (/.to-predicate threshold fuzzy)]]
(<| (_.context (%.name (name-of /.cut)))
($_ _.and
(_.test "Can increase the threshold of membership of a fuzzy set."
- (bit@= (r/> //.false (/.membership sample vip-fuzzy))
- (r/> threshold (/.membership sample fuzzy))))
+ (bit@= (r.> //.false (/.membership sample vip-fuzzy))
+ (r.> threshold (/.membership sample fuzzy))))
(_.test "Can turn fuzzy sets into predicates through a threshold."
(bit@= (member? sample)
- (r/> threshold (/.membership sample fuzzy))))
+ (r.> threshold (/.membership sample fuzzy))))
))))
(def: #export test