aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2016-12-12 01:57:55 -0400
committerEduardo Julian2016-12-12 01:57:55 -0400
commitbe0245eed09d242a1fa81a64ce9c3084e8251252 (patch)
treeb6114a276f85ae2ea5ce74ac395dd6d118801220 /stdlib/test
parentf2ca9f956cbedb251603a835b2f3c6b1dded3d00 (diff)
- Added tests for lux/math/ratio and lux/math/simple.
- Some minor refactorings. - Ratios now work with nats instead of ints.
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/concurrency/actor.lux2
-rw-r--r--stdlib/test/test/lux/concurrency/frp.lux2
-rw-r--r--stdlib/test/test/lux/concurrency/promise.lux2
-rw-r--r--stdlib/test/test/lux/data/format/json.lux2
-rw-r--r--stdlib/test/test/lux/math/ratio.lux106
-rw-r--r--stdlib/test/test/lux/math/simple.lux107
-rw-r--r--stdlib/test/tests.lux9
7 files changed, 221 insertions, 9 deletions
diff --git a/stdlib/test/test/lux/concurrency/actor.lux b/stdlib/test/test/lux/concurrency/actor.lux
index ff1d831b6..7940cb22d 100644
--- a/stdlib/test/test/lux/concurrency/actor.lux
+++ b/stdlib/test/test/lux/concurrency/actor.lux
@@ -8,7 +8,7 @@
(lux (control monad)
(data [number]
text/format
- error)
+ [error #- fail])
(concurrency [promise #+ Promise Monad<Promise> "Promise/" Monad<Promise>]
["&" actor #+ actor:])
(codata function
diff --git a/stdlib/test/test/lux/concurrency/frp.lux b/stdlib/test/test/lux/concurrency/frp.lux
index 65d38b9c2..6bec2ea37 100644
--- a/stdlib/test/test/lux/concurrency/frp.lux
+++ b/stdlib/test/test/lux/concurrency/frp.lux
@@ -8,7 +8,7 @@
(lux (control monad)
(data [number]
text/format
- error)
+ [error #- fail])
(concurrency [promise #+ Promise Monad<Promise> "Promise/" Monad<Promise>]
["&" frp])
(codata function
diff --git a/stdlib/test/test/lux/concurrency/promise.lux b/stdlib/test/test/lux/concurrency/promise.lux
index c8e8acad7..51a62df7f 100644
--- a/stdlib/test/test/lux/concurrency/promise.lux
+++ b/stdlib/test/test/lux/concurrency/promise.lux
@@ -8,7 +8,7 @@
(lux (control monad)
(data [number]
text/format
- error)
+ [error #- fail])
(concurrency ["&" promise])
(codata function
[io #- run])
diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux
index 270a42358..39f039717 100644
--- a/stdlib/test/test/lux/data/format/json.lux
+++ b/stdlib/test/test/lux/data/format/json.lux
@@ -11,7 +11,7 @@
eq)
(data [text "Text/" Monoid<Text>]
text/format
- error
+ [error #- fail]
[bool]
[char]
[maybe]
diff --git a/stdlib/test/test/lux/math/ratio.lux b/stdlib/test/test/lux/math/ratio.lux
new file mode 100644
index 000000000..9c7eacd77
--- /dev/null
+++ b/stdlib/test/test/lux/math/ratio.lux
@@ -0,0 +1,106 @@
+## Copyright (c) Eduardo Julian. All rights reserved.
+## This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0.
+## If a copy of the MPL was not distributed with this file,
+## You can obtain one at http://mozilla.org/MPL/2.0/.
+
+(;module:
+ lux
+ (lux (codata [io])
+ (control monad)
+ (data [text "Text/" Monoid<Text>]
+ text/format
+ [bool "b/" Eq<Bool>]
+ [number "r/" Number<Real>]
+ (struct [list "List/" Fold<List> Functor<List>])
+ [product])
+ (codata function)
+ (math ["R" random])
+ pipe
+ ["&" math/ratio "&/" Number<Ratio>])
+ lux/test)
+
+(def: gen-ratio
+ (R;Random &;Ratio)
+ (do R;Monad<Random>
+ [numerator R;nat
+ denominator (|> R;nat (R;filter (|>. (n.= +0) not)))]
+ (wrap (&;ratio numerator denominator))))
+
+(test: "Normalization"
+ [denom1 R;nat
+ denom2 R;nat
+ sample gen-ratio]
+ ($_ seq
+ (assert "All zeroes are the same."
+ (&;q.= (&;ratio +0 denom1)
+ (&;ratio +0 denom2)))
+
+ (assert "All ratios are built normalized."
+ (|> sample &;normalize (&;q.= sample)))
+ ))
+
+(test: "Arithmetic"
+ [x gen-ratio
+ y gen-ratio
+ #let [min (&;q.min x y)
+ max (&;q.max x y)]]
+ ($_ seq
+ (assert "Addition and subtraction are opposites."
+ (and (|> max (&;q.- min) (&;q.+ min) (&;q.= max))
+ (|> max (&;q.+ min) (&;q.- min) (&;q.= max))))
+
+ (assert "Multiplication and division are opposites."
+ (and (|> max (&;q./ min) (&;q.* min) (&;q.= max))
+ (|> max (&;q.* min) (&;q./ min) (&;q.= max))))
+
+ (assert "Modulus by a larger ratio doesn't change the value."
+ (|> min (&;q.% max) (&;q.= min)))
+
+ (assert "Modulus by a smaller ratio results in a value smaller than the limit."
+ (|> max (&;q.% min) (&;q.< min)))
+
+ (assert "Can get the remainder of a division."
+ (let [remainder (&;q.% min max)
+ multiple (&;q.- remainder max)
+ factor (&;q./ min multiple)]
+ (and (|> factor (get@ #&;denominator) (n.= +1))
+ (|> factor (&;q.* min) (&;q.+ remainder) (&;q.= max)))))
+ ))
+
+(test: "Negation, absolute value and signum"
+ [sample gen-ratio]
+ ($_ seq
+ (assert "Negation is it's own inverse."
+ (let [there (&/negate sample)
+ back-again (&/negate there)]
+ (and (not (&;q.= there sample))
+ (&;q.= back-again sample))))
+
+ (assert "All ratios are already at their absolute value."
+ (|> sample &/abs (&;q.= sample)))
+
+ (assert "Signum is the identity."
+ (|> sample (&;q.* (&/signum sample)) (&;q.= sample)))
+ ))
+
+(test: "Order"
+ [x gen-ratio
+ y gen-ratio]
+ ($_ seq
+ (assert "Can compare ratios."
+ (and (or (&;q.<= y x)
+ (&;q.> y x))
+ (or (&;q.>= y x)
+ (&;q.< y x))))
+ ))
+
+(test: "Codec"
+ [sample gen-ratio
+ #let [(^open "&/") &;Codec<Text,Ratio>]]
+ (assert "Can encode/decode ratios."
+ (|> sample &/encode &/decode
+ (case> (#;Right output)
+ (&;q.= sample output)
+
+ _
+ false))))
diff --git a/stdlib/test/test/lux/math/simple.lux b/stdlib/test/test/lux/math/simple.lux
new file mode 100644
index 000000000..9e3af0c59
--- /dev/null
+++ b/stdlib/test/test/lux/math/simple.lux
@@ -0,0 +1,107 @@
+## Copyright (c) Eduardo Julian. All rights reserved.
+## This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0.
+## If a copy of the MPL was not distributed with this file,
+## You can obtain one at http://mozilla.org/MPL/2.0/.
+
+(;module:
+ lux
+ (lux (codata [io])
+ (control monad)
+ (data [text "Text/" Monoid<Text>]
+ text/format
+ [bool "b/" Eq<Bool>]
+ [number "r/" Number<Real>]
+ (struct [list "List/" Fold<List> Functor<List>])
+ [product])
+ (codata function)
+ (math ["R" random])
+ pipe
+ ["&" math/simple])
+ lux/test)
+
+(do-template [<category> <generator> <=> <+> <-> <*> </> <%>]
+ [(test: (format <category> " aritmetic")
+ [x <generator>
+ y <generator>]
+ ($_ seq
+ (assert "Can add."
+ (<=> (<+> y x) (&;+ y x)))
+ (assert "Can subtract."
+ (<=> (<-> y x) (&;- y x)))
+ (assert "Can multiply."
+ (<=> (<*> y x) (&;* y x)))
+ (assert "Can divide."
+ (<=> (</> y x) (&;/ y x)))
+ (assert "Can get remainder."
+ (<=> (<%> y x) (&;% y x)))
+ ))]
+
+ ["Nat" R;nat n.= n.+ n.- n.* n./ n.%]
+ ["Int" R;int i.= i.+ i.- i.* i./ i.%]
+ ["Real" R;real r.= r.+ r.- r.* r./ r.%]
+ ["Frac" R;frac f.= f.+ f.- f.* f./ f.%]
+ )
+
+(do-template [<category> <generator> <lt> <lte> <gt> <gte>]
+ [(test: (format <category> " comparisons")
+ [x <generator>
+ y <generator>]
+ ($_ seq
+ (assert "<"
+ (b/= (<lt> y x) (&;< y x)))
+ (assert "<="
+ (b/= (<lte> y x) (&;<= y x)))
+ (assert ">"
+ (b/= (<gt> y x) (&;> y x)))
+ (assert ">="
+ (b/= (<gte> y x) (&;>= y x)))
+ ))]
+
+ ["Nat" R;nat n.< n.<= n.> n.>=]
+ ["Int" R;int i.< i.<= i.> i.>=]
+ ["Real" R;real r.< r.<= r.> r.>=]
+ ["Frac" R;frac f.< f.<= f.> f.>=]
+ )
+
+(do-template [<category> <generator> <=> <min> <max>]
+ [(test: (format <category> " min & max")
+ [x <generator>
+ y <generator>]
+ ($_ seq
+ (assert "Min."
+ (<=> (<min> y x) (&;min y x)))
+ (assert "Max."
+ (<=> (<max> y x) (&;max y x)))
+ ))]
+
+ ["Nat" R;nat n.= n.min n.max]
+ ["Int" R;int i.= i.min i.max]
+ )
+
+(do-template [<category> <generator> <=> <inc> <dec>]
+ [(test: (format <category> " inc & dec")
+ [x <generator>]
+ ($_ seq
+ (assert "Inc."
+ (<=> (<inc> x) (&;inc x)))
+ (assert "Dec."
+ (<=> (<dec> x) (&;dec x)))
+ ))]
+
+ ["Nat" R;nat n.= n.inc n.dec]
+ ["Int" R;int i.= i.inc i.dec]
+ )
+
+(do-template [<category> <generator> <even?> <odd?>]
+ [(test: (format <category> " even & odd")
+ [x <generator>]
+ ($_ seq
+ (assert "Even."
+ (b/= (<even?> x) (&;even? x)))
+ (assert "Odd."
+ (b/= (<odd?> x) (&;odd? x)))
+ ))]
+
+ ["Nat" R;nat n.even? n.odd?]
+ ["Int" R;int i.even? i.odd?]
+ )
diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux
index 86de3d341..4b46a7cd5 100644
--- a/stdlib/test/tests.lux
+++ b/stdlib/test/tests.lux
@@ -47,10 +47,10 @@
[zipper])
(text [format]))
["_;" math]
- (math ## ["_;" ratio]
+ (math ["_;" ratio]
["_;" complex]
## ["_;" random]
- ## ["_;" simple]
+ ["_;" simple]
)
## ["_;" pipe]
## ["_;" lexer]
@@ -59,6 +59,7 @@
## (macro [ast]
## [syntax])
## [type]
+ ## (control ...)
)
)
## (lux (codata [cont])
@@ -69,9 +70,7 @@
## ["poly_;" text-encoder]
## ["poly_;" functor]))
## (type [check] [auto])
- ## (control [effect])
- ## ["_;" lexer]
- ## ["_;" regex])
+ ## (control [effect]))
)
## [Program]