From be0245eed09d242a1fa81a64ce9c3084e8251252 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Mon, 12 Dec 2016 01:57:55 -0400 Subject: - Added tests for lux/math/ratio and lux/math/simple. - Some minor refactorings. - Ratios now work with nats instead of ints. --- stdlib/test/test/lux/concurrency/actor.lux | 2 +- stdlib/test/test/lux/concurrency/frp.lux | 2 +- stdlib/test/test/lux/concurrency/promise.lux | 2 +- stdlib/test/test/lux/data/format/json.lux | 2 +- stdlib/test/test/lux/math/ratio.lux | 106 ++++++++++++++++++++++++++ stdlib/test/test/lux/math/simple.lux | 107 +++++++++++++++++++++++++++ stdlib/test/tests.lux | 9 +-- 7 files changed, 221 insertions(+), 9 deletions(-) create mode 100644 stdlib/test/test/lux/math/ratio.lux create mode 100644 stdlib/test/test/lux/math/simple.lux (limited to 'stdlib/test') 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/" Monad] ["&" 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/" Monad] ["&" 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/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/format + [bool "b/" Eq] + [number "r/" Number] + (struct [list "List/" Fold Functor]) + [product]) + (codata function) + (math ["R" random]) + pipe + ["&" math/ratio "&/" Number]) + lux/test) + +(def: gen-ratio + (R;Random &;Ratio) + (do R;Monad + [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]] + (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/format + [bool "b/" Eq] + [number "r/" Number] + (struct [list "List/" Fold Functor]) + [product]) + (codata function) + (math ["R" random]) + pipe + ["&" math/simple]) + lux/test) + +(do-template [ <=> <+> <-> <*> <%>] + [(test: (format " aritmetic") + [x + y ] + ($_ 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 [ ] + [(test: (format " comparisons") + [x + y ] + ($_ seq + (assert "<" + (b/= ( y x) (&;< y x))) + (assert "<=" + (b/= ( y x) (&;<= y x))) + (assert ">" + (b/= ( y x) (&;> y x))) + (assert ">=" + (b/= ( 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 [ <=> ] + [(test: (format " min & max") + [x + y ] + ($_ seq + (assert "Min." + (<=> ( y x) (&;min y x))) + (assert "Max." + (<=> ( y x) (&;max y x))) + ))] + + ["Nat" R;nat n.= n.min n.max] + ["Int" R;int i.= i.min i.max] + ) + +(do-template [ <=> ] + [(test: (format " inc & dec") + [x ] + ($_ seq + (assert "Inc." + (<=> ( x) (&;inc x))) + (assert "Dec." + (<=> ( x) (&;dec x))) + ))] + + ["Nat" R;nat n.= n.inc n.dec] + ["Int" R;int i.= i.inc i.dec] + ) + +(do-template [ ] + [(test: (format " even & odd") + [x ] + ($_ seq + (assert "Even." + (b/= ( x) (&;even? x))) + (assert "Odd." + (b/= ( 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] -- cgit v1.2.3