From d6a7a133c5c4a734ab45e9497c8e5df749ce383a Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Mon, 27 Nov 2017 02:09:04 -0400 Subject: - Changed the prefixes of numeric functions. --- stdlib/test/test/lux.lux | 42 +++++----- stdlib/test/test/lux/cli.lux | 2 +- stdlib/test/test/lux/concurrency/actor.lux | 8 +- stdlib/test/test/lux/concurrency/atom.lux | 10 +-- stdlib/test/test/lux/concurrency/frp.lux | 12 +-- stdlib/test/test/lux/concurrency/space.lux | 2 +- stdlib/test/test/lux/concurrency/stm.lux | 18 ++--- stdlib/test/test/lux/control/cont.lux | 22 +++--- stdlib/test/test/lux/control/exception.lux | 2 +- stdlib/test/test/lux/control/interval.lux | 12 +-- stdlib/test/test/lux/control/parser.lux | 21 +++-- stdlib/test/test/lux/control/pipe.lux | 42 +++++----- stdlib/test/test/lux/control/reader.lux | 18 ++--- stdlib/test/test/lux/control/state.lux | 48 ++++++------ stdlib/test/test/lux/control/writer.lux | 12 +-- stdlib/test/test/lux/data/bit.lux | 34 ++++---- stdlib/test/test/lux/data/coll/array.lux | 38 ++++----- stdlib/test/test/lux/data/coll/dict.lux | 36 ++++----- stdlib/test/test/lux/data/coll/list.lux | 94 +++++++++++------------ stdlib/test/test/lux/data/coll/ordered/dict.lux | 16 ++-- stdlib/test/test/lux/data/coll/ordered/set.lux | 12 +-- stdlib/test/test/lux/data/coll/priority-queue.lux | 12 +-- stdlib/test/test/lux/data/coll/queue.lux | 12 +-- stdlib/test/test/lux/data/coll/sequence.lux | 28 +++---- stdlib/test/test/lux/data/coll/set.lux | 6 +- stdlib/test/test/lux/data/coll/stack.lux | 8 +- stdlib/test/test/lux/data/coll/stream.lux | 70 ++++++++--------- stdlib/test/test/lux/data/coll/tree/rose.lux | 8 +- stdlib/test/test/lux/data/coll/tree/zipper.lux | 4 +- stdlib/test/test/lux/data/color.lux | 38 ++++----- stdlib/test/test/lux/data/error.lux | 14 ++-- stdlib/test/test/lux/data/format/json.lux | 17 ++-- stdlib/test/test/lux/data/format/xml.lux | 6 +- stdlib/test/test/lux/data/ident.lux | 8 +- stdlib/test/test/lux/data/lazy.lux | 20 ++--- stdlib/test/test/lux/data/maybe.lux | 2 +- stdlib/test/test/lux/data/number.lux | 40 +++++----- stdlib/test/test/lux/data/number/complex.lux | 65 ++++++++-------- stdlib/test/test/lux/data/number/ratio.lux | 8 +- stdlib/test/test/lux/data/product.lux | 8 +- stdlib/test/test/lux/data/sum.lux | 4 +- stdlib/test/test/lux/data/text.lux | 22 +++--- stdlib/test/test/lux/data/text/lexer.lux | 2 +- stdlib/test/test/lux/host.jvm.lux | 12 +-- stdlib/test/test/lux/io.lux | 12 +-- stdlib/test/test/lux/lang/syntax.lux | 37 ++++----- stdlib/test/test/lux/lang/type.lux | 12 +-- stdlib/test/test/lux/lang/type/check.lux | 12 +-- stdlib/test/test/lux/macro/poly/eq.lux | 6 +- stdlib/test/test/lux/macro/poly/functor.lux | 2 +- stdlib/test/test/lux/math.lux | 91 ++++++++++------------ stdlib/test/test/lux/math/logic/continuous.lux | 14 ++-- stdlib/test/test/lux/math/logic/fuzzy.lux | 68 ++++++++-------- stdlib/test/test/lux/math/random.lux | 24 +++--- stdlib/test/test/lux/time/duration.lux | 6 +- stdlib/test/test/lux/time/instant.lux | 7 +- stdlib/test/test/lux/type/implicit.lux | 12 +-- stdlib/test/test/lux/type/object.lux | 6 +- stdlib/test/test/lux/world/blob.lux | 48 ++++++------ stdlib/test/test/lux/world/file.lux | 42 +++++----- stdlib/test/test/lux/world/net/tcp.lux | 10 +-- stdlib/test/test/lux/world/net/udp.lux | 12 +-- 62 files changed, 667 insertions(+), 669 deletions(-) (limited to 'stdlib/test') diff --git a/stdlib/test/test/lux.lux b/stdlib/test/test/lux.lux index addc7a33a..d73f0c5a9 100644 --- a/stdlib/test/test/lux.lux +++ b/stdlib/test/test/lux.lux @@ -14,7 +14,7 @@ (context: "Value identity." (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) x (r;text size) y (r;text size)] ($_ seq @@ -52,8 +52,8 @@ (and (|> value inc even?) (|> value dec even?)))))))] - ["Nat" r;nat n.inc n.dec n.even? n.odd? n.= n.< n.>] - ["Int" r;int i.inc i.dec i.even? i.odd? i.= i.< i.>] + ["Nat" r;nat n/inc n/dec n/even? n/odd? n/= n/< n/>] + ["Int" r;int i/inc i/dec i/even? i/odd? i/= i/< i/>] ) (do-template [category rand-gen = < > <= >= min max] @@ -80,10 +80,10 @@ (>= y (max x y))) )))))] - ["Int" r;int i.= i.< i.> i.<= i.>= i.min i.max] - ["Nat" r;nat n.= n.< n.> n.<= n.>= n.min n.max] - ["Frac" r;frac f.= f.< f.> f.<= f.>= f.min f.max] - ["Deg" r;deg d.= d.< d.> d.<= d.>= d.min d.max] + ["Int" r;int i/= i/< i/> i/<= i/>= i/min i/max] + ["Nat" r;nat n/= n/< n/> n/<= n/>= n/min n/max] + ["Frac" r;frac f/= f/< f/> f/<= f/>= f/min f/max] + ["Deg" r;deg d/= d/< d/> d/<= d/>= d/min d/max] ) (do-template [category rand-gen = + - * / <%> > <0> <1> %x ] @@ -136,10 +136,10 @@ (|> x' (/ y) (* y) (= x')))) ))))] - ["Nat" r;nat n.= n.+ n.- n.* n./ n.% n.> +0 +1 +1000000 %n (n.% +1000) id] - ["Int" r;int i.= i.+ i.- i.* i./ i.% i.> 0 1 1000000 %i (i.% 1000) id] - ["Frac" r;frac f.= f.+ f.- f.* f./ f.% f.> 0.0 1.0 1000000.0 %r id math;floor] - ["Deg" r;deg d.= d.+ d.- d.* d./ d.% d.> .0 ("lux deg max") ("lux deg max") %f id id] + ["Nat" r;nat n/= n/+ n/- n/* n// n/% n/> +0 +1 +1000000 %n (n/% +1000) id] + ["Int" r;int i/= i/+ i/- i/* i// i/% i/> 0 1 1000000 %i (i/% 1000) id] + ["Frac" r;frac f/= f/+ f/- f/* f// f/% f/> 0.0 1.0 1000000.0 %r id math;floor] + ["Deg" r;deg d/= d/+ d/- d/* d// d/% d/> .0 ("lux deg max") ("lux deg max") %f id id] ) (do-template [category rand-gen -> <- = %a %z] @@ -151,21 +151,21 @@ (test "" (|> value -> <- (= value))))))] - ["Int->Nat" r;int int-to-nat nat-to-int i.= (i.% 1000000) %i %n] - ["Nat->Int" r;nat nat-to-int int-to-nat n.= (n.% +1000000) %n %i] - ["Int->Frac" r;int int-to-frac frac-to-int i.= (i.% 1000000) %i %r] - ["Frac->Int" r;frac frac-to-int int-to-frac f.= math;floor %r %i] - ## [r;frac frac-to-deg deg-to-frac f.= (f.% 1.0) %r %f] + ["Int->Nat" r;int int-to-nat nat-to-int i/= (i/% 1000000) %i %n] + ["Nat->Int" r;nat nat-to-int int-to-nat n/= (n/% +1000000) %n %i] + ["Int->Frac" r;int int-to-frac frac-to-int i/= (i/% 1000000) %i %r] + ["Frac->Int" r;frac frac-to-int int-to-frac f/= math;floor %r %i] + ## [r;frac frac-to-deg deg-to-frac f/= (f/% 1.0) %r %f] ) (context: "Simple macros and constructs" ($_ seq (test "Can write easy loops for iterative programming." - (i.= 1000 + (i/= 1000 (loop [counter 0 value 1] - (if (i.< 3 counter) - (recur (i.inc counter) (i.* 10 value)) + (if (i/< 3 counter) + (recur (i/inc counter) (i/* 10 value)) value)))) (test "Can create lists easily through macros." @@ -192,7 +192,7 @@ )) (template: (hypotenuse x y) - (i.+ (i.* x x) (i.* y y))) + (i/+ (i/* x x) (i/* y y))) (context: "Templates." (<| (times +100) @@ -200,7 +200,7 @@ [x r;int y r;int] (test "Template application is a stand-in for the templated code." - (i.= (i.+ (i.* x x) (i.* y y)) + (i/= (i/+ (i/* x x) (i/* y y)) (hypotenuse x y)))))) (context: "Cross-platform support." diff --git a/stdlib/test/test/lux/cli.lux b/stdlib/test/test/lux/cli.lux index 35400da79..bb3765e63 100644 --- a/stdlib/test/test/lux/cli.lux +++ b/stdlib/test/test/lux/cli.lux @@ -18,7 +18,7 @@ (context: "CLI" (<| (times +100) (do @ - [num-args (|> r;nat (:: @ map (n.% +10))) + [num-args (|> r;nat (:: @ map (n/% +10))) #let [(^open "Nat/") number;Codec gen-arg (:: @ map Nat/encode r;nat)] yes gen-arg diff --git a/stdlib/test/test/lux/concurrency/actor.lux b/stdlib/test/test/lux/concurrency/actor.lux index 8abcae045..450f3b399 100644 --- a/stdlib/test/test/lux/concurrency/actor.lux +++ b/stdlib/test/test/lux/concurrency/actor.lux @@ -28,7 +28,7 @@ (message: #export Counter (count! [increment Nat] state self Nat) - (let [state' (n.+ increment state)] + (let [state' (n/+ increment state)] (T;return [state' state']))) (context: "Actors" @@ -74,9 +74,9 @@ output-1 (count! +1 counter) output-2 (count! +1 counter) output-3 (count! +1 counter)] - (wrap (and (n.= +1 output-1) - (n.= +2 output-2) - (n.= +3 output-3))))] + (wrap (and (n/= +1 output-1) + (n/= +2 output-2) + (n/= +3 output-3))))] (assert "Can send messages to actors." (case result (#E;Success outcome) diff --git a/stdlib/test/test/lux/concurrency/atom.lux b/stdlib/test/test/lux/concurrency/atom.lux index 039546436..c7e2c42b3 100644 --- a/stdlib/test/test/lux/concurrency/atom.lux +++ b/stdlib/test/test/lux/concurrency/atom.lux @@ -18,17 +18,17 @@ #let [box (&;atom value)]] ($_ seq (test "Can obtain the value of an atom." - (n.= value (io;run (&;read box)))) + (n/= value (io;run (&;read box)))) (test "Can swap the value of an atom." (and (io;run (&;compare-and-swap value swap-value box)) - (n.= swap-value (io;run (&;read box))))) + (n/= swap-value (io;run (&;read box))))) (test "Can update the value of an atom." - (exec (io;run (&;update n.inc box)) - (n.= (n.inc swap-value) (io;run (&;read box))))) + (exec (io;run (&;update n/inc box)) + (n/= (n/inc swap-value) (io;run (&;read box))))) (test "Can immediately set the value of an atom." (exec (io;run (&;write set-value box)) - (n.= set-value (io;run (&;read box))))) + (n/= set-value (io;run (&;read box))))) )))) diff --git a/stdlib/test/test/lux/concurrency/frp.lux b/stdlib/test/test/lux/concurrency/frp.lux index 3fb3d847a..5faa404e9 100644 --- a/stdlib/test/test/lux/concurrency/frp.lux +++ b/stdlib/test/test/lux/concurrency/frp.lux @@ -43,7 +43,7 @@ false)))) (wrap (do P;Monad - [elems (&;consume (&;filter i.even? (to-channel (list 0 1 2 3 4 5))))] + [elems (&;consume (&;filter i/even? (to-channel (list 0 1 2 3 4 5))))] (assert "Can filter a channel's elements." (case elems (^ (list 0 2 4)) @@ -64,9 +64,9 @@ false)))) (wrap (do P;Monad - [output (&;fold (function [base input] (P/wrap (i.+ input base))) 0 (to-channel (list 0 1 2 3 4 5)))] + [output (&;fold (function [base input] (P/wrap (i/+ input base))) 0 (to-channel (list 0 1 2 3 4 5)))] (assert "Can fold over a channel." - (i.= 15 output)))) + (i/= 15 output)))) (wrap (do P;Monad [elems (&;consume (&;distinct number;Eq (to-channel (list 0 0 0 1 2 2 3 3 3 3 4 4 4 5 5))))] @@ -89,7 +89,7 @@ false)))) (wrap (do P;Monad - [elems (&;consume (:: &;Functor map i.inc (to-channel (list 0 1 2 3 4 5))))] + [elems (&;consume (:: &;Functor map i/inc (to-channel (list 0 1 2 3 4 5))))] (assert "Functor goes over every element in a channel." (case elems (^ (list 1 2 3 4 5 6)) @@ -100,7 +100,7 @@ (wrap (do P;Monad [elems (&;consume (let [(^open) &;Applicative] - (apply (wrap i.inc) (wrap 12345))))] + (apply (wrap i/inc) (wrap 12345))))] (assert "Applicative works over all channel values." (case elems (^ (list 12346)) @@ -111,7 +111,7 @@ (wrap (do P;Monad [elems (&;consume (do &;Monad - [f (wrap i.inc) + [f (wrap i/inc) a (wrap 12345)] (wrap (f a))))] (assert "Monad works over all channel values." diff --git a/stdlib/test/test/lux/concurrency/space.lux b/stdlib/test/test/lux/concurrency/space.lux index d99733958..1e71d03c1 100644 --- a/stdlib/test/test/lux/concurrency/space.lux +++ b/stdlib/test/test/lux/concurrency/space.lux @@ -20,4 +20,4 @@ #Pong #Ping) where self)] - (wrap (update@ #hits n.inc state)))) + (wrap (update@ #hits n/inc state)))) diff --git a/stdlib/test/test/lux/concurrency/stm.lux b/stdlib/test/test/lux/concurrency/stm.lux index 96c486e67..75354b374 100644 --- a/stdlib/test/test/lux/concurrency/stm.lux +++ b/stdlib/test/test/lux/concurrency/stm.lux @@ -24,7 +24,7 @@ (&;read _var))) output3 (&;commit (do &;Monad [temp (&;read _var) - _ (&;update (i.* 3) _var)] + _ (&;update (i/* 3) _var)] (&;read _var))) ?c1+changes' changes #let [[c1 changes'] (maybe;default [-1 changes] ?c1+changes')] @@ -34,18 +34,18 @@ Can write STM vars. Can update STM vars. Can follow all the changes to STM vars." - (and (i.= 0 output1) - (i.= 5 output2) - (i.= 15 output3) - (and (i.= 5 c1) (i.= 15 c2)))))) + (and (i/= 0 output1) + (i/= 5 output2) + (i/= 15 output3) + (and (i/= 5 c1) (i/= 15 c2)))))) (wrap (let [_concurrency-var (&;var 0)] (do promise;Monad [_ (M;seq @ (map (function [_] - (M;map @ (function [_] (&;commit (&;update i.inc _concurrency-var))) - (list;i.range 1 iterations/processes))) - (list;i.range 1 (nat-to-int promise;concurrency-level)))) + (M;map @ (function [_] (&;commit (&;update i/inc _concurrency-var))) + (list;i/range 1 iterations/processes))) + (list;i/range 1 (nat-to-int promise;concurrency-level)))) last-val (&;commit (&;read _concurrency-var))] (assert "Can modify STM vars concurrently from multiple threads." - (i.= (i.* iterations/processes (nat-to-int promise;concurrency-level)) + (i/= (i/* iterations/processes (nat-to-int promise;concurrency-level)) last-val))))))) diff --git a/stdlib/test/test/lux/control/cont.lux b/stdlib/test/test/lux/control/cont.lux index 23b3a9bf3..c0fd26ccc 100644 --- a/stdlib/test/test/lux/control/cont.lux +++ b/stdlib/test/test/lux/control/cont.lux @@ -19,22 +19,22 @@ elems (r;list +3 r;nat)] ($_ seq (test "Can run continuations to compute their values." - (n.= sample (&;run (&/wrap sample)))) + (n/= sample (&;run (&/wrap sample)))) (test "Can use functor." - (n.= (n.inc sample) (&;run (&/map n.inc (&/wrap sample))))) + (n/= (n/inc sample) (&;run (&/map n/inc (&/wrap sample))))) (test "Can use applicative." - (n.= (n.inc sample) (&;run (&/apply (&/wrap n.inc) (&/wrap sample))))) + (n/= (n/inc sample) (&;run (&/apply (&/wrap n/inc) (&/wrap sample))))) (test "Can use monad." - (n.= (n.inc sample) (&;run (do &;Monad - [func (wrap n.inc) + (n/= (n/inc sample) (&;run (do &;Monad + [func (wrap n/inc) arg (wrap sample)] (wrap (func arg)))))) (test "Can use the current-continuation as a escape hatch." - (n.= (n.* +2 sample) + (n/= (n/* +2 sample) (&;run (do &;Monad [value (&;call/cc (function [k] @@ -42,16 +42,16 @@ [temp (k sample)] ## If this code where to run, ## the output would be - ## (n.* +4 sample) + ## (n/* +4 sample) (k temp))))] - (wrap (n.* +2 value)))))) + (wrap (n/* +2 value)))))) (test "Can use the current-continuation to build a time machine." - (n.= (n.+ +100 sample) + (n/= (n/+ +100 sample) (&;run (do &;Monad [[restart [output idx]] (&;portal [sample +0])] - (if (n.< +10 idx) - (restart [(n.+ +10 output) (n.inc idx)]) + (if (n/< +10 idx) + (restart [(n/+ +10 output) (n/inc idx)]) (wrap output)))))) (test "Can use delimited continuations with shifting." diff --git a/stdlib/test/test/lux/control/exception.lux b/stdlib/test/test/lux/control/exception.lux index 144a08b1f..e7adbe93b 100644 --- a/stdlib/test/test/lux/control/exception.lux +++ b/stdlib/test/test/lux/control/exception.lux @@ -46,4 +46,4 @@ (&;catch Another-Exception (function [ex] another-val)) (&;otherwise (function [ex] otherwise-val)))]] (test "Catch and otherwhise handlers can properly handle the flow of exception-handling." - (n.= expected actual))))) + (n/= expected actual))))) diff --git a/stdlib/test/test/lux/control/interval.lux b/stdlib/test/test/lux/control/interval.lux index 589063961..a8d5c3c9e 100644 --- a/stdlib/test/test/lux/control/interval.lux +++ b/stdlib/test/test/lux/control/interval.lux @@ -60,13 +60,13 @@ (r;Random (&;Interval Int)) (do r;Monad [bottom r;int - top (|> r;int (r;filter (|>. (i.= bottom) not)))] + top (|> r;int (r;filter (|>. (i/= bottom) not)))] (if ( top bottom) (wrap (&;between number;Enum bottom top)) (wrap (&;between number;Enum top bottom)))))] - [gen-inner i.<] - [gen-outer i.>] + [gen-inner i/<] + [gen-outer i/>] ) (def: gen-singleton @@ -143,7 +143,7 @@ (do @ [[l m r] (|> (r;set number;Hash +3 r;int) (:: @ map (|>. S;to-list - (L;sort i.<) + (L;sort i/<) (case> (^ (list b t1 t2)) [b t1 t2] @@ -165,7 +165,7 @@ (do @ [[b t1 t2] (|> (r;set number;Hash +3 r;int) (:: @ map (|>. S;to-list - (L;sort i.<) + (L;sort i/<) (case> (^ (list b t1 t2)) [b t1 t2] @@ -192,7 +192,7 @@ [some-interval gen-interval [x0 x1 x2 x3] (|> (r;set number;Hash +4 r;int) (:: @ map (|>. S;to-list - (L;sort i.<) + (L;sort i/<) (case> (^ (list x0 x1 x2 x3)) [x0 x1 x2 x3] diff --git a/stdlib/test/test/lux/control/parser.lux b/stdlib/test/test/lux/control/parser.lux index 0f6b4a4b1..b5ec72dc5 100644 --- a/stdlib/test/test/lux/control/parser.lux +++ b/stdlib/test/test/lux/control/parser.lux @@ -106,14 +106,19 @@ (&;many s;nat))))) (test "Can use either parser." - (and (match 123 - (&;run (list (code;int 123) (code;int 456) (code;int 789)) - (&;either s;pos-int s;int))) - (match -123 - (&;run (list (code;int -123) (code;int 456) (code;int 789)) - (&;either s;pos-int s;int))) - (fails? (&;run (list (code;bool true) (code;int 456) (code;int 789)) - (&;either s;pos-int s;int))))) + (let [positive (: (s;Syntax Int) + (do &;Monad + [value s;int + _ (&;assert "" (i/> 0 value))] + (wrap value)))] + (and (match 123 + (&;run (list (code;int 123) (code;int 456) (code;int 789)) + (&;either positive s;int))) + (match -123 + (&;run (list (code;int -123) (code;int 456) (code;int 789)) + (&;either positive s;int))) + (fails? (&;run (list (code;bool true) (code;int 456) (code;int 789)) + (&;either positive s;int)))))) (test "Can create the opposite/negation of any parser." (and (fails? (&;run (list (code;int 123) (code;int 456) (code;int 789)) diff --git a/stdlib/test/test/lux/control/pipe.lux b/stdlib/test/test/lux/control/pipe.lux index 527db91c3..9147f501e 100644 --- a/stdlib/test/test/lux/control/pipe.lux +++ b/stdlib/test/test/lux/control/pipe.lux @@ -15,44 +15,44 @@ ($_ seq (test "Can dismiss previous pipeline results and begin a new line." (|> 20 - (i.* 3) - (i.+ 4) - (new> 0 i.inc) - (i.= 1))) + (i/* 3) + (i/+ 4) + (new> 0 i/inc) + (i/= 1))) (test "Can give names to piped values within a pipeline's scope." (|> 5 - (let> X [(i.+ X X)]) - (i.= 10))) + (let> X [(i/+ X X)]) + (i/= 10))) (test "Can do branching in pipelines." (and (|> 5 - (cond> [i.even?] [(i.* 2)] - [i.odd?] [(i.* 3)] + (cond> [i/even?] [(i/* 2)] + [i/odd?] [(i/* 3)] [(new> -1)]) - (i.= 15)) + (i/= 15)) (|> 4 - (cond> [i.even?] [(i.* 2)] - [i.odd?] [(i.* 3)]) - (i.= 8)) + (cond> [i/even?] [(i/* 2)] + [i/odd?] [(i/* 3)]) + (i/= 8)) (|> 5 - (cond> [i.even?] [(i.* 2)] + (cond> [i/even?] [(i/* 2)] [(new> -1)]) - (i.= -1)))) + (i/= -1)))) (test "Can loop within pipelines." (|> 1 - (loop> [(i.< 10)] - [i.inc]) - (i.= 10))) + (loop> [(i/< 10)] + [i/inc]) + (i/= 10))) (test "Can use monads within pipelines." (|> 5 (do> Monad - [(i.* 3)] - [(i.+ 4)] - [i.inc]) - (i.= 20))) + [(i/* 3)] + [(i/+ 4)] + [i/inc]) + (i/= 20))) (test "Can pattern-match against piped values." (|> 5 diff --git a/stdlib/test/test/lux/control/reader.lux b/stdlib/test/test/lux/control/reader.lux index 6a6133aa1..804660a2c 100644 --- a/stdlib/test/test/lux/control/reader.lux +++ b/stdlib/test/test/lux/control/reader.lux @@ -11,14 +11,14 @@ (context: "Readers" ($_ seq - (test "" (i.= 123 (&;run 123 &;ask))) - (test "" (i.= 246 (&;run 123 (&;local (i.* 2) &;ask)))) - (test "" (i.= 134 (&;run 123 (:: &;Functor map i.inc (i.+ 10))))) - (test "" (i.= 10 (&;run 123 (:: &;Applicative wrap 10)))) - (test "" (i.= 30 (&;run 123 (let [(^open "&/") &;Applicative] - (&/apply (&/wrap (i.+ 10)) (&/wrap 20)))))) - (test "" (i.= 30 (&;run 123 (do &;Monad - [f (wrap i.+) + (test "" (i/= 123 (&;run 123 &;ask))) + (test "" (i/= 246 (&;run 123 (&;local (i/* 2) &;ask)))) + (test "" (i/= 134 (&;run 123 (:: &;Functor map i/inc (i/+ 10))))) + (test "" (i/= 10 (&;run 123 (:: &;Applicative wrap 10)))) + (test "" (i/= 30 (&;run 123 (let [(^open "&/") &;Applicative] + (&/apply (&/wrap (i/+ 10)) (&/wrap 20)))))) + (test "" (i/= 30 (&;run 123 (do &;Monad + [f (wrap i/+) x (wrap 10) y (wrap 20)] (wrap (f x y)))))))) @@ -29,7 +29,7 @@ (|> (do (&;ReaderT io;Monad) [a (&;lift (io/wrap 123)) b (wrap 456)] - (wrap (i.+ a b))) + (wrap (i/+ a b))) (&;run "") io;run (case> 579 true diff --git a/stdlib/test/test/lux/control/state.lux b/stdlib/test/test/lux/control/state.lux index e2b25d051..070f3425c 100644 --- a/stdlib/test/test/lux/control/state.lux +++ b/stdlib/test/test/lux/control/state.lux @@ -16,7 +16,7 @@ (|> computation (&;run state) product;right - (n.= output))) + (n/= output))) (context: "Basics" (<| (times +100) @@ -33,16 +33,16 @@ [_ (&;put value)] &;get))) (test "Can update the state." - (with-conditions [state (n.* value state)] + (with-conditions [state (n/* value state)] (do &;Monad - [_ (&;update (n.* value))] + [_ (&;update (n/* value))] &;get))) (test "Can use the state." - (with-conditions [state (n.inc state)] - (&;use n.inc))) + (with-conditions [state (n/inc state)] + (&;use n/inc))) (test "Can use a temporary (local) state." - (with-conditions [state (n.* value state)] - (&;local (n.* value) + (with-conditions [state (n/* value state)] + (&;local (n/* value) &;get))) )))) @@ -53,20 +53,20 @@ value r;nat] ($_ seq (test "Can use functor." - (with-conditions [state (n.inc state)] - (:: &;Functor map n.inc &;get))) + (with-conditions [state (n/inc state)] + (:: &;Functor map n/inc &;get))) (test "Can use applicative." (let [(^open "&/") &;Applicative] (and (with-conditions [state value] (&/wrap value)) - (with-conditions [state (n.+ value value)] - (&/apply (&/wrap (n.+ value)) + (with-conditions [state (n/+ value value)] + (&/apply (&/wrap (n/+ value)) (&/wrap value)))))) (test "Can use monad." - (with-conditions [state (n.+ value value)] + (with-conditions [state (n/+ value value)] (: (&;State Nat Nat) (do &;Monad - [f (wrap n.+) + [f (wrap n/+) x (wrap value) y (wrap value)] (wrap (f x y)))))) @@ -84,32 +84,32 @@ (do (&;StateT io;Monad) [a (&;lift io;Monad (io/wrap left)) b (wrap right)] - (wrap (n.+ a b)))) + (wrap (n/+ a b)))) (&;run' state) io;run (case> [state' output'] - (and (n.= state state') - (n.= (n.+ left right) output'))))) + (and (n/= state state') + (n/= (n/+ left right) output'))))) )))) (context: "Loops" (<| (times +100) (do @ - [limit (|> r;nat (:: @ map (n.% +10))) + [limit (|> r;nat (:: @ map (n/% +10))) #let [condition (do &;Monad [state &;get] - (wrap (n.< limit state)))]] + (wrap (n/< limit state)))]] ($_ seq (test "'while' will only execute if the condition is true." - (|> (&;while condition (&;update n.inc)) + (|> (&;while condition (&;update n/inc)) (&;run +0) (case> [state' output'] - (n.= limit state')))) + (n/= limit state')))) (test "'do-while' will execute at least once." - (|> (&;do-while condition (&;update n.inc)) + (|> (&;do-while condition (&;update n/inc)) (&;run +0) (case> [state' output'] - (or (n.= limit state') - (and (n.= +0 limit) - (n.= +1 state')))))) + (or (n/= limit state') + (and (n/= +0 limit) + (n/= +1 state')))))) )))) diff --git a/stdlib/test/test/lux/control/writer.lux b/stdlib/test/test/lux/control/writer.lux index 8c9e1c676..cbabbb6cd 100644 --- a/stdlib/test/test/lux/control/writer.lux +++ b/stdlib/test/test/lux/control/writer.lux @@ -13,15 +13,15 @@ (let [(^open "&/") (&;Monad text;Monoid)] ($_ seq (test "Functor respects Writer." - (i.= 11 (product;right (&/map i.inc ["" 10])))) + (i/= 11 (product;right (&/map i/inc ["" 10])))) (test "Applicative respects Writer." - (and (i.= 20 (product;right (&/wrap 20))) - (i.= 30 (product;right (&/apply (&/wrap (i.+ 10)) (&/wrap 20)))))) + (and (i/= 20 (product;right (&/wrap 20))) + (i/= 30 (product;right (&/apply (&/wrap (i/+ 10)) (&/wrap 20)))))) (test "Monad respects Writer." - (i.= 30 (product;right (do (&;Monad text;Monoid) - [f (wrap i.+) + (i/= 30 (product;right (do (&;Monad text;Monoid) + [f (wrap i/+) a (wrap 10) b (wrap 20)] (wrap (f a b)))))) @@ -37,7 +37,7 @@ (|> (io;run (do (&;WriterT text;Monoid io;Monad) [a (lift (io/wrap 123)) b (wrap 456)] - (wrap (i.+ a b)))) + (wrap (i/+ a b)))) (case> ["" 579] true _ false))) )) diff --git a/stdlib/test/test/lux/data/bit.lux b/stdlib/test/test/lux/data/bit.lux index 62bc2ce0b..ac80f9b06 100644 --- a/stdlib/test/test/lux/data/bit.lux +++ b/stdlib/test/test/lux/data/bit.lux @@ -11,14 +11,14 @@ (<| (times +100) (do @ [pattern r;nat - idx (:: @ map (n.% &;width) r;nat)] + idx (:: @ map (n/% &;width) r;nat)] ($_ seq (test "Clearing and settings bits should alter the count." - (and (n.< (&;count (&;set idx pattern)) + (and (n/< (&;count (&;set idx pattern)) (&;count (&;clear idx pattern))) - (n.<= (&;count pattern) + (n/<= (&;count pattern) (&;count (&;clear idx pattern))) - (n.>= (&;count pattern) + (n/>= (&;count pattern) (&;count (&;set idx pattern))))) (test "Can query whether a bit is set." (and (or (and (&;set? idx pattern) @@ -31,41 +31,41 @@ (and (not (&;set? idx pattern)) (&;set? idx (&;flip idx pattern)))))) (test "The negation of a bit pattern should have a complementary bit count." - (n.= &;width - (n.+ (&;count pattern) + (n/= &;width + (n/+ (&;count pattern) (&;count (&;not pattern))))) (test "Can do simple binary boolean logic." - (and (n.= +0 + (and (n/= +0 (&;and pattern (&;not pattern))) - (n.= (&;not +0) + (n/= (&;not +0) (&;or pattern (&;not pattern))) - (n.= (&;not +0) + (n/= (&;not +0) (&;xor pattern (&;not pattern))) - (n.= +0 + (n/= +0 (&;xor pattern pattern)))) (test "rotate-left and rotate-right are inverses of one another." (and (|> pattern (&;rotate-left idx) (&;rotate-right idx) - (n.= pattern)) + (n/= pattern)) (|> pattern (&;rotate-right idx) (&;rotate-left idx) - (n.= pattern)))) + (n/= pattern)))) (test "Rotate as many spaces as the bit-pattern's width leaves the pattern unchanged." (and (|> pattern (&;rotate-left &;width) - (n.= pattern)) + (n/= pattern)) (|> pattern (&;rotate-right &;width) - (n.= pattern)))) + (n/= pattern)))) (test "Shift right respect the sign of ints." (let [value (nat-to-int pattern)] - (if (i.< 0 value) - (i.< 0 (&;signed-shift-right idx value)) - (i.>= 0 (&;signed-shift-right idx value))))) + (if (i/< 0 value) + (i/< 0 (&;signed-shift-right idx value)) + (i/>= 0 (&;signed-shift-right idx value))))) )))) diff --git a/stdlib/test/test/lux/data/coll/array.lux b/stdlib/test/test/lux/data/coll/array.lux index 5f679b910..663592c34 100644 --- a/stdlib/test/test/lux/data/coll/array.lux +++ b/stdlib/test/test/lux/data/coll/array.lux @@ -13,7 +13,7 @@ (def: bounded-size (r;Random Nat) (|> r;nat - (:: r;Monad map (|>. (n.% +100) (n.+ +1))))) + (:: r;Monad map (|>. (n/% +100) (n/+ +1))))) (context: "Arrays and their copies" (<| (times +100) @@ -27,7 +27,7 @@ (@;new size))]] ($_ seq (test "Size function must correctly return size of array." - (n.= size (@;size original))) + (n/= size (@;size original))) (test "Cloning an array should yield and identical array, but not the same one." (and (:: (@;Eq number;Eq) = original clone) (not (is original clone)))) @@ -39,7 +39,7 @@ (exec (:: @;Fold fold (function [x idx] (exec (@;write idx x manual-copy) - (n.inc idx))) + (n/inc idx))) +0 original) (:: (@;Eq number;Eq) = original manual-copy))) @@ -53,9 +53,9 @@ (<| (times +100) (do @ [size bounded-size - idx (:: @ map (n.% size) r;nat) + idx (:: @ map (n/% size) r;nat) array (|> (r;array size r;nat) - (r;filter (|>. @;to-list (list;any? n.odd?)))) + (r;filter (|>. @;to-list (list;any? n/odd?)))) #let [value (maybe;assume (@;read idx array))]] ($_ seq (test "Shouldn't be able to find a value in an unoccupied cell." @@ -64,16 +64,16 @@ #;None true)) (test "You should be able to access values put into the array." (case (@;read idx (@;write idx value array)) - (#;Some value') (n.= value' value) + (#;Some value') (n/= value' value) #;None false)) (test "All cells should be occupied on a full array." - (and (n.= size (@;occupied array)) - (n.= +0 (@;vacant array)))) + (and (n/= size (@;occupied array)) + (n/= +0 (@;vacant array)))) (test "Filtering mutates the array to remove invalid values." - (exec (@;filter n.even? array) - (and (n.< size (@;occupied array)) - (n.> +0 (@;vacant array)) - (n.= size (n.+ (@;occupied array) + (exec (@;filter n/even? array) + (and (n/< size (@;occupied array)) + (n/> +0 (@;vacant array)) + (n/= size (n/+ (@;occupied array) (@;vacant array)))))) )))) @@ -82,16 +82,16 @@ (do @ [size bounded-size array (|> (r;array size r;nat) - (r;filter (|>. @;to-list (list;any? n.even?))))] + (r;filter (|>. @;to-list (list;any? n/even?))))] ($_ seq (test "Can find values inside arrays." - (|> (@;find n.even? array) + (|> (@;find n/even? array) (case> (#;Some _) true #;None false))) (test "Can find values inside arrays (with access to indices)." (|> (@;find+ (function [idx n] - (and (n.even? n) - (n.< size idx))) + (and (n/even? n) + (n/< size idx))) array) (case> (#;Some _) true #;None false))))))) @@ -109,8 +109,8 @@ (and (= array copy) (not (is array copy))))) (test "Functor should go over all available array elements." - (let [there (map n.inc array) - back-again (map n.dec there)] + (let [there (map n/inc array) + back-again (map n/dec there)] (and (not (= array there)) (= array back-again))))))))) @@ -126,7 +126,7 @@ fusion (compose left right)]] ($_ seq (test "Appending two arrays should produce a new one twice as large." - (n.= (n.+ sizeL sizeR) (@;size fusion))) + (n/= (n/+ sizeL sizeR) (@;size fusion))) (test "First elements of fused array should equal the first array." (|> (: (Array Nat) (@;new sizeL)) diff --git a/stdlib/test/test/lux/data/coll/dict.lux b/stdlib/test/test/lux/data/coll/dict.lux index ddc1ddd2d..4f1b94478 100644 --- a/stdlib/test/test/lux/data/coll/dict.lux +++ b/stdlib/test/test/lux/data/coll/dict.lux @@ -15,17 +15,17 @@ (context: "Dictionaries." (<| (times +100) (do @ - [#let [capped-nat (:: r;Monad map (n.% +100) r;nat)] + [#let [capped-nat (:: r;Monad map (n/% +100) r;nat)] size capped-nat dict (r;dict number;Hash size r;nat capped-nat) non-key (|> r;nat (r;filter (function [key] (not (&;contains? key dict))))) test-val (|> r;nat (r;filter (function [val] (not (list;member? number;Eq (&;values dict) val)))))] ($_ seq (test "Size function should correctly represent Dict size." - (n.= size (&;size dict))) + (n/= size (&;size dict))) (test "Dicts of size 0 should be considered empty." - (if (n.= +0 size) + (if (n/= +0 size) (&;empty? dict) (not (&;empty? dict)))) @@ -52,19 +52,19 @@ (test "Should be able to put and then get a value." (case (&;get non-key (&;put non-key test-val dict)) - (#;Some v) (n.= test-val v) + (#;Some v) (n/= test-val v) _ true)) (test "Should be able to put~ and then get a value." (case (&;get non-key (&;put~ non-key test-val dict)) - (#;Some v) (n.= test-val v) + (#;Some v) (n/= test-val v) _ true)) (test "Shouldn't be able to put~ an existing key." - (or (n.= +0 size) + (or (n/= +0 size) (let [first-key (|> dict &;keys list;head maybe;assume)] (case (&;get first-key (&;put~ first-key test-val dict)) - (#;Some v) (not (n.= test-val v)) + (#;Some v) (not (n/= test-val v)) _ true)))) (test "Removing a key should make it's value inaccessible." @@ -74,10 +74,10 @@ (test "Should be possible to update values via their keys." (let [base (&;put non-key test-val dict) - updt (&;update non-key n.inc base)] + updt (&;update non-key n/inc base)] (case [(&;get non-key base) (&;get non-key updt)] [(#;Some x) (#;Some y)] - (n.= (n.inc x) y) + (n/= (n/inc x) y) _ false))) @@ -85,8 +85,8 @@ (test "Additions and removals to a Dict should affect its size." (let [plus (&;put non-key test-val dict) base (&;remove non-key plus)] - (and (n.= (n.inc (&;size dict)) (&;size plus)) - (n.= (n.dec (&;size plus)) (&;size base))))) + (and (n/= (n/inc (&;size dict)) (&;size plus)) + (n/= (n/dec (&;size plus)) (&;size base))))) (test "A Dict should equal itself & going to<->from lists shouldn't change that." (let [(^open) (&;Eq number;Eq)] @@ -99,30 +99,30 @@ (test "If you merge, and the second dict has overlapping keys, it should overwrite yours." (let [dict' (|> dict &;entries - (list/map (function [[k v]] [k (n.inc v)])) + (list/map (function [[k v]] [k (n/inc v)])) (&;from-list number;Hash)) (^open) (&;Eq number;Eq)] (= dict' (&;merge dict' dict)))) (test "Can merge values in such a way that they become combined." - (list;every? (function [[x x*2]] (n.= (n.* +2 x) x*2)) + (list;every? (function [[x x*2]] (n/= (n/* +2 x) x*2)) (list;zip2 (&;values dict) - (&;values (&;merge-with n.+ dict dict))))) + (&;values (&;merge-with n/+ dict dict))))) (test "Should be able to select subset of keys from dict." (|> dict (&;put non-key test-val) (&;select (list non-key)) &;size - (n.= +1))) + (n/= +1))) (test "Should be able to re-bind existing values to different keys." - (or (n.= +0 size) + (or (n/= +0 size) (let [first-key (|> dict &;keys list;head maybe;assume) rebound (&;re-bind first-key non-key dict)] - (and (n.= (&;size dict) (&;size rebound)) + (and (n/= (&;size dict) (&;size rebound)) (&;contains? non-key rebound) (not (&;contains? first-key rebound)) - (n.= (maybe;assume (&;get first-key dict)) + (n/= (maybe;assume (&;get first-key dict)) (maybe;assume (&;get non-key rebound))))))) )))) diff --git a/stdlib/test/test/lux/data/coll/list.lux b/stdlib/test/test/lux/data/coll/list.lux index c1e69445f..942a2aa56 100644 --- a/stdlib/test/test/lux/data/coll/list.lux +++ b/stdlib/test/test/lux/data/coll/list.lux @@ -15,13 +15,13 @@ (def: bounded-size (r;Random Nat) (|> r;nat - (:: r;Monad map (|>. (n.% +100) (n.+ +10))))) + (:: r;Monad map (|>. (n/% +100) (n/+ +10))))) (context: "Lists: Part 1" (<| (times +100) (do @ [size bounded-size - idx (:: @ map (n.% size) r;nat) + idx (:: @ map (n/% size) r;nat) sample (r;list size r;nat) other-size bounded-size other-sample (r;list other-size r;nat) @@ -30,13 +30,13 @@ (^open "&/") &;Functor]] ($_ seq (test "The size function should correctly portray the size of the list." - (n.= size (&;size sample))) + (n/= size (&;size sample))) (test "The repeat function should produce as many elements as asked of it." - (n.= size (&;size (&;repeat size [])))) + (n/= size (&;size (&;repeat size [])))) (test "Reversing a list does not change it's size." - (n.= (&;size sample) + (n/= (&;size sample) (&;size (&;reverse sample)))) (test "Reversing a list twice results in the original list." @@ -44,19 +44,19 @@ (&;reverse (&;reverse sample)))) (test "Filtering by a predicate and its complement should result in a number of elements equal to the original list." - (and (n.= (&;size sample) - (n.+ (&;size (&;filter n.even? sample)) - (&;size (&;filter (bool;complement n.even?) sample)))) - (let [[plus minus] (&;partition n.even? sample)] - (n.= (&;size sample) - (n.+ (&;size plus) + (and (n/= (&;size sample) + (n/+ (&;size (&;filter n/even? sample)) + (&;size (&;filter (bool;complement n/even?) sample)))) + (let [[plus minus] (&;partition n/even? sample)] + (n/= (&;size sample) + (n/+ (&;size plus) (&;size minus)))))) (test "If every element in a list satisfies a predicate, there can't be any that satisfy its complement." - (if (&;every? n.even? sample) - (and (not (&;any? (bool;complement n.even?) sample)) - (&;empty? (&;filter (bool;complement n.even?) sample))) - (&;any? (bool;complement n.even?) sample))) + (if (&;every? n/even? sample) + (and (not (&;any? (bool;complement n/even?) sample)) + (&;empty? (&;filter (bool;complement n/even?) sample))) + (&;any? (bool;complement n/even?) sample))) (test "Any element of the list can be considered its member." (let [elem (maybe;assume (&;nth idx sample))] @@ -67,7 +67,7 @@ (<| (times +100) (do @ [size bounded-size - idx (:: @ map (n.% size) r;nat) + idx (:: @ map (n/% size) r;nat) sample (r;list size r;nat) other-size bounded-size other-sample (r;list other-size r;nat) @@ -90,15 +90,15 @@ (test "Functor should go over every element of the list." (let [(^open) &;Functor - there (map n.inc sample) - back-again (map n.dec there)] + there (map n/inc sample) + back-again (map n/dec there)] (and (not (= sample there)) (= sample back-again)))) (test "Splitting a list into chunks and re-appending them should yield the original list." (let [(^open) &;Monoid [left right] (&;split idx sample) - [left' right'] (&;split-with n.even? sample)] + [left' right'] (&;split-with n/even? sample)] (and (= sample (compose left right)) (= sample @@ -107,28 +107,28 @@ (compose (&;take idx sample) (&;drop idx sample))) (= sample - (compose (&;take-while n.even? sample) - (&;drop-while n.even? sample))) + (compose (&;take-while n/even? sample) + (&;drop-while n/even? sample))) ))) (test "Segmenting the list in pairs should yield as many elements as N/2." - (n.= (n./ +2 size) + (n/= (n// +2 size) (&;size (&;as-pairs sample)))) (test "Sorting a list shouldn't change it's size." - (n.= (&;size sample) - (&;size (&;sort n.< sample)))) + (n/= (&;size sample) + (&;size (&;sort n/< sample)))) (test "Sorting a list with one order should yield the reverse of sorting it with the opposite order." - (= (&;sort n.< sample) - (&;reverse (&;sort n.> sample)))) + (= (&;sort n/< sample) + (&;reverse (&;sort n/> sample)))) )))) (context: "Lists: Part 3" (<| (times +100) (do @ [size bounded-size - idx (:: @ map (n.% size) r;nat) + idx (:: @ map (n/% size) r;nat) sample (r;list size r;nat) other-size bounded-size other-sample (r;list other-size r;nat) @@ -137,8 +137,8 @@ (^open "&/") &;Functor]] ($_ seq (test "If you zip 2 lists, the result's size will be that of the smaller list." - (n.= (&;size (&;zip2 sample other-sample)) - (n.min (&;size sample) (&;size other-sample)))) + (n/= (&;size (&;zip2 sample other-sample)) + (n/min (&;size sample) (&;size other-sample)))) (test "I can pair-up elements of a list in order." (let [(^open) &;Functor @@ -150,21 +150,21 @@ (test "You can generate indices for any size, and they will be in ascending order." (let [(^open) &;Functor indices (&;indices size)] - (and (n.= size (&;size indices)) + (and (n/= size (&;size indices)) (= indices - (&;sort n.< indices)) - (&;every? (n.= (n.dec size)) - (&;zip2-with n.+ + (&;sort n/< indices)) + (&;every? (n/= (n/dec size)) + (&;zip2-with n/+ indices - (&;sort n.> indices))) + (&;sort n/> indices))) ))) (test "The 'interpose' function places a value between every member of a list." (let [(^open) &;Functor sample+ (&;interpose separator sample)] - (and (n.= (|> size (n.* +2) n.dec) + (and (n/= (|> size (n/* +2) n/dec) (&;size sample+)) - (|> sample+ &;as-pairs (map product;right) (&;every? (n.= separator)))))) + (|> sample+ &;as-pairs (map product;right) (&;every? (n/= separator)))))) (test "List append is a monoid." (let [(^open) &;Monoid] @@ -177,8 +177,8 @@ (test "Applicative allows you to create singleton lists, and apply lists of functions to lists of values." (let [(^open) &;Applicative] (and (= (list separator) (wrap separator)) - (= (map n.inc sample) - (apply (wrap n.inc) sample))))) + (= (map n/inc sample) + (apply (wrap n/inc) sample))))) (test "List concatenation is a monad." (let [(^open) &;Monad @@ -187,19 +187,19 @@ (join (list sample other-sample))))) (test "You can find any value that satisfies some criterium, if such values exist in the list." - (case (&;find n.even? sample) + (case (&;find n/even? sample) (#;Some found) - (and (n.even? found) - (&;any? n.even? sample) - (not (&;every? (bool;complement n.even?) sample))) + (and (n/even? found) + (&;any? n/even? sample) + (not (&;every? (bool;complement n/even?) sample))) #;None - (and (not (&;any? n.even? sample)) - (&;every? (bool;complement n.even?) sample)))) + (and (not (&;any? n/even? sample)) + (&;every? (bool;complement n/even?) sample)))) (test "You can iteratively construct a list, generating values until you're done." - (= (&;n.range +0 (n.dec size)) - (&;iterate (function [n] (if (n.< size n) (#;Some (n.inc n)) #;None)) + (= (&;n/range +0 (n/dec size)) + (&;iterate (function [n] (if (n/< size n) (#;Some (n/inc n)) #;None)) +0))) (test "Can enumerate all elements in a list." @@ -217,7 +217,7 @@ (|> (io;run (do (&;ListT io;Monad) [a (lift (io/wrap 123)) b (wrap 456)] - (wrap (i.+ a b)))) + (wrap (i/+ a b)))) (case> (^ (list 579)) true _ false))) )) diff --git a/stdlib/test/test/lux/data/coll/ordered/dict.lux b/stdlib/test/test/lux/data/coll/ordered/dict.lux index 49e4f2678..93774eb99 100644 --- a/stdlib/test/test/lux/data/coll/ordered/dict.lux +++ b/stdlib/test/test/lux/data/coll/ordered/dict.lux @@ -15,7 +15,7 @@ (context: "Dict" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (n.% +100))) + [size (|> r;nat (:: @ map (n/% +100))) keys (r;set number;Hash size r;nat) values (r;set number;Hash size r;nat) extra-key (|> r;nat (r;filter (|>. (s;member? keys) not))) @@ -24,13 +24,13 @@ (s;to-list values)) sample (&;from-list number;Order pairs) sorted-pairs (list;sort (function [[left _] [right _]] - (n.< left right)) + (n/< left right)) pairs) sorted-values (L/map product;right sorted-pairs) (^open "&/") (&;Eq number;Eq)]] ($_ seq (test "Can query the size of a dictionary." - (n.= size (&;size sample))) + (n/= size (&;size sample))) (test "Can query value for minimum key." (case [(&;min sample) (list;head sorted-values)] @@ -38,7 +38,7 @@ true [(#;Some reference) (#;Some sample)] - (n.= reference sample) + (n/= reference sample) _ false)) @@ -49,7 +49,7 @@ true [(#;Some reference) (#;Some sample)] - (n.= reference sample) + (n/= reference sample) _ false)) @@ -62,8 +62,8 @@ (test "Order is preserved." (let [(^open "L/") (list;Eq (: (Eq [Nat Nat]) (function [[kr vr] [ks vs]] - (and (n.= kr ks) - (n.= vr vs)))))] + (and (n/= kr ks) + (n/= vr vs)))))] (L/= (&;entries sample) sorted-pairs))) @@ -80,7 +80,7 @@ (case [(&;get extra-key sample') (&;get extra-key sample'')] [(#;Some found) #;None] - (n.= extra-value found) + (n/= extra-value found) _ false))) diff --git a/stdlib/test/test/lux/data/coll/ordered/set.lux b/stdlib/test/test/lux/data/coll/ordered/set.lux index f01db29a5..87c720597 100644 --- a/stdlib/test/test/lux/data/coll/ordered/set.lux +++ b/stdlib/test/test/lux/data/coll/ordered/set.lux @@ -13,7 +13,7 @@ (def: gen-nat (r;Random Nat) (|> r;nat - (:: r;Monad map (n.% +100)))) + (:: r;Monad map (n/% +100)))) (context: "Sets" (<| (times +100) @@ -25,12 +25,12 @@ #let [(^open "&/") &;Eq setL (&;from-list number;Order listL) setR (&;from-list number;Order listR) - sortedL (list;sort n.< listL) + sortedL (list;sort n/< listL) minL (list;head sortedL) maxL (list;last sortedL)]] ($_ seq (test "I can query the size of a set." - (n.= sizeL (&;size setL))) + (n/= sizeL (&;size setL))) (test "Can query minimum value." (case [(&;min setL) minL] @@ -38,7 +38,7 @@ true [(#;Some reference) (#;Some sample)] - (n.= reference sample) + (n/= reference sample) _ false)) @@ -49,7 +49,7 @@ true [(#;Some reference) (#;Some sample)] - (n.= reference sample) + (n/= reference sample) _ false)) @@ -63,7 +63,7 @@ (let [listL (&;to-list setL) (^open "L/") (list;Eq number;Eq)] (L/= listL - (list;sort n.< listL)))) + (list;sort n/< listL)))) (test "Every set is a sub-set of the union of itself with another." (let [setLR (&;union setL setR)] diff --git a/stdlib/test/test/lux/data/coll/priority-queue.lux b/stdlib/test/test/lux/data/coll/priority-queue.lux index 7a3d5a659..f1f7999a0 100644 --- a/stdlib/test/test/lux/data/coll/priority-queue.lux +++ b/stdlib/test/test/lux/data/coll/priority-queue.lux @@ -22,19 +22,19 @@ (context: "Queues" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (n.% +100))) + [size (|> r;nat (:: @ map (n/% +100))) sample (gen-queue size) non-member-priority r;nat non-member (|> r;nat (r;filter (|>. (&;member? number;Eq sample) not)))] ($_ seq (test "I can query the size of a queue (and empty queues have size 0)." - (n.= size (&;size sample))) + (n/= size (&;size sample))) (test "Enqueueing and dequeing affects the size of queues." - (and (n.= (n.inc size) + (and (n/= (n/inc size) (&;size (&;push non-member-priority non-member sample))) - (or (n.= +0 (&;size sample)) - (n.= (n.dec size) + (or (n/= +0 (&;size sample)) + (n/= (n/dec size) (&;size (&;pop sample)))))) (test "I can query whether an element belongs to a queue." @@ -42,7 +42,7 @@ (&;member? number;Eq (&;push non-member-priority non-member sample) non-member)) - (or (n.= +0 (&;size sample)) + (or (n/= +0 (&;size sample)) (and (&;member? number;Eq sample (maybe;assume (&;peek sample))) diff --git a/stdlib/test/test/lux/data/coll/queue.lux b/stdlib/test/test/lux/data/coll/queue.lux index bf04cd90c..1a6f884cf 100644 --- a/stdlib/test/test/lux/data/coll/queue.lux +++ b/stdlib/test/test/lux/data/coll/queue.lux @@ -10,21 +10,21 @@ (context: "Queues" (<| (times +100) (do @ - [size (:: @ map (n.% +100) r;nat) + [size (:: @ map (n/% +100) r;nat) sample (r;queue size r;nat) non-member (|> r;nat (r;filter (. not (&;member? number;Eq sample))))] ($_ seq (test "I can query the size of a queue (and empty queues have size 0)." - (if (n.= +0 size) + (if (n/= +0 size) (&;empty? sample) - (n.= size (&;size sample)))) + (n/= size (&;size sample)))) (test "Enqueueing and dequeing affects the size of queues." - (and (n.= (n.inc size) (&;size (&;push non-member sample))) + (and (n/= (n/inc size) (&;size (&;push non-member sample))) (or (&;empty? sample) - (n.= (n.dec size) (&;size (&;pop sample)))) - (n.= size (&;size (&;pop (&;push non-member sample)))))) + (n/= (n/dec size) (&;size (&;pop sample)))) + (n/= size (&;size (&;pop (&;push non-member sample)))))) (test "Transforming to/from list can't change the queue." (let [(^open "&/") (&;Eq number;Eq)] diff --git a/stdlib/test/test/lux/data/coll/sequence.lux b/stdlib/test/test/lux/data/coll/sequence.lux index f52cb3abf..234456d1e 100644 --- a/stdlib/test/test/lux/data/coll/sequence.lux +++ b/stdlib/test/test/lux/data/coll/sequence.lux @@ -14,8 +14,8 @@ (context: "Sequences" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1)))) - idx (|> r;nat (:: @ map (n.% size))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +1)))) + idx (|> r;nat (:: @ map (n/% size))) sample (r;sequence size r;nat) other-sample (r;sequence size r;nat) non-member (|> r;nat (r;filter (. not (&;member? number;Eq sample)))) @@ -26,13 +26,13 @@ ($_ seq (test "Can query size of sequence." (if (&;empty? sample) - (and (n.= +0 size) - (n.= +0 (&;size sample))) - (n.= size (&;size sample)))) + (and (n/= +0 size) + (n/= +0 (&;size sample))) + (n/= size (&;size sample)))) (test "Can add and remove elements to sequences." - (and (n.= (n.inc size) (&;size (&;add non-member sample))) - (n.= (n.dec size) (&;size (&;pop sample))))) + (and (n/= (n/inc size) (&;size (&;add non-member sample))) + (n/= (n/dec size) (&;size (&;pop sample))))) (test "Can put and get elements into sequences." (|> sample @@ -43,9 +43,9 @@ (test "Can update elements of sequences." (|> sample - (&;put idx non-member) (&;update idx n.inc) + (&;put idx non-member) (&;update idx n/inc) (&;nth idx) maybe;assume - (n.= (n.inc non-member)))) + (n/= (n/inc non-member)))) (test "Can safely transform to/from lists." (|> sample &;to-list &;from-list (&/= sample))) @@ -55,18 +55,18 @@ (&;member? number;Eq (&;add non-member sample) non-member))) (test "Can fold over elements of sequence." - (n.= (List/fold n.+ +0 (&;to-list sample)) - (&/fold n.+ +0 sample))) + (n/= (List/fold n/+ +0 (&;to-list sample)) + (&/fold n/+ +0 sample))) (test "Functor goes over every element." - (let [there (&/map n.inc sample) - back-again (&/map n.dec there)] + (let [there (&/map n/inc sample) + back-again (&/map n/dec there)] (and (not (&/= sample there)) (&/= sample back-again)))) (test "Applicative allows you to create singleton sequences, and apply sequences of functions to sequences of values." (and (&/= (&;sequence non-member) (&/wrap non-member)) - (&/= (&/map n.inc sample) (&/apply (&/wrap n.inc) sample)))) + (&/= (&/map n/inc sample) (&/apply (&/wrap n/inc) sample)))) (test "Sequence concatenation is a monad." (&/= (&/compose sample other-sample) diff --git a/stdlib/test/test/lux/data/coll/set.lux b/stdlib/test/test/lux/data/coll/set.lux index c13f60f25..48b0905fa 100644 --- a/stdlib/test/test/lux/data/coll/set.lux +++ b/stdlib/test/test/lux/data/coll/set.lux @@ -11,7 +11,7 @@ (def: gen-nat (r;Random Nat) (|> r;nat - (:: r;Monad map (n.% +100)))) + (:: r;Monad map (n/% +100)))) (context: "Sets" (<| (times +100) @@ -25,8 +25,8 @@ #let [(^open "&/") &;Eq]] ($_ seq (test "I can query the size of a set." - (and (n.= sizeL (&;size setL)) - (n.= sizeR (&;size setR)))) + (and (n/= sizeL (&;size setL)) + (n/= sizeR (&;size setR)))) (test "Converting sets to/from lists can't change their values." (|> setL diff --git a/stdlib/test/test/lux/data/coll/stack.lux b/stdlib/test/test/lux/data/coll/stack.lux index 069a9258b..d9e365d61 100644 --- a/stdlib/test/test/lux/data/coll/stack.lux +++ b/stdlib/test/test/lux/data/coll/stack.lux @@ -12,7 +12,7 @@ (def: gen-nat (r;Random Nat) (|> r;nat - (:: r;Monad map (n.% +100)))) + (:: r;Monad map (n/% +100)))) (context: "Stacks" (<| (times +100) @@ -22,7 +22,7 @@ new-top gen-nat] ($_ seq (test "Can query the size of a stack." - (n.= size (&;size sample))) + (n/= size (&;size sample))) (test "Can peek inside non-empty stacks." (case (&;peek sample) @@ -32,14 +32,14 @@ (test "Popping empty stacks doesn't change anything. But, if they're non-empty, the top of the stack is removed." (let [sample' (&;pop sample)] - (or (n.= (&;size sample) (n.inc (&;size sample'))) + (or (n/= (&;size sample) (n/inc (&;size sample'))) (and (&;empty? sample) (&;empty? sample'))) )) (test "Pushing onto a stack always increases it by 1, adding a new value at the top." (and (is sample (&;pop (&;push new-top sample))) - (n.= (n.inc (&;size sample)) (&;size (&;push new-top sample))) + (n/= (n/inc (&;size sample)) (&;size (&;push new-top sample))) (|> (&;push new-top sample) &;peek maybe;assume (is new-top)))) )))) diff --git a/stdlib/test/test/lux/data/coll/stream.lux b/stdlib/test/test/lux/data/coll/stream.lux index fdb7965b2..8c3db3ac4 100644 --- a/stdlib/test/test/lux/data/coll/stream.lux +++ b/stdlib/test/test/lux/data/coll/stream.lux @@ -16,60 +16,60 @@ (context: "Streams" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +2)))) - offset (|> r;nat (:: @ map (n.% +100))) - factor (|> r;nat (:: @ map (|>. (n.% +100) (n.max +2)))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +2)))) + offset (|> r;nat (:: @ map (n/% +100))) + factor (|> r;nat (:: @ map (|>. (n/% +100) (n/max +2)))) elem r;nat cycle-seed (r;list size r;nat) - cycle-sample-idx (|> r;nat (:: @ map (n.% +1000))) + cycle-sample-idx (|> r;nat (:: @ map (n/% +1000))) #let [(^open "List/") (list;Eq number;Eq) - sample0 (&;iterate n.inc +0) - sample1 (&;iterate n.inc offset)]] + sample0 (&;iterate n/inc +0) + sample1 (&;iterate n/inc offset)]] ($_ seq (test "Can move along a stream and take slices off it." - (and (and (List/= (list;n.range +0 (n.dec size)) + (and (and (List/= (list;n/range +0 (n/dec size)) (&;take size sample0)) - (List/= (list;n.range offset (n.dec (n.+ offset size))) + (List/= (list;n/range offset (n/dec (n/+ offset size))) (&;take size (&;drop offset sample0))) (let [[drops takes...] (&;split size sample0)] - (and (List/= (list;n.range +0 (n.dec size)) + (and (List/= (list;n/range +0 (n/dec size)) drops) - (List/= (list;n.range size (n.dec (n.* +2 size))) + (List/= (list;n/range size (n/dec (n/* +2 size))) (&;take size takes...))))) - (and (List/= (list;n.range +0 (n.dec size)) - (&;take-while (n.< size) sample0)) - (List/= (list;n.range offset (n.dec (n.+ offset size))) - (&;take-while (n.< (n.+ offset size)) - (&;drop-while (n.< offset) sample0))) - (let [[drops takes...] (&;split-while (n.< size) sample0)] - (and (List/= (list;n.range +0 (n.dec size)) + (and (List/= (list;n/range +0 (n/dec size)) + (&;take-while (n/< size) sample0)) + (List/= (list;n/range offset (n/dec (n/+ offset size))) + (&;take-while (n/< (n/+ offset size)) + (&;drop-while (n/< offset) sample0))) + (let [[drops takes...] (&;split-while (n/< size) sample0)] + (and (List/= (list;n/range +0 (n/dec size)) drops) - (List/= (list;n.range size (n.dec (n.* +2 size))) - (&;take-while (n.< (n.* +2 size)) takes...))))) + (List/= (list;n/range size (n/dec (n/* +2 size))) + (&;take-while (n/< (n/* +2 size)) takes...))))) )) (test "Can repeat any element and infinite number of times." - (n.= elem (&;nth offset (&;repeat elem)))) + (n/= elem (&;nth offset (&;repeat elem)))) (test "Can obtain the head & tail of a stream." - (and (n.= offset (&;head sample1)) - (List/= (list;n.range (n.inc offset) (n.+ offset size)) + (and (n/= offset (&;head sample1)) + (List/= (list;n/range (n/inc offset) (n/+ offset size)) (&;take size (&;tail sample1))))) (test "Can filter streams." - (and (n.= (n.* +2 offset) + (and (n/= (n/* +2 offset) (&;nth offset - (&;filter n.even? sample0))) - (let [[evens odds] (&;partition n.even? (&;iterate n.inc +0))] - (and (n.= (n.* +2 offset) + (&;filter n/even? sample0))) + (let [[evens odds] (&;partition n/even? (&;iterate n/inc +0))] + (and (n/= (n/* +2 offset) (&;nth offset evens)) - (n.= (n.inc (n.* +2 offset)) + (n/= (n/inc (n/* +2 offset)) (&;nth offset odds)))))) (test "Functor goes over 'all' elements in a stream." (let [(^open "&/") &;Functor - there (&/map (n.* factor) sample0) - back-again (&/map (n./ factor) there)] + there (&/map (n/* factor) sample0) + back-again (&/map (n// factor) there)] (and (not (List/= (&;take size sample0) (&;take size there))) (List/= (&;take size sample0) @@ -77,26 +77,26 @@ (test "CoMonad produces a value for every element in a stream." (let [(^open "&/") &;Functor] - (List/= (&;take size (&/map (n.* factor) sample1)) + (List/= (&;take size (&/map (n/* factor) sample1)) (&;take size (be &;CoMonad [inputs sample1] - (n.* factor (&;head inputs))))))) + (n/* factor (&;head inputs))))))) (test "'unfold' generalizes 'iterate'." (let [(^open "&/") &;Functor (^open "List/") (list;Eq text;Eq)] (List/= (&;take size - (&/map Nat/encode (&;iterate n.inc offset))) + (&/map Nat/encode (&;iterate n/inc offset))) (&;take size - (&;unfold (function [n] [(n.inc n) (Nat/encode n)]) + (&;unfold (function [n] [(n/inc n) (Nat/encode n)]) offset))))) (test "Can cycle over the same elements as an infinite stream." (|> (&;cycle cycle-seed) maybe;assume (&;nth cycle-sample-idx) - (n.= (|> cycle-seed - (list;nth (n.% size cycle-sample-idx)) + (n/= (|> cycle-seed + (list;nth (n/% size cycle-sample-idx)) maybe;assume)))) )))) diff --git a/stdlib/test/test/lux/data/coll/tree/rose.lux b/stdlib/test/test/lux/data/coll/tree/rose.lux index 7a69fbf0e..09f3f13f6 100644 --- a/stdlib/test/test/lux/data/coll/tree/rose.lux +++ b/stdlib/test/test/lux/data/coll/tree/rose.lux @@ -18,11 +18,11 @@ (r;either (:: r;Monad map (|>. &;leaf [+1]) r;nat) (do r;Monad [value r;nat - num-children (|> r;nat (:: @ map (n.% +3))) + num-children (|> r;nat (:: @ map (n/% +3))) children' (r;list num-children gen-tree) - #let [size' (L/fold n.+ +0 (L/map product;left children')) + #let [size' (L/fold n/+ +0 (L/map product;left children')) children (L/map product;right children')]] - (wrap [(n.inc size') + (wrap [(n/inc size') (&;branch value children)])) )))) @@ -38,7 +38,7 @@ (&/= sample sample)) (test "Can flatten a tree to get all the nodes as a flat tree." - (n.= size + (n/= size (list;size (&;flatten sample)))) (test "Can fold trees." diff --git a/stdlib/test/test/lux/data/coll/tree/zipper.lux b/stdlib/test/test/lux/data/coll/tree/zipper.lux index 691510885..f184090db 100644 --- a/stdlib/test/test/lux/data/coll/tree/zipper.lux +++ b/stdlib/test/test/lux/data/coll/tree/zipper.lux @@ -18,7 +18,7 @@ (r;rec (function [gen-tree] (do r;Monad ## Each branch can have, at most, 1 child. - [size (|> r;nat (:: @ map (n.% +2)))] + [size (|> r;nat (:: @ map (n/% +2)))] (r;seq r;nat (r;list size gen-tree)))))) @@ -95,7 +95,7 @@ #;None true)))))) (test "Can set and update the value of a node." - (|> sample &;zip (&;set new-val) &;value (n.= new-val))) + (|> sample &;zip (&;set new-val) &;value (n/= new-val))) (test "Zipper traversal follows the outline of the tree depth-first." (L/= (rose;flatten sample) diff --git a/stdlib/test/test/lux/data/color.lux b/stdlib/test/test/lux/data/color.lux index ba0772349..6a97b0e72 100644 --- a/stdlib/test/test/lux/data/color.lux +++ b/stdlib/test/test/lux/data/color.lux @@ -23,10 +23,10 @@ (-> @;Color @;Color Frac) (let [[fr fg fb] (@;unpack from) [tr tg tb] (@;unpack to)] - (math;root2 ($_ f.+ - (|> (scale tr) (f.- (scale fr)) square) - (|> (scale tg) (f.- (scale fg)) square) - (|> (scale tb) (f.- (scale fb)) square))))) + (math;root2 ($_ f/+ + (|> (scale tr) (f/- (scale fr)) square) + (|> (scale tg) (f/- (scale fg)) square) + (|> (scale tb) (f/- (scale fb)) square))))) (def: error-margin Frac 1.8) @@ -48,33 +48,33 @@ (do @ [any color colorful (|> color - (r;filter (function [color] (|> (distance color black) (f.>= 100.0)))) - (r;filter (function [color] (|> (distance color white) (f.>= 100.0))))) + (r;filter (function [color] (|> (distance color black) (f/>= 100.0)))) + (r;filter (function [color] (|> (distance color white) (f/>= 100.0))))) mediocre (|> color (r;filter (|>. saturation ((function [saturation] - (and (f.>= 0.25 saturation) - (f.<= 0.75 saturation))))))) - ratio (|> r;frac (r;filter (f.>= 0.5)))] + (and (f/>= 0.25 saturation) + (f/<= 0.75 saturation))))))) + ratio (|> r;frac (r;filter (f/>= 0.5)))] ($_ seq (test "Has equality." (:: @;Eq = any any)) (test "Can convert to/from HSL." (|> any @;to-hsl @;from-hsl (distance any) - (f.<= error-margin))) + (f/<= error-margin))) (test "Can convert to/from HSB." (|> any @;to-hsb @;from-hsb (distance any) - (f.<= error-margin))) + (f/<= error-margin))) (test "Can convert to/from CMYK." (|> any @;to-cmyk @;from-cmyk (distance any) - (f.<= error-margin))) + (f/<= error-margin))) (test "Can interpolate between 2 colors." - (and (f.<= (distance colorful black) + (and (f/<= (distance colorful black) (distance (@;darker ratio colorful) black)) - (f.<= (distance colorful white) + (f/<= (distance colorful white) (distance (@;brighter ratio colorful) white)))) (test "Can calculate complement." (let [~any (@;complement any) @@ -82,17 +82,17 @@ (and (not (@/= any ~any)) (@/= any (@;complement ~any))))) (test "Can saturate color." - (f.> (saturation mediocre) + (f/> (saturation mediocre) (saturation (@;saturate ratio mediocre)))) (test "Can de-saturate color." - (f.< (saturation mediocre) + (f/< (saturation mediocre) (saturation (@;de-saturate ratio mediocre)))) (test "Can gray-scale color." (let [gray'ed (@;gray-scale mediocre)] - (and (f.= 0.0 + (and (f/= 0.0 (saturation gray'ed)) (|> (luminance gray'ed) - (f.- (luminance mediocre)) + (f/- (luminance mediocre)) frac/abs - (f.<= error-margin))))) + (f/<= error-margin))))) )))) diff --git a/stdlib/test/test/lux/data/error.lux b/stdlib/test/test/lux/data/error.lux index a72a45403..9eeec4fbc 100644 --- a/stdlib/test/test/lux/data/error.lux +++ b/stdlib/test/test/lux/data/error.lux @@ -12,31 +12,31 @@ ($_ seq (test "Functor correctly handles both cases." (and (|> (: (&;Error Int) (#&;Success 10)) - (&/map i.inc) + (&/map i/inc) (case> (#&;Success 11) true _ false)) (|> (: (&;Error Int) (#&;Error "YOLO")) - (&/map i.inc) + (&/map i/inc) (case> (#&;Error "YOLO") true _ false)) )) (test "Applicative correctly handles both cases." (and (|> (&/wrap 20) (case> (#&;Success 20) true _ false)) - (|> (&/apply (&/wrap i.inc) (&/wrap 10)) + (|> (&/apply (&/wrap i/inc) (&/wrap 10)) (case> (#&;Success 11) true _ false)) - (|> (&/apply (&/wrap i.inc) (#&;Error "YOLO")) + (|> (&/apply (&/wrap i/inc) (#&;Error "YOLO")) (case> (#&;Error "YOLO") true _ false)))) (test "Monad correctly handles both cases." (and (|> (do &;Monad - [f (wrap i.+) + [f (wrap i/+) a (wrap 10) b (wrap 20)] (wrap (f a b))) (case> (#&;Success 30) true _ false)) (|> (do &;Monad - [f (wrap i.+) + [f (wrap i/+) a (#&;Error "YOLO") b (wrap 20)] (wrap (f a b))) @@ -51,6 +51,6 @@ (|> (io;run (do (&;ErrorT io;Monad) [a (lift (io/wrap 123)) b (wrap 456)] - (wrap (i.+ a b)))) + (wrap (i/+ a b)))) (case> (#&;Success 579) true _ false))))) diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux index 167e80555..c8ba05f1d 100644 --- a/stdlib/test/test/lux/data/format/json.lux +++ b/stdlib/test/test/lux/data/format/json.lux @@ -11,7 +11,7 @@ ["e" error] [bool] [maybe] - [number "i/" Number] + [number] (format ["@" json]) (coll [sequence #+ sequence] ["d" dict] @@ -37,11 +37,11 @@ (r;Random @;JSON) (r;rec (function [gen-json] (do r;Monad - [size (:: @ map (n.% +2) r;nat)] + [size (:: @ map (n/% +2) r;nat)] ($_ r;alt (:: @ wrap []) r;bool - (|> r;frac (:: @ map (f.* 1_000_000.0))) + (|> r;frac (:: @ map (f/* 1_000_000.0))) (r;text size) (r;sequence size gen-json) (r;dict text;Hash size (r;text size) gen-json) @@ -108,7 +108,7 @@ (def: gen-record (r;Random Record) (do r;Monad - [size (:: @ map (n.% +2) r;nat)] + [size (:: @ map (n/% +2) r;nat)] ($_ r;seq ## (:: @ wrap []) ## r;bool @@ -139,12 +139,12 @@ (:: text;Eq = left' right') [(#Case2 left') (#Case2 right')] - (f.= left' right') + (f/= left' right') _ false))] (and ## (:: bool;Eq = (get@ #bool recL) (get@ #bool recR)) - ## (f.= (get@ #frac recL) (get@ #frac recR)) + ## (f/= (get@ #frac recL) (get@ #frac recR)) ## (:: text;Eq = (get@ #text recL) (get@ #text recR)) ## (:: (maybe;Eq number;Eq) = (get@ #maybe recL) (get@ #maybe recR)) ## (:: (list;Eq number;Eq) = (get@ #list recL) (get@ #list recR)) @@ -152,7 +152,7 @@ ## (let [[tL0 tL1 tL2] (get@ #tuple recL) ## [tR0 tR1 tR2] (get@ #tuple recR)] ## (and (:: bool;Eq = tL0 tR0) - ## (f.= tL1 tR1) + ## (f/= tL1 tR1) ## (:: text;Eq = tL2 tR2))) ## (:: (d;Eq number;Eq) = (get@ #dict recL) (get@ #dict recR)) ## (:: Eq = (get@ #recursive recL) (get@ #recursive recR)) @@ -163,7 +163,8 @@ )))) (context: "Polytypism" - (<| (times +100) + (<| (seed +10473881104006775240) + ## (times +100) (do @ [sample gen-record #let [(^open "@/") Eq diff --git a/stdlib/test/test/lux/data/format/xml.lux b/stdlib/test/test/lux/data/format/xml.lux index 817c7159e..bcbf63f9e 100644 --- a/stdlib/test/test/lux/data/format/xml.lux +++ b/stdlib/test/test/lux/data/format/xml.lux @@ -25,12 +25,12 @@ (def: xml-char^ (r;Random Nat) (do r;Monad - [idx (|> r;nat (:: @ map (n.% (text;size char-range))))] + [idx (|> r;nat (:: @ map (n/% (text;size char-range))))] (wrap (maybe;assume (text;nth idx char-range))))) (def: (size^ bottom top) (-> Nat Nat (r;Random Nat)) - (let [constraint (|>. (n.% top) (n.max bottom))] + (let [constraint (|>. (n/% top) (n/max bottom))] (r/map constraint r;nat))) (def: (xml-text^ bottom top) @@ -78,7 +78,7 @@ (<| (times +100) (do @ [text (xml-text^ +1 +10) - num-children (|> r;nat (:: @ map (n.% +5))) + num-children (|> r;nat (:: @ map (n/% +5))) children (r;list num-children (xml-text^ +1 +10)) tag xml-identifier^ attr xml-identifier^ diff --git a/stdlib/test/test/lux/data/ident.lux b/stdlib/test/test/lux/data/ident.lux index 24b06c7c7..f03cfa9a2 100644 --- a/stdlib/test/test/lux/data/ident.lux +++ b/stdlib/test/test/lux/data/ident.lux @@ -17,14 +17,14 @@ (<| (times +100) (do @ [## First Ident - sizeM1 (|> r;nat (:: @ map (n.% +100))) - sizeN1 (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1)))) + sizeM1 (|> r;nat (:: @ map (n/% +100))) + sizeN1 (|> r;nat (:: @ map (|>. (n/% +100) (n/max +1)))) module1 (gen-part sizeM1) name1 (gen-part sizeN1) #let [ident1 [module1 name1]] ## Second Ident - sizeM2 (|> r;nat (:: @ map (n.% +100))) - sizeN2 (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1)))) + sizeM2 (|> r;nat (:: @ map (n/% +100))) + sizeN2 (|> r;nat (:: @ map (|>. (n/% +100) (n/max +1)))) module2 (gen-part sizeM2) name2 (gen-part sizeN2) #let [ident2 [module2 name2]] diff --git a/stdlib/test/test/lux/data/lazy.lux b/stdlib/test/test/lux/data/lazy.lux index ce0e6a79a..52e850d80 100644 --- a/stdlib/test/test/lux/data/lazy.lux +++ b/stdlib/test/test/lux/data/lazy.lux @@ -11,11 +11,11 @@ (do @ [left r;nat right r;nat - #let [lazy (&;freeze (n.* left right)) - expected (n.* left right)]] + #let [lazy (&;freeze (n/* left right)) + expected (n/* left right)]] ($_ seq (test "Lazying does not alter the expected value." - (n.= expected + (n/= expected (&;thaw lazy))) (test "Lazy values only evaluate once." (and (not (is expected @@ -31,27 +31,27 @@ ($_ seq (test "Functor map." (|> (&;freeze sample) - (:: &;Functor map n.inc) + (:: &;Functor map n/inc) &;thaw - (n.= (n.inc sample)))) + (n/= (n/inc sample)))) (test "Applicative wrap." (|> sample (:: &;Applicative wrap) &;thaw - (n.= sample))) + (n/= sample))) (test "Applicative apply." (let [(^open "&/") &;Applicative] - (|> (&/apply (&/wrap n.inc) (&/wrap sample)) + (|> (&/apply (&/wrap n/inc) (&/wrap sample)) &;thaw - (n.= (n.inc sample))))) + (n/= (n/inc sample))))) (test "Monad." (|> (do &;Monad - [f (wrap n.inc) + [f (wrap n/inc) a (wrap sample)] (wrap (f a))) &;thaw - (n.= (n.inc sample)))) + (n/= (n/inc sample)))) )))) diff --git a/stdlib/test/test/lux/data/maybe.lux b/stdlib/test/test/lux/data/maybe.lux index fed83c4b9..16d5c850d 100644 --- a/stdlib/test/test/lux/data/maybe.lux +++ b/stdlib/test/test/lux/data/maybe.lux @@ -51,6 +51,6 @@ (|> (io;run (do (&;MaybeT io;Monad) [a (lift (io/wrap 123)) b (wrap 456)] - (wrap (i.+ a b)))) + (wrap (i/+ a b)))) (case> (#;Some 579) true _ false))))) diff --git a/stdlib/test/test/lux/data/number.lux b/stdlib/test/test/lux/data/number.lux index c5ff11668..2fe050740 100644 --- a/stdlib/test/test/lux/data/number.lux +++ b/stdlib/test/test/lux/data/number.lux @@ -84,7 +84,7 @@ ["Nat" r;nat Number Order Interval (function [_] true)] ["Int" r;int Number Order Interval (function [_] true)] ## Both min and max values will be positive (thus, greater than zero) - ["Frac" r;frac Number Order Interval (f.> 0.0)] + ["Frac" r;frac Number Order Interval (f/> 0.0)] ["Deg" r;deg Number Order Interval (function [_] true)] ) @@ -101,22 +101,22 @@ (= x (compose x identity)) (= identity (compose identity identity)))))))] - ["Nat/Add" r;nat Number Order Add@Monoid (n.% +1000) (function [_] true)] - ["Nat/Mul" r;nat Number Order Mul@Monoid (n.% +1000) (function [_] true)] - ["Nat/Min" r;nat Number Order Min@Monoid (n.% +1000) (function [_] true)] - ["Nat/Max" r;nat Number Order Max@Monoid (n.% +1000) (function [_] true)] - ["Int/Add" r;int Number Order Add@Monoid (i.% 1000) (function [_] true)] - ["Int/Mul" r;int Number Order Mul@Monoid (i.% 1000) (function [_] true)] - ["Int/Min" r;int Number Order Min@Monoid (i.% 1000) (function [_] true)] - ["Int/Max" r;int Number Order Max@Monoid (i.% 1000) (function [_] true)] - ["Frac/Add" r;frac Number Order Add@Monoid (f.% 1000.0) (f.> 0.0)] - ["Frac/Mul" r;frac Number Order Mul@Monoid (f.% 1000.0) (f.> 0.0)] - ["Frac/Min" r;frac Number Order Min@Monoid (f.% 1000.0) (f.> 0.0)] - ["Frac/Max" r;frac Number Order Max@Monoid (f.% 1000.0) (f.> 0.0)] - ["Deg/Add" r;deg Number Order Add@Monoid (d.% .125) (function [_] true)] - ## ["Deg/Mul" r;deg Number Order Mul@Monoid (d.% .125) (function [_] true)] - ["Deg/Min" r;deg Number Order Min@Monoid (d.% .125) (function [_] true)] - ["Deg/Max" r;deg Number Order Max@Monoid (d.% .125) (function [_] true)] + ["Nat/Add" r;nat Number Order Add@Monoid (n/% +1000) (function [_] true)] + ["Nat/Mul" r;nat Number Order Mul@Monoid (n/% +1000) (function [_] true)] + ["Nat/Min" r;nat Number Order Min@Monoid (n/% +1000) (function [_] true)] + ["Nat/Max" r;nat Number Order Max@Monoid (n/% +1000) (function [_] true)] + ["Int/Add" r;int Number Order Add@Monoid (i/% 1000) (function [_] true)] + ["Int/Mul" r;int Number Order Mul@Monoid (i/% 1000) (function [_] true)] + ["Int/Min" r;int Number Order Min@Monoid (i/% 1000) (function [_] true)] + ["Int/Max" r;int Number Order Max@Monoid (i/% 1000) (function [_] true)] + ["Frac/Add" r;frac Number Order Add@Monoid (f/% 1000.0) (f/> 0.0)] + ["Frac/Mul" r;frac Number Order Mul@Monoid (f/% 1000.0) (f/> 0.0)] + ["Frac/Min" r;frac Number Order Min@Monoid (f/% 1000.0) (f/> 0.0)] + ["Frac/Max" r;frac Number Order Max@Monoid (f/% 1000.0) (f/> 0.0)] + ["Deg/Add" r;deg Number Order Add@Monoid (d/% .125) (function [_] true)] + ## ["Deg/Mul" r;deg Number Order Mul@Monoid (d/% .125) (function [_] true)] + ["Deg/Min" r;deg Number Order Min@Monoid (d/% .125) (function [_] true)] + ["Deg/Max" r;deg Number Order Max@Monoid (d/% .125) (function [_] true)] ) (do-template [ ] @@ -159,7 +159,7 @@ (<| (times +100) (do @ [raw r;frac - factor (|> r;nat (:: @ map (|>. (n.% +1000) (n.max +1)))) - #let [sample (|> factor nat-to-int int-to-frac (f.* raw))]] + factor (|> r;nat (:: @ map (|>. (n/% +1000) (n/max +1)))) + #let [sample (|> factor nat-to-int int-to-frac (f/* raw))]] (test "Can convert frac values to/from their bit patterns." - (|> sample frac-to-bits bits-to-frac (f.= sample)))))) + (|> sample frac-to-bits bits-to-frac (f/= sample)))))) diff --git a/stdlib/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux index 410fa1cb9..c7b0691df 100644 --- a/stdlib/test/test/lux/data/number/complex.lux +++ b/stdlib/test/test/lux/data/number/complex.lux @@ -3,12 +3,9 @@ (lux [io] (control [monad #+ do Monad] pipe) - (data [text "Text/" Monoid] - text/format - [bool "b/" Eq] - [number "f/" Number] + (data [number "frac/" Number] ["&" number/complex] - (coll [list "List/" Fold Functor]) + (coll [list "list/" Functor]) [product]) [math] ["r" math/random]) @@ -18,19 +15,19 @@ (def: (within? margin standard value) (-> Frac &;Complex &;Complex Bool) - (let [real-dist (f/abs (f.- (get@ #&;real standard) - (get@ #&;real value))) - imgn-dist (f/abs (f.- (get@ #&;imaginary standard) - (get@ #&;imaginary value)))] - (and (f.< margin real-dist) - (f.< margin imgn-dist)))) + (let [real-dist (frac/abs (f/- (get@ #&;real standard) + (get@ #&;real value))) + imgn-dist (frac/abs (f/- (get@ #&;imaginary standard) + (get@ #&;imaginary value)))] + (and (f/< margin real-dist) + (f/< margin imgn-dist)))) (def: gen-dim (r;Random Frac) (do r;Monad - [factor (|> r;nat (:: @ map (|>. (n.% +1000) (n.max +1)))) - measure (|> r;frac (r;filter (f.> 0.0)))] - (wrap (f.* (|> factor nat-to-int int-to-frac) + [factor (|> r;nat (:: @ map (|>. (n/% +1000) (n/max +1)))) + measure (|> r;frac (r;filter (f/> 0.0)))] + (wrap (f/* (|> factor nat-to-int int-to-frac) measure)))) (def: gen-complex @@ -48,8 +45,8 @@ ($_ seq (test "Can build and tear apart complex numbers" (let [r+i (&;complex real imaginary)] - (and (f.= real (get@ #&;real r+i)) - (f.= imaginary (get@ #&;imaginary r+i))))) + (and (f/= real (get@ #&;real r+i)) + (f/= imaginary (get@ #&;imaginary r+i))))) (test "If either the real part or the imaginary part is NaN, the composite is NaN." (and (&;not-a-number? (&;complex number;not-a-number imaginary)) @@ -65,18 +62,18 @@ (test "Absolute value of complex >= absolute value of any of the parts." (let [r+i (&;complex real imaginary) abs (get@ #&;real (&;c.abs r+i))] - (and (f.>= (f/abs real) abs) - (f.>= (f/abs imaginary) abs)))) + (and (f/>= (frac/abs real) abs) + (f/>= (frac/abs imaginary) abs)))) (test "The absolute value of a complex number involving a NaN on either dimension, results in a NaN value." (and (number;not-a-number? (get@ #&;real (&;c.abs (&;complex number;not-a-number imaginary)))) (number;not-a-number? (get@ #&;real (&;c.abs (&;complex real number;not-a-number)))))) (test "The absolute value of a complex number involving an infinity on either dimension, results in an infinite value." - (and (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;positive-infinity imaginary)))) - (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;positive-infinity)))) - (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;negative-infinity imaginary)))) - (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;negative-infinity)))))) + (and (f/= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;positive-infinity imaginary)))) + (f/= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;positive-infinity)))) + (f/= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;negative-infinity imaginary)))) + (f/= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;negative-infinity)))))) )))) (context: "Addidion, substraction, multiplication and division" @@ -89,17 +86,17 @@ (test "Adding 2 complex numbers is the same as adding their parts." (let [z (&;c.+ y x)] (and (&;c.= z - (&;complex (f.+ (get@ #&;real y) + (&;complex (f/+ (get@ #&;real y) (get@ #&;real x)) - (f.+ (get@ #&;imaginary y) + (f/+ (get@ #&;imaginary y) (get@ #&;imaginary x))))))) (test "Subtracting 2 complex numbers is the same as adding their parts." (let [z (&;c.- y x)] (and (&;c.= z - (&;complex (f.- (get@ #&;real y) + (&;complex (f/- (get@ #&;real y) (get@ #&;real x)) - (f.- (get@ #&;imaginary y) + (f/- (get@ #&;imaginary y) (get@ #&;imaginary x))))))) (test "Subtraction is the inverse of addition." @@ -130,9 +127,9 @@ ($_ seq (test "Conjugate has same real part as original, and opposite of imaginary part." (let [cx (&;conjugate x)] - (and (f.= (get@ #&;real x) + (and (f/= (get@ #&;real x) (get@ #&;real cx)) - (f.= (f/negate (get@ #&;imaginary x)) + (f/= (frac/negate (get@ #&;imaginary x)) (get@ #&;imaginary cx))))) (test "The reciprocal functions is its own inverse." @@ -143,9 +140,9 @@ (test "Absolute value of signum is always root2(2), 1 or 0." (let [signum-abs (|> x &;c.signum &;c.abs (get@ #&;real))] - (or (f.= 0.0 signum-abs) - (f.= 1.0 signum-abs) - (f.= (math;root2 2.0) signum-abs)))) + (or (f/= 0.0 signum-abs) + (f/= 1.0 signum-abs) + (f/= (math;root2 2.0) signum-abs)))) (test "Negation is its own inverse." (let [there (&;c.negate x) @@ -154,7 +151,7 @@ (&;c.= back-again x)))) (test "Negation doesn't change the absolute value." - (f.= (get@ #&;real (&;c.abs x)) + (f/= (get@ #&;real (&;c.abs x)) (get@ #&;real (&;c.abs (&;c.negate x))))) )))) @@ -188,9 +185,9 @@ (<| (times +100) (do @ [sample gen-complex - degree (|> r;nat (:: @ map (|>. (n.max +1) (n.% +5))))] + degree (|> r;nat (:: @ map (|>. (n/max +1) (n/% +5))))] (test "Can calculate the N roots for any complex number." (|> sample (&;nth-roots degree) - (List/map (&;pow' (|> degree nat-to-int int-to-frac))) + (list/map (&;pow' (|> degree nat-to-int int-to-frac))) (list;every? (within? margin-of-error sample))))))) diff --git a/stdlib/test/test/lux/data/number/ratio.lux b/stdlib/test/test/lux/data/number/ratio.lux index 3e65ddd13..0cd1f58ea 100644 --- a/stdlib/test/test/lux/data/number/ratio.lux +++ b/stdlib/test/test/lux/data/number/ratio.lux @@ -14,15 +14,15 @@ (def: gen-part (r;Random Nat) - (|> r;nat (:: r;Monad map (|>. (n.% +1000) (n.max +1))))) + (|> r;nat (:: r;Monad map (|>. (n/% +1000) (n/max +1))))) (def: gen-ratio (r;Random &;Ratio) (do r;Monad [numerator gen-part denominator (|> gen-part - (r;filter (|>. (n.= +0) not)) - (r;filter (. not (n.= numerator))))] + (r;filter (|>. (n/= +0) not)) + (r;filter (. not (n/= numerator))))] (wrap (&;ratio numerator denominator)))) (context: "Normalization" @@ -66,7 +66,7 @@ (let [remainder (&;q.% min max) multiple (&;q.- remainder max) factor (&;q./ min multiple)] - (and (|> factor (get@ #&;denominator) (n.= +1)) + (and (|> factor (get@ #&;denominator) (n/= +1)) (|> factor (&;q.* min) (&;q.+ remainder) (&;q.= max))))) )))) diff --git a/stdlib/test/test/lux/data/product.lux b/stdlib/test/test/lux/data/product.lux index de424fe9a..11f394af6 100644 --- a/stdlib/test/test/lux/data/product.lux +++ b/stdlib/test/test/lux/data/product.lux @@ -10,11 +10,11 @@ (context: "Products" ($_ seq (test "Can access the sides of a pair." - (and (i.= 1 (left [1 2])) - (i.= 2 (right [1 2])))) + (and (i/= 1 (left [1 2])) + (i/= 2 (right [1 2])))) (test "Can swap the sides of a pair." (let [[_left _right] (swap [1 2])] - (and (i.= 2 _left) - (i.= 1 _right)))) + (and (i/= 2 _left) + (i/= 1 _right)))) )) diff --git a/stdlib/test/test/lux/data/sum.lux b/stdlib/test/test/lux/data/sum.lux index 90c679ad1..b5e4db76e 100644 --- a/stdlib/test/test/lux/data/sum.lux +++ b/stdlib/test/test/lux/data/sum.lux @@ -28,10 +28,10 @@ (list (+0 "0") (+1 "1") (+0 "2")))))))) (test "Can apply a function to an Either value depending on the case." - (and (i.= 10 (either (function [_] 10) + (and (i/= 10 (either (function [_] 10) (function [_] 20) (: (| Text Text) (+0 "")))) - (i.= 20 (either (function [_] 10) + (i/= 20 (either (function [_] 10) (function [_] 20) (: (| Text Text) (+1 "")))))) ))) diff --git a/stdlib/test/test/lux/data/text.lux b/stdlib/test/test/lux/data/text.lux index 10f51708e..a0747866e 100644 --- a/stdlib/test/test/lux/data/text.lux +++ b/stdlib/test/test/lux/data/text.lux @@ -13,22 +13,22 @@ (context: "Size" (<| (times +100) (do @ - [size (:: @ map (n.% +100) r;nat) + [size (:: @ map (n/% +100) r;nat) sample (r;text size)] - (test "" (or (and (n.= +0 size) + (test "" (or (and (n/= +0 size) (&;empty? sample)) - (n.= size (&;size sample))))))) + (n/= size (&;size sample))))))) (def: bounded-size (r;Random Nat) (|> r;nat - (:: r;Monad map (|>. (n.% +20) (n.+ +1))))) + (:: r;Monad map (|>. (n/% +20) (n/+ +1))))) (context: "Locations" (<| (times +100) (do @ [size bounded-size - idx (:: @ map (n.% size) r;nat) + idx (:: @ map (n/% size) r;nat) sample (r;text size)] (test "" (|> sample (&;nth idx) @@ -40,11 +40,11 @@ (&;last-index-of' char idx sample)] [(#;Some io) (#;Some lio) (#;Some io') (#;Some lio')]]) - (and (n.<= idx io) - (n.>= idx lio) + (and (n/<= idx io) + (n/>= idx lio) - (n.= idx io') - (n.>= idx lio') + (n/= idx io') + (n/>= idx lio') (&;contains? char sample)) @@ -104,7 +104,7 @@ #let [## The wider unicode charset includes control characters that ## can make text replacement work improperly. ## Because of that, I restrict the charset. - normal-char-gen (|> r;nat (:: @ map (|>. (n.% +128) (n.max +1))))] + normal-char-gen (|> r;nat (:: @ map (|>. (n/% +128) (n/max +1))))] sep1 (r;text' normal-char-gen +1) sep2 (r;text' normal-char-gen +1) #let [part-gen (|> (r;text' normal-char-gen sizeP) @@ -115,7 +115,7 @@ (^open "&/") &;Eq]] ($_ seq (test "Can split text through a separator." - (n.= (list;size parts) + (n/= (list;size parts) (list;size (&;split-all-with sep1 sample1)))) (test "Can replace occurrences of a piece of text inside a larger text." diff --git a/stdlib/test/test/lux/data/text/lexer.lux b/stdlib/test/test/lux/data/text/lexer.lux index 81422af4b..bdac87f89 100644 --- a/stdlib/test/test/lux/data/text/lexer.lux +++ b/stdlib/test/test/lux/data/text/lexer.lux @@ -72,7 +72,7 @@ (context: "Literals" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) sample (r;text size) non-sample (|> (r;text size) (r;filter (|>. (text/= sample) not)))] diff --git a/stdlib/test/test/lux/host.jvm.lux b/stdlib/test/test/lux/host.jvm.lux index 070457799..97f13f2df 100644 --- a/stdlib/test/test/lux/host.jvm.lux +++ b/stdlib/test/test/lux/host.jvm.lux @@ -67,9 +67,9 @@ (with-expansions [ (do-template [ ] [(test - (or (|> sample (i.= sample)) + (or (|> sample (i/= sample)) (let [capped-sample (|> sample )] - (|> capped-sample (i.= capped-sample)))))] + (|> capped-sample (i/= capped-sample)))))] [&;l2b &;b2l "Can succesfully convert to/from byte."] [&;l2s &;s2l "Can succesfully convert to/from short."] @@ -112,14 +112,14 @@ (context: "Arrays" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1)))) - idx (|> r;nat (:: @ map (n.% size))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +1)))) + idx (|> r;nat (:: @ map (n/% size))) value r;int] ($_ seq (test "Can create arrays of some length." - (n.= size (&;array-length (&;array Long size)))) + (n/= size (&;array-length (&;array Long size)))) (test "Can set and get array values." (let [arr (&;array Long size)] (exec (&;array-write idx value arr) - (i.= value (&;array-read idx arr))))))))) + (i/= value (&;array-read idx arr))))))))) diff --git a/stdlib/test/test/lux/io.lux b/stdlib/test/test/lux/io.lux index 7a76a2ac9..30eda396f 100644 --- a/stdlib/test/test/lux/io.lux +++ b/stdlib/test/test/lux/io.lux @@ -10,12 +10,12 @@ (context: "I/O" ($_ seq (test "" (Text/= "YOLO" (&;run (&;io "YOLO")))) - (test "" (i.= 11 (&;run (:: &;Functor map i.inc (&;io 10))))) - (test "" (i.= 10 (&;run (:: &;Applicative wrap 10)))) - (test "" (i.= 30 (&;run (let [(^open "&/") &;Applicative] - (&/apply (&/wrap (i.+ 10)) (&/wrap 20)))))) - (test "" (i.= 30 (&;run (do &;Monad - [f (wrap i.+) + (test "" (i/= 11 (&;run (:: &;Functor map i/inc (&;io 10))))) + (test "" (i/= 10 (&;run (:: &;Applicative wrap 10)))) + (test "" (i/= 30 (&;run (let [(^open "&/") &;Applicative] + (&/apply (&/wrap (i/+ 10)) (&/wrap 20)))))) + (test "" (i/= 30 (&;run (do &;Monad + [f (wrap i/+) x (wrap 10) y (wrap 20)] (wrap (f x y)))))))) diff --git a/stdlib/test/test/lux/lang/syntax.lux b/stdlib/test/test/lux/lang/syntax.lux index 4a7c16807..e93ef3f83 100644 --- a/stdlib/test/test/lux/lang/syntax.lux +++ b/stdlib/test/test/lux/lang/syntax.lux @@ -31,7 +31,7 @@ (r;filter (function [sample] (not (text;contains? (text;from-code sample) invalid-range)))))] - size (|> r;nat (:: @ map (|>. (n.% +20) (n.max +1))))] + size (|> r;nat (:: @ map (|>. (n/% +20) (n/max +1))))] (r;text' char-gen size))) (def: ident^ @@ -50,7 +50,7 @@ textual^ (: (r;Random Code) ($_ r;either (do r;Monad - [size (|> r;nat (r/map (n.% +20)))] + [size (|> r;nat (r/map (n/% +20)))] (|> (r;text size) (r/map (|>. #;Text [default-cursor])))) (|> ident^ (r/map (|>. #;Symbol [default-cursor]))) (|> ident^ (r/map (|>. #;Tag [default-cursor]))))) @@ -61,14 +61,14 @@ (r;rec (function [code^] (let [multi^ (do r;Monad - [size (|> r;nat (r/map (n.% +3)))] + [size (|> r;nat (r/map (n/% +3)))] (r;list size code^)) composite^ (: (r;Random Code) ($_ r;either (|> multi^ (r/map (|>. #;Form [default-cursor]))) (|> multi^ (r/map (|>. #;Tuple [default-cursor]))) (do r;Monad - [size (|> r;nat (r/map (n.% +3)))] + [size (|> r;nat (r/map (n/% +3)))] (|> (r;list size (r;seq code^ code^)) (r/map (|>. #;Record [default-cursor]))))))] (r;either simple^ @@ -113,10 +113,10 @@ (context: "Frac special syntax." (<| (times +100) (do @ - [numerator (|> r;nat (:: @ map (|>. (n.% +100) nat-to-frac))) - denominator (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1) nat-to-frac))) + [numerator (|> r;nat (:: @ map (|>. (n/% +100) nat-to-frac))) + denominator (|> r;nat (:: @ map (|>. (n/% +100) (n/max +1) nat-to-frac))) signed? r;bool - #let [expected (|> numerator (f./ denominator) (f.* (if signed? -1.0 1.0)))]] + #let [expected (|> numerator (f// denominator) (f/* (if signed? -1.0 1.0)))]] (test "Can parse frac ratio syntax." (case (&;read "" (dict;new text;Hash) [default-cursor +0 @@ -125,7 +125,7 @@ "/" (%i (frac-to-int denominator)))]) (#e;Success [_ [_ (#;Frac actual)]]) - (f.= expected actual) + (f/= expected actual) _ false) @@ -134,13 +134,13 @@ (context: "Nat special syntax." (<| (times +100) (do @ - [expected (|> r;nat (:: @ map (n.% +1_000)))] + [expected (|> r;nat (:: @ map (n/% +1_000)))] (test "Can parse nat char syntax." (case (&;read "" (dict;new text;Hash) [default-cursor +0 (format "#" (%t (text;from-code expected)) "")]) (#e;Success [_ [_ (#;Nat actual)]]) - (n.= expected actual) + (n/= expected actual) _ false) @@ -150,11 +150,11 @@ (r;Random Text) (let [char-gen (|> r;nat (r;filter (function [value] (not (or (text;space? value) - (n.= (char "#") value) - (n.= (char "(") value) - (n.= (char ")") value))))))] + (n/= (char "#") value) + (n/= (char "(") value) + (n/= (char ")") value))))))] (do r;Monad - [size (|> r;nat (r/map (n.% +20)))] + [size (|> r;nat (r/map (n/% +20)))] (r;text' char-gen size)))) (def: comment^ @@ -169,15 +169,16 @@ (wrap (format "#( " comment " )#"))))))) (context: "Multi-line text & comments." - (<| (times +100) + (<| (seed +6749851812188286456) + ## (times +100) (do @ [#let [char-gen (|> r;nat (r;filter (function [value] (not (or (text;space? value) - (n.= (char "\"") value))))))] + (n/= (char "\"") value))))))] x char-gen y char-gen z char-gen - offset-size (|> r;nat (r/map (|>. (n.% +10) (n.max +1)))) + offset-size (|> r;nat (r/map (|>. (n/% +10) (n/max +1)))) #let [offset (text;join-with "" (list;repeat offset-size " "))] sample code^ comment comment^ @@ -203,7 +204,7 @@ (text;from-code y) "\n" (text;from-code z))] (case (&;read "" (dict;new text;Hash) - [(|> default-cursor (update@ #;column (n.+ (n.dec offset-size)))) + [(|> default-cursor (update@ #;column (n/+ (n/dec offset-size)))) +0 (format "\"" good-input "\"")]) (#e;Error error) diff --git a/stdlib/test/test/lux/lang/type.lux b/stdlib/test/test/lux/lang/type.lux index a592df312..81a0a3cd9 100644 --- a/stdlib/test/test/lux/lang/type.lux +++ b/stdlib/test/test/lux/lang/type.lux @@ -16,7 +16,7 @@ (def: gen-name (r;Random Text) (do r;Monad - [size (|> r;nat (:: @ map (n.% +10)))] + [size (|> r;nat (:: @ map (n/% +10)))] (r;text size))) (def: gen-ident @@ -83,7 +83,7 @@ (context: "Type construction [structs]" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (n.% +3))) + [size (|> r;nat (:: @ map (n/% +3))) members (|> gen-type (r;filter (function [type] (case type @@ -114,7 +114,7 @@ (context: "Type construction [parameterized]" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (n.% +3))) + [size (|> r;nat (:: @ map (n/% +3))) members (M;seq @ (list;repeat size gen-type)) extra (|> gen-type (r;filter (function [type] @@ -134,13 +134,13 @@ (test "Can build and tear-down application types." (let [[tfunc tparams] (|> extra (&;application members) &;flatten-application)] - (n.= (list;size members) (list;size tparams)))) + (n/= (list;size members) (list;size tparams)))) )))) (context: "Type construction [higher order]" (<| (times +100) (do @ - [size (|> r;nat (:: @ map (n.% +3))) + [size (|> r;nat (:: @ map (n/% +3))) extra (|> gen-type (r;filter (function [type] (case type @@ -154,7 +154,7 @@ [ (do-template [ ] [(test (format "Can build and tear-down " " types.") (let [[flat-size flat-body] (|> extra ( size) )] - (and (n.= size flat-size) + (and (n/= size flat-size) (&/= extra flat-body))))] ["universally-quantified" &;univ-q &;flatten-univ-q] diff --git a/stdlib/test/test/lux/lang/type/check.lux b/stdlib/test/test/lux/lang/type/check.lux index 32f7e832b..06c5c3d6b 100644 --- a/stdlib/test/test/lux/lang/type/check.lux +++ b/stdlib/test/test/lux/lang/type/check.lux @@ -19,7 +19,7 @@ (def: gen-name (r;Random Text) (do r;Monad - [size (|> r;nat (:: @ map (n.% +10)))] + [size (|> r;nat (:: @ map (n/% +10)))] (r;text size))) (def: gen-ident @@ -206,7 +206,7 @@ (context: "Rings of type variables." (<| (times +100) (do @ - [num-connections (|> r;nat (:: @ map (n.% +100))) + [num-connections (|> r;nat (:: @ map (n/% +100))) boundT (|> gen-type (r;filter (|>. (case> (#;Var _) false _ true)))) pick-pcg (r;seq r;nat r;nat)] ($_ seq @@ -218,10 +218,10 @@ tailR (@;ring tail-id)] (@;assert "" (let [same-rings? (:: set;Eq = headR tailR) - expected-size? (n.= (n.inc num-connections) (set;size headR)) + expected-size? (n/= (n/inc num-connections) (set;size headR)) same-vars? (|> (set;to-list headR) - (list;sort n.<) - (:: (list;Eq number;Eq) = (list;sort n.< (#;Cons head-id ids))))] + (list;sort n/<) + (:: (list;Eq number;Eq) = (list;sort n/< (#;Cons head-id ids))))] (and same-rings? expected-size? same-vars?)))))) @@ -254,7 +254,7 @@ headRR-post (@;ring head-idR)] (@;assert "" (let [same-rings? (:: set;Eq = headRL-post headRR-post) - expected-size? (n.= (n.* +2 (n.inc num-connections)) + expected-size? (n/= (n/* +2 (n/inc num-connections)) (set;size headRL-post)) union? (:: set;Eq = headRL-post (set;union headRL-pre headRR-pre))] (and same-rings? diff --git a/stdlib/test/test/lux/macro/poly/eq.lux b/stdlib/test/test/lux/macro/poly/eq.lux index e1d7604e7..e071ba043 100644 --- a/stdlib/test/test/lux/macro/poly/eq.lux +++ b/stdlib/test/test/lux/macro/poly/eq.lux @@ -5,7 +5,7 @@ [eq #+ Eq]) (data text/format [bool] - [number "i/" Number] + [number "int/" Number] [text] [maybe] (coll [list])) @@ -46,8 +46,8 @@ (def: gen-record (r;Random Record) (do r;Monad - [size (:: @ map (n.% +2) r;nat) - #let [gen-int (|> r;int (:: @ map (|>. i/abs (i.% 1_000_000))))]] + [size (:: @ map (n/% +2) r;nat) + #let [gen-int (|> r;int (:: @ map (|>. int/abs (i/% 1_000_000))))]] ($_ r;seq (:: @ wrap []) r;bool diff --git a/stdlib/test/test/lux/macro/poly/functor.lux b/stdlib/test/test/lux/macro/poly/functor.lux index 45e54bae7..d1c42cde5 100644 --- a/stdlib/test/test/lux/macro/poly/functor.lux +++ b/stdlib/test/test/lux/macro/poly/functor.lux @@ -7,7 +7,7 @@ [state]) (data text/format [bool] - [number "i/" Number] + [number] [text] [identity]) ["r" math/random] diff --git a/stdlib/test/test/lux/math.lux b/stdlib/test/test/lux/math.lux index a2ef96186..c79720956 100644 --- a/stdlib/test/test/lux/math.lux +++ b/stdlib/test/test/lux/math.lux @@ -1,31 +1,24 @@ (;module: lux (lux [io] - (control ["M" monad #+ do Monad]) - (data [text "Text/" Monoid] - text/format - [bool "b/" Eq] - [number "f/" Number] - (coll [list "List/" Fold Functor]) - [product]) + (control [monad #+ do Monad]) + (data [bool "bool/" Eq] + [number "frac/" Number]) ["r" math/random] ["&" math]) lux/test) (def: (within? margin-of-error standard value) (-> Frac Frac Frac Bool) - (f.< margin-of-error - (f/abs (f.- standard value)))) + (f/< margin-of-error + (frac/abs (f/- standard value)))) (def: margin Frac 0.0000001) -## The JVM trigonometry functions sometimes give me funky results. -## I won't be testing this, until I can figure out what's going on, or -## come up with my own implementation (context: "Trigonometry" - (<| (times +100) + (<| (seed +4611737486687492590) (do @ - [angle (|> r;frac (:: @ map (f.* &;tau)))] + [angle (|> r;frac (:: @ map (f/* &;tau)))] ($_ seq (test "Sine and arc-sine are inverse functions." (|> angle &;sin &;asin (within? margin angle))) @@ -40,66 +33,66 @@ (context: "Roots" (<| (times +100) (do @ - [factor (|> r;nat (:: @ map (|>. (n.% +1000) - (n.max +1) + [factor (|> r;nat (:: @ map (|>. (n/% +1000) + (n/max +1) nat-to-int int-to-frac))) - base (|> r;frac (:: @ map (f.* factor)))] + base (|> r;frac (:: @ map (f/* factor)))] ($_ seq (test "Square-root is inverse of square." - (|> base (&;pow 2.0) &;root2 (f.= base))) + (|> base (&;pow 2.0) &;root2 (f/= base))) (test "Cubic-root is inverse of cube." - (|> base (&;pow 3.0) &;root3 (f.= base))) + (|> base (&;pow 3.0) &;root3 (f/= base))) )))) (context: "Rounding" (<| (times +100) (do @ - [sample (|> r;frac (:: @ map (f.* 1000.0)))] + [sample (|> r;frac (:: @ map (f/* 1000.0)))] ($_ seq (test "The ceiling will be an integer value, and will be >= the original." (let [ceil'd (&;ceil sample)] - (and (|> ceil'd frac-to-int int-to-frac (f.= ceil'd)) - (f.>= sample ceil'd) - (f.<= 1.0 (f.- sample ceil'd))))) + (and (|> ceil'd frac-to-int int-to-frac (f/= ceil'd)) + (f/>= sample ceil'd) + (f/<= 1.0 (f/- sample ceil'd))))) (test "The floor will be an integer value, and will be <= the original." (let [floor'd (&;floor sample)] - (and (|> floor'd frac-to-int int-to-frac (f.= floor'd)) - (f.<= sample floor'd) - (f.<= 1.0 (f.- floor'd sample))))) + (and (|> floor'd frac-to-int int-to-frac (f/= floor'd)) + (f/<= sample floor'd) + (f/<= 1.0 (f/- floor'd sample))))) (test "The round will be an integer value, and will be < or > or = the original." (let [round'd (&;round sample)] - (and (|> round'd frac-to-int int-to-frac (f.= round'd)) - (f.<= 1.0 (f/abs (f.- sample round'd)))))) + (and (|> round'd frac-to-int int-to-frac (f/= round'd)) + (f/<= 1.0 (frac/abs (f/- sample round'd)))))) )))) (context: "Exponentials and logarithms" (<| (times +100) (do @ - [sample (|> r;frac (:: @ map (f.* 10.0)))] + [sample (|> r;frac (:: @ map (f/* 10.0)))] (test "Logarithm is the inverse of exponential." (|> sample &;exp &;log (within? 1.0e-15 sample)))))) (context: "Greatest-Common-Divisor and Least-Common-Multiple" (<| (times +100) (do @ - [#let [gen-nat (|> r;nat (:: @ map (|>. (n.% +1000) (n.max +1))))] + [#let [gen-nat (|> r;nat (:: @ map (|>. (n/% +1000) (n/max +1))))] x gen-nat y gen-nat] ($_ (test "GCD" (let [gcd (&;gcd x y)] - (and (n.= +0 (n.% gcd x)) - (n.= +0 (n.% gcd y)) - (n.>= +1 gcd)))) + (and (n/= +0 (n/% gcd x)) + (n/= +0 (n/% gcd y)) + (n/>= +1 gcd)))) (test "LCM" (let [lcm (&;lcm x y)] - (and (n.= +0 (n.% x lcm)) - (n.= +0 (n.% y lcm)) - (n.<= (n.* x y) lcm)))) + (and (n/= +0 (n/% x lcm)) + (n/= +0 (n/% y lcm)) + (n/<= (n/* x y) lcm)))) )))) (context: "Infix syntax" @@ -109,32 +102,32 @@ y r;nat z r;nat theta r;frac - #let [top (|> x (n.max y) (n.max z)) - bottom (|> x (n.min y) (n.min z))]] + #let [top (|> x (n/max y) (n/max z)) + bottom (|> x (n/min y) (n/min z))]] ($_ seq (test "Constant values don't change." - (n.= x + (n/= x (&;infix x))) (test "Can call binary functions." - (n.= (&;gcd y x) + (n/= (&;gcd y x) (&;infix [x &;gcd y]))) (test "Can call unary functions." - (f.= (&;sin theta) + (f/= (&;sin theta) (&;infix [&;sin theta]))) (test "Can use regular syntax in the middle of infix code." - (n.= (&;gcd +450 (n.* +3 +9)) - (&;infix [(n.* +3 +9) &;gcd +450]))) + (n/= (&;gcd +450 (n/* +3 +9)) + (&;infix [(n/* +3 +9) &;gcd +450]))) (test "Can use non-numerical functions/macros as operators." - (b/= (and (n.< y x) (n.< z y)) - (&;infix [[x n.< y] and [y n.< z]]))) + (bool/= (and (n/< y x) (n/< z y)) + (&;infix [[x n/< y] and [y n/< z]]))) (test "Can combine boolean operations in special ways via special keywords." - (and (b/= (and (n.< y x) (n.< z y)) - (&;infix [#and x n.< y n.< z])) - (b/= (and (n.< y x) (n.> z y)) - (&;infix [#and x n.< y n.> z])))) + (and (bool/= (and (n/< y x) (n/< z y)) + (&;infix [#and x n/< y n/< z])) + (bool/= (and (n/< y x) (n/> z y)) + (&;infix [#and x n/< y n/> z])))) )))) diff --git a/stdlib/test/test/lux/math/logic/continuous.lux b/stdlib/test/test/lux/math/logic/continuous.lux index 5df89cfef..0bf2aabcf 100644 --- a/stdlib/test/test/lux/math/logic/continuous.lux +++ b/stdlib/test/test/lux/math/logic/continuous.lux @@ -14,20 +14,20 @@ ($_ seq (test "AND is the minimum." (let [result (&;~and left right)] - (and (d.<= left result) - (d.<= right result)))) + (and (d/<= left result) + (d/<= right result)))) (test "OR is the maximum." (let [result (&;~or left right)] - (and (d.>= left result) - (d.>= right result)))) + (and (d/>= left result) + (d/>= right result)))) (test "Double negation results in the original value." - (d.= left (&;~not (&;~not left)))) + (d/= left (&;~not (&;~not left)))) (test "Every value is equivalent to itself." - (and (d.>= left + (and (d/>= left (&;~= left left)) - (d.>= right + (d/>= right (&;~= right right)))) )))) diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux index 3c7ff926e..7be4d05f0 100644 --- a/stdlib/test/test/lux/math/logic/fuzzy.lux +++ b/stdlib/test/test/lux/math/logic/fuzzy.lux @@ -33,25 +33,25 @@ triangle ( x y z)]] ($_ seq (test "The middle value will always have maximum membership." - (d.= ~true (&;membership middle triangle))) + (d/= ~true (&;membership middle triangle))) (test "Boundary values will always have 0 membership." - (and (d.= ~false (&;membership bottom triangle)) - (d.= ~false (&;membership top triangle)))) + (and (d/= ~false (&;membership bottom triangle)) + (d/= ~false (&;membership top triangle)))) (test "Values within range, will have membership > 0." - (B/= (d.> ~false (&;membership sample triangle)) + (B/= (d/> ~false (&;membership sample triangle)) (and ( bottom sample) ( top sample)))) (test "Values outside of range, will have membership = 0." - (B/= (d.= ~false (&;membership sample triangle)) + (B/= (d/= ~false (&;membership sample triangle)) (or ( bottom sample) ( top sample)))) ))))] - ["Frac" number;Hash r;frac &;f.triangle f.< f.<= f.> f.>=] - ["Deg" number;Hash r;deg &;d.triangle d.< d.<= d.> d.>=] + ["Frac" number;Hash r;frac &;f/triangle f/< f/<= f/> f/>=] + ["Deg" number;Hash r;deg &;d/triangle d/< d/<= d/> d/>=] ) (do-template [ ] @@ -75,41 +75,41 @@ trapezoid ( w x y z)]] ($_ seq (test "The middle values will always have maximum membership." - (and (d.= ~true (&;membership middle-bottom trapezoid)) - (d.= ~true (&;membership middle-top trapezoid)))) + (and (d/= ~true (&;membership middle-bottom trapezoid)) + (d/= ~true (&;membership middle-top trapezoid)))) (test "Boundary values will always have 0 membership." - (and (d.= ~false (&;membership bottom trapezoid)) - (d.= ~false (&;membership top trapezoid)))) + (and (d/= ~false (&;membership bottom trapezoid)) + (d/= ~false (&;membership top trapezoid)))) (test "Values within inner range will have membership = 1" - (B/= (d.= ~true (&;membership sample trapezoid)) + (B/= (d/= ~true (&;membership sample trapezoid)) (and ( middle-bottom sample) ( middle-top sample)))) (test "Values within range, will have membership > 0." - (B/= (d.> ~false (&;membership sample trapezoid)) + (B/= (d/> ~false (&;membership sample trapezoid)) (and ( bottom sample) ( top sample)))) (test "Values outside of range, will have membership = 0." - (B/= (d.= ~false (&;membership sample trapezoid)) + (B/= (d/= ~false (&;membership sample trapezoid)) (or ( bottom sample) ( top sample)))) ))))] - ["Frac" number;Hash r;frac &;f.trapezoid f.< f.<= f.> f.>=] - ["Deg" number;Hash r;deg &;d.trapezoid d.< d.<= d.> d.>=] + ["Frac" number;Hash r;frac &;f/trapezoid f/< f/<= f/> f/>=] + ["Deg" number;Hash r;deg &;d/trapezoid d/< d/<= d/> d/>=] ) (context: "Gaussian" (<| (times +100) (do @ - [deviation (|> r;frac (r;filter (f.> 0.0))) + [deviation (|> r;frac (r;filter (f/> 0.0))) center r;frac #let [gaussian (&;gaussian deviation center)]] (test "The center value will always have maximum membership." - (d.= ~true (&;membership center gaussian)))))) + (d/= ~true (&;membership center gaussian)))))) (def: gen-triangle (r;Random (&;Fuzzy Frac)) @@ -117,7 +117,7 @@ [x r;frac y r;frac z r;frac] - (wrap (&;f.triangle x y z)))) + (wrap (&;f/triangle x y z)))) (context: "Combinators" (<| (times +100) @@ -129,44 +129,44 @@ (test "Union membership as as high as membership in any of its members." (let [combined (&;union left right) combined-membership (&;membership sample combined)] - (and (d.>= (&;membership sample left) + (and (d/>= (&;membership sample left) combined-membership) - (d.>= (&;membership sample right) + (d/>= (&;membership sample right) combined-membership)))) (test "Intersection membership as as low as membership in any of its members." (let [combined (&;intersection left right) combined-membership (&;membership sample combined)] - (and (d.<= (&;membership sample left) + (and (d/<= (&;membership sample left) combined-membership) - (d.<= (&;membership sample right) + (d/<= (&;membership sample right) combined-membership)))) (test "Complement membership is the opposite of normal membership." - (d.= (&;membership sample left) + (d/= (&;membership sample left) (~not (&;membership sample (&;complement left))))) (test "Membership in the difference will never be higher than in the set being subtracted." - (B/= (d.> (&;membership sample right) + (B/= (d/> (&;membership sample right) (&;membership sample left)) - (d.< (&;membership sample left) + (d/< (&;membership sample left) (&;membership sample (&;difference left right))))) )))) (context: "From predicates and sets" (<| (times +100) (do @ - [#let [set-10 (set;from-list number;Hash (list;n.range +0 +10))] - sample (|> r;nat (:: @ map (n.% +20)))] + [#let [set-10 (set;from-list number;Hash (list;n/range +0 +10))] + sample (|> r;nat (:: @ map (n/% +20)))] ($_ seq (test "Values that satisfy a predicate have membership = 1. Values that don't have membership = 0." - (B/= (d.= ~true (&;membership sample (&;from-predicate n.even?))) - (n.even? sample))) + (B/= (d/= ~true (&;membership sample (&;from-predicate n/even?))) + (n/even? sample))) (test "Values that belong to a set have membership = 1. Values that don't have membership = 0." - (B/= (d.= ~true (&;membership sample (&;from-set set-10))) + (B/= (d/= ~true (&;membership sample (&;from-set set-10))) (set;member? set-10 sample))) )))) @@ -180,10 +180,10 @@ member? (&;to-predicate threshold fuzzy)]] ($_ seq (test "Can increase the threshold of membership of a fuzzy set." - (B/= (d.> ~false (&;membership sample vip-fuzzy)) - (d.> threshold (&;membership sample fuzzy)))) + (B/= (d/> ~false (&;membership sample vip-fuzzy)) + (d/> threshold (&;membership sample fuzzy)))) (test "Can turn fuzzy sets into predicates through a threshold." (B/= (member? sample) - (d.> threshold (&;membership sample fuzzy)))) + (d/> threshold (&;membership sample fuzzy)))) )))) diff --git a/stdlib/test/test/lux/math/random.lux b/stdlib/test/test/lux/math/random.lux index 5efacca05..9aefcc8f7 100644 --- a/stdlib/test/test/lux/math/random.lux +++ b/stdlib/test/test/lux/math/random.lux @@ -17,7 +17,7 @@ (context: "Random." (<| (times +100) (do @ - [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + [size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) _list (r;list size r;nat) _sequence (r;sequence size r;nat) _array (r;array size r;nat) @@ -26,28 +26,28 @@ _set (r;set number;Hash size r;nat) _dict (r;dict number;Hash size r;nat r;nat) top r;nat - filtered (|> r;nat (r;filter (n.<= top))) + filtered (|> r;nat (r;filter (n/<= top))) shuffle-seed r;nat - #let [sorted (|> _sequence sequence;to-list (list;sort n.<)) + #let [sorted (|> _sequence sequence;to-list (list;sort n/<)) shuffled (|> sorted sequence;from-list (r;shuffle shuffle-seed)) - re-sorted (|> shuffled sequence;to-list (list;sort n.<))]] + re-sorted (|> shuffled sequence;to-list (list;sort n/<))]] ($_ seq (test "Can produce lists." - (n.= size (list;size _list))) + (n/= size (list;size _list))) (test "Can produce sequences." - (n.= size (sequence;size _sequence))) + (n/= size (sequence;size _sequence))) (test "Can produce arrays." - (n.= size (array;size _array))) + (n/= size (array;size _array))) (test "Can produce queues." - (n.= size (queue;size _queue))) + (n/= size (queue;size _queue))) (test "Can produce stacks." - (n.= size (stack;size _stack))) + (n/= size (stack;size _stack))) (test "Can produce sets." - (n.= size (set;size _set))) + (n/= size (set;size _set))) (test "Can produce dicts." - (n.= size (dict;size _dict))) + (n/= size (dict;size _dict))) (test "Can filter values." - (n.<= top filtered)) + (n/<= top filtered)) (test "Can shuffle sequences." (let [(^open "v/") (sequence;Eq number;Eq) sorted (sequence;from-list sorted)] diff --git a/stdlib/test/test/lux/time/duration.lux b/stdlib/test/test/lux/time/duration.lux index ef891fcf6..b56e828bf 100644 --- a/stdlib/test/test/lux/time/duration.lux +++ b/stdlib/test/test/lux/time/duration.lux @@ -16,7 +16,7 @@ (do @ [millis r;int] (test "Can convert from/to milliseconds." - (|> millis @;from-millis @;to-millis (i.= millis)))))) + (|> millis @;from-millis @;to-millis (i/= millis)))))) (context: "Equality" (<| (times +100) @@ -43,11 +43,11 @@ (do @ [sample (|> duration (:: @ map (@;frame @;day))) frame duration - factor (|> r;int (:: @ map (|>. (i.% 10) (i.max 1)))) + factor (|> r;int (:: @ map (|>. (i/% 10) (i/max 1)))) #let [(^open "@/") @;Order]] ($_ seq (test "Can scale a duration." - (|> sample (@;scale factor) (@;query sample) (i.= factor))) + (|> sample (@;scale factor) (@;query sample) (i/= factor))) (test "Scaling a duration by one does not change it." (|> sample (@;scale 1) (@/= sample))) (test "Merging with the empty duration changes nothing." diff --git a/stdlib/test/test/lux/time/instant.lux b/stdlib/test/test/lux/time/instant.lux index 95a2ce441..db99c8628 100644 --- a/stdlib/test/test/lux/time/instant.lux +++ b/stdlib/test/test/lux/time/instant.lux @@ -18,14 +18,14 @@ (def: #export instant (r;Random @;Instant) - (|> r;int (:: r;Monad map (|>. (i.% boundary) @;from-millis)))) + (|> r;int (:: r;Monad map (|>. (i/% boundary) @;from-millis)))) (context: "Conversion." (<| (times +100) (do @ [millis r;int] (test "Can convert from/to milliseconds." - (|> millis @;from-millis @;to-millis (i.= millis)))))) + (|> millis @;from-millis @;to-millis (i/= millis)))))) (context: "Equality" (<| (times +100) @@ -78,7 +78,8 @@ (|> @;epoch (@;shift (@;relative sample)) (@/= sample))))))) (context: "Codec" - (<| (times +100) + (<| (seed +9863552679229274604) + ## (times +100) (do @ [sample instant #let [(^open "@/") @;Eq diff --git a/stdlib/test/test/lux/type/implicit.lux b/stdlib/test/test/lux/type/implicit.lux index 138a16b2e..662c2df80 100644 --- a/stdlib/test/test/lux/type/implicit.lux +++ b/stdlib/test/test/lux/type/implicit.lux @@ -22,17 +22,17 @@ (let [(^open "list/") (list;Eq number;Eq)] (and (bool/= (:: number;Eq = x y) (::: = x y)) - (list/= (list;n.range +1 +10) - (::: map n.inc (list;n.range +0 +9))) + (list/= (list;n/range +1 +10) + (::: map n/inc (list;n/range +0 +9))) ))) (test "Can automatically select second-order structures." (::: = - (list;n.range +1 +10) - (list;n.range +1 +10))) + (list;n/range +1 +10) + (list;n/range +1 +10))) (test "Can automatically select third-order structures." - (let [lln (::: map (list;n.range +1) - (list;n.range +1 +10))] + (let [lln (::: map (list;n/range +1) + (list;n/range +1 +10))] (::: = lln lln))) )))) diff --git a/stdlib/test/test/lux/type/object.lux b/stdlib/test/test/lux/type/object.lux index c85ff5770..96c71a75c 100644 --- a/stdlib/test/test/lux/type/object.lux +++ b/stdlib/test/test/lux/type/object.lux @@ -12,7 +12,7 @@ Nat (def: inc - (update@Counter n.inc)) + (update@Counter n/inc)) (def: read get@Counter)) @@ -63,7 +63,7 @@ (def: (poly1 counter) (-> Resettable-Counter Nat) - (n.+ (read counter) + (n/+ (read counter) (read (reset counter)))) (def: poly1-0 Nat (poly1 (new@NatRC +0 []))) @@ -77,7 +77,7 @@ (def: (poly3 counter) (-> NatRC Nat) - (n.+ (read counter) + (n/+ (read counter) (read (reset counter)))) (def: poly3-0 Nat (poly3 (new@NatRC +0 []))) diff --git a/stdlib/test/test/lux/world/blob.lux b/stdlib/test/test/lux/world/blob.lux index d523f5823..3986a6a23 100644 --- a/stdlib/test/test/lux/world/blob.lux +++ b/stdlib/test/test/lux/world/blob.lux @@ -25,35 +25,35 @@ (do r;Monad [] (loop [idx +0] - (if (n.< size idx) + (if (n/< size idx) (do @ [byte r;nat] (exec (E;assume (@;write-8 idx byte blob)) - (recur (n.inc idx)))) + (recur (n/inc idx)))) (wrap blob)))))) (context: "Blob." (<| (times +100) (do @ - [blob-size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +8)))) + [blob-size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +8)))) random-blob (blob blob-size) #let [clean-blob (@;create blob-size) size (@;size clean-blob)] value r;nat - idx (|> r;nat (:: @ map (n.% size))) - [from to] (|> (r;list +2 (|> r;nat (:: @ map (n.% size)))) + idx (|> r;nat (:: @ map (n/% size))) + [from to] (|> (r;list +2 (|> r;nat (:: @ map (n/% size)))) (:: @ map - (|>. (list;sort n.<) + (|>. (list;sort n/<) (pipe;case> (^ (list from to)) [from to] _ (undefined))))) - #let [value-8 (n.% (bit;shift-left +8 +1) value) - value-16 (n.% (bit;shift-left +16 +1) value) - value-32 (n.% (bit;shift-left +32 +1) value) + #let [value-8 (n/% (bit;shift-left +8 +1) value) + value-16 (n/% (bit;shift-left +16 +1) value) + value-32 (n/% (bit;shift-left +32 +1) value) value-64 value - slice-size (|> to (n.- from) n.inc) + slice-size (|> to (n/- from) n/inc) random-slice (E;assume (@;slice from to random-blob))]] ($_ seq (test "Has equality." @@ -62,48 +62,48 @@ (E;assume (@;slice from to clean-blob)) (E;assume (@;slice from to clean-blob))))) (test "Can get size of blob." - (n.= blob-size size)) + (n/= blob-size size)) (test "Can read/write 8-bit values." (succeed (do E;Monad [_ (@;write-8 idx value-8 clean-blob) output-8 (@;read-8 idx clean-blob)] - (wrap (n.= value-8 output-8))))) + (wrap (n/= value-8 output-8))))) (test "Can read/write 16-bit values." - (or (n.>= size (n.+ +1 idx)) + (or (n/>= size (n/+ +1 idx)) (succeed (do E;Monad [_ (@;write-16 idx value-16 clean-blob) output-16 (@;read-16 idx clean-blob)] - (wrap (n.= value-16 output-16)))))) + (wrap (n/= value-16 output-16)))))) (test "Can read/write 32-bit values." - (or (n.>= size (n.+ +3 idx)) + (or (n/>= size (n/+ +3 idx)) (succeed (do E;Monad [_ (@;write-32 idx value-32 clean-blob) output-32 (@;read-32 idx clean-blob)] - (wrap (n.= value-32 output-32)))))) + (wrap (n/= value-32 output-32)))))) (test "Can read/write 64-bit values." - (or (n.>= size (n.+ +7 idx)) + (or (n/>= size (n/+ +7 idx)) (succeed (do E;Monad [_ (@;write-64 idx value-64 clean-blob) output-64 (@;read-64 idx clean-blob)] - (wrap (n.= value-64 output-64)))))) + (wrap (n/= value-64 output-64)))))) (test "Can slice blobs." - (and (n.= slice-size (@;size random-slice)) + (and (n/= slice-size (@;size random-slice)) (loop [idx +0] (let [loop-recur recur] - (if (n.< slice-size idx) + (if (n/< slice-size idx) (and (succeed (do E;Monad - [reference (@;read-8 (n.+ from idx) random-blob) + [reference (@;read-8 (n/+ from idx) random-blob) sample (@;read-8 idx random-slice)] - (wrap (n.= reference sample)))) - (loop-recur (n.inc idx))) + (wrap (n/= reference sample)))) + (loop-recur (n/inc idx))) true))))) (test "Slicing the whole blob does not change anything." (:: @;Eq = random-blob - (E;assume (@;slice +0 (n.dec blob-size) random-blob)))) + (E;assume (@;slice +0 (n/dec blob-size) random-blob)))) )))) diff --git a/stdlib/test/test/lux/world/file.lux b/stdlib/test/test/lux/world/file.lux index 4af26b095..5c68c1097 100644 --- a/stdlib/test/test/lux/world/file.lux +++ b/stdlib/test/test/lux/world/file.lux @@ -17,11 +17,11 @@ (// ["_;" blob])) (def: truncate-millis - (|>. (i./ 1_000) (i.* 1_000))) + (|>. (i// 1_000) (i/* 1_000))) (context: "File system." (do @ - [file-size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + [file-size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) dataL (_blob;blob file-size) dataR (_blob;blob file-size) code r;nat @@ -31,7 +31,7 @@ i;absolute)))] ($_ seq (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +0 code)))] + [#let [file (format "temp_file_" (%n (n/+ +0 code)))] result (do T;Monad [pre (@;exists? file) _ (@;write dataL file) @@ -43,7 +43,7 @@ (assert "Can create/delete files." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +1 code)))] + [#let [file (format "temp_file_" (%n (n/+ +1 code)))] result (do T;Monad [_ (@;write dataL file) output (@;read file) @@ -52,29 +52,29 @@ (assert "Can write/read files." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +2 code)))] + [#let [file (format "temp_file_" (%n (n/+ +2 code)))] result (do T;Monad [_ (@;write dataL file) read-size (@;size file) _ (@;delete file)] - (wrap (n.= file-size read-size)))] + (wrap (n/= file-size read-size)))] (assert "Can read file size." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +3 code)))] + [#let [file (format "temp_file_" (%n (n/+ +3 code)))] result (do T;Monad [_ (@;write dataL file) _ (@;append dataR file) output (@;read file) read-size (@;size file) _ (@;delete file)] - (wrap (and (n.= (n.* +2 file-size) read-size) - (:: blob;Eq = dataL (E;assume (blob;slice +0 (n.dec file-size) output))) - (:: blob;Eq = dataR (E;assume (blob;slice file-size (n.dec read-size) output))))))] + (wrap (and (n/= (n/* +2 file-size) read-size) + (:: blob;Eq = dataL (E;assume (blob;slice +0 (n/dec file-size) output))) + (:: blob;Eq = dataR (E;assume (blob;slice file-size (n/dec read-size) output))))))] (assert "Can append to files." (E;default false result)))) (wrap (do P;Monad - [#let [dir (format "temp_dir_" (%n (n.+ +4 code)))] + [#let [dir (format "temp_dir_" (%n (n/+ +4 code)))] result (do T;Monad [pre (@;exists? dir) _ (@;make-dir dir) @@ -86,8 +86,8 @@ (assert "Can create/delete directories." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +5 code))) - dir (format "temp_dir_" (%n (n.+ +5 code)))] + [#let [file (format "temp_file_" (%n (n/+ +5 code))) + dir (format "temp_dir_" (%n (n/+ +5 code)))] result (do T;Monad [_ (@;write dataL file) file-is-file (@;file? file) @@ -102,8 +102,8 @@ (assert "Can differentiate files from directories." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +6 code))) - dir (format "temp_dir_" (%n (n.+ +6 code)))] + [#let [file (format "temp_file_" (%n (n/+ +6 code))) + dir (format "temp_dir_" (%n (n/+ +6 code)))] result (do T;Monad [_ (@;make-dir dir) #let [file' (format dir "/" file)] @@ -111,14 +111,14 @@ read-size (@;size file') deleted-file (@;delete file') deleted-dir (@;delete dir)] - (wrap (and (n.= file-size read-size) + (wrap (and (n/= file-size read-size) deleted-file deleted-dir)))] (assert "Can create files inside of directories." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +7 code))) - dir (format "temp_dir_" (%n (n.+ +7 code)))] + [#let [file (format "temp_file_" (%n (n/+ +7 code))) + dir (format "temp_dir_" (%n (n/+ +7 code)))] result (do T;Monad [_ (@;make-dir dir) #let [file' (format dir "/" file)] @@ -135,7 +135,7 @@ (assert "Can list files inside a directory." (E;default false result)))) (wrap (do P;Monad - [#let [file (format "temp_file_" (%n (n.+ +8 code)))] + [#let [file (format "temp_file_" (%n (n/+ +8 code)))] result (do T;Monad [_ (@;write dataL file) was-modified? (@;set-last-modified last-modified file) @@ -146,8 +146,8 @@ (assert "Can change the time of last modification." (E;default false result)))) (wrap (do P;Monad - [#let [file0 (format "temp_file_" (%n (n.+ +9 code)) "0") - file1 (format "temp_file_" (%n (n.+ +9 code)) "1")] + [#let [file0 (format "temp_file_" (%n (n/+ +9 code)) "0") + file1 (format "temp_file_" (%n (n/+ +9 code)) "1")] result (do T;Monad [_ (@;write dataL file0) pre (@;exists? file0) diff --git a/stdlib/test/test/lux/world/net/tcp.lux b/stdlib/test/test/lux/world/net/tcp.lux index d07f5e200..c18d3929b 100644 --- a/stdlib/test/test/lux/world/net/tcp.lux +++ b/stdlib/test/test/lux/world/net/tcp.lux @@ -21,8 +21,8 @@ (r;Random net;Port) (|> r;nat (:: r;Monad map - (|>. (n.% +1000) - (n.+ +8000))))) + (|>. (n/% +1000) + (n/+ +8000))))) (exception: Empty-Channel) @@ -40,7 +40,7 @@ (context: "TCP networking." (do @ [port ;;port - size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) from (_blob;blob size) to (_blob;blob size) #let [temp (blob;create size)]] @@ -53,12 +53,12 @@ _ (@;write from +0 size client) socket (head server) bytes-from (@;read temp +0 size socket) - #let [from-worked? (and (n.= size bytes-from) + #let [from-worked? (and (n/= size bytes-from) (:: blob;Eq = from temp))] #################### _ (@;write to +0 size socket) bytes-to (@;read temp +0 size client) - #let [to-worked? (and (n.= size bytes-to) + #let [to-worked? (and (n/= size bytes-to) (:: blob;Eq = to temp))] #################### _ (@;close client) diff --git a/stdlib/test/test/lux/world/net/udp.lux b/stdlib/test/test/lux/world/net/udp.lux index 988db0471..a4707744e 100644 --- a/stdlib/test/test/lux/world/net/udp.lux +++ b/stdlib/test/test/lux/world/net/udp.lux @@ -21,8 +21,8 @@ (r;Random net;Port) (|> r;nat (:: r;Monad map - (|>. (n.% +1000) - (n.+ +8000))))) + (|>. (n/% +1000) + (n/+ +8000))))) (exception: Empty-Channel) @@ -40,7 +40,7 @@ (context: "UDP networking." (do @ [port ;;port - size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10)))) + size (|> r;nat (:: @ map (|>. (n/% +100) (n/max +10)))) from (_blob;blob size) to (_blob;blob size) #let [temp (blob;create size)]] @@ -52,14 +52,14 @@ #################### _ (@;write localhost port from +0 size client) [bytes-from from-address from-port] (@;read temp +0 size server) - #let [from-worked? (and (n.= size bytes-from) + #let [from-worked? (and (n/= size bytes-from) (:: blob;Eq = from temp))] #################### _ (@;write from-address from-port to +0 size server) [bytes-to to-address to-port] (@;read temp +0 size client) - #let [to-worked? (and (n.= size bytes-to) + #let [to-worked? (and (n/= size bytes-to) (:: blob;Eq = to temp) - (n.= port to-port))] + (n/= port to-port))] #################### _ (@;close client) _ (@;close server)] -- cgit v1.2.3