From a0889b2ee76c1ae7a9a5bbe2eec9f051b4f341e4 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 26 Jul 2019 21:23:27 -0400 Subject: No more "n/"-prefixed functions. --- stdlib/source/test/licentia.lux | 12 +-- stdlib/source/test/lux.lux | 53 ++++++------ stdlib/source/test/lux/abstract/apply.lux | 18 ++-- stdlib/source/test/lux/abstract/fold.lux | 9 +- stdlib/source/test/lux/abstract/functor.lux | 17 ++-- stdlib/source/test/lux/abstract/interval.lux | 68 +++++++-------- stdlib/source/test/lux/abstract/monad.lux | 14 ++-- .../source/test/lux/control/concurrency/actor.lux | 10 ++- .../source/test/lux/control/concurrency/atom.lux | 13 +-- stdlib/source/test/lux/control/concurrency/frp.lux | 8 +- .../test/lux/control/concurrency/semaphore.lux | 12 +-- stdlib/source/test/lux/control/concurrency/stm.lux | 18 ++-- stdlib/source/test/lux/control/continuation.lux | 18 ++-- stdlib/source/test/lux/control/exception.lux | 10 ++- stdlib/source/test/lux/control/io.lux | 7 +- stdlib/source/test/lux/control/parser.lux | 42 +++++----- stdlib/source/test/lux/control/parser/cli.lux | 10 +-- stdlib/source/test/lux/control/parser/text.lux | 4 +- stdlib/source/test/lux/control/pipe.lux | 56 +++++++------ stdlib/source/test/lux/control/reader.lux | 12 +-- stdlib/source/test/lux/control/region.lux | 14 ++-- stdlib/source/test/lux/control/security/policy.lux | 6 +- stdlib/source/test/lux/control/state.lux | 30 +++---- stdlib/source/test/lux/control/thread.lux | 6 +- stdlib/source/test/lux/control/try.lux | 10 +-- stdlib/source/test/lux/control/writer.lux | 6 +- stdlib/source/test/lux/data/binary.lux | 24 +++--- stdlib/source/test/lux/data/collection/array.lux | 44 +++++----- stdlib/source/test/lux/data/collection/bits.lux | 23 ++--- .../source/test/lux/data/collection/dictionary.lux | 56 ++++++------- .../lux/data/collection/dictionary/ordered.lux | 30 +++---- stdlib/source/test/lux/data/collection/list.lux | 98 +++++++++++----------- stdlib/source/test/lux/data/collection/queue.lux | 28 +++---- .../test/lux/data/collection/queue/priority.lux | 24 +++--- stdlib/source/test/lux/data/collection/row.lux | 30 +++---- .../source/test/lux/data/collection/sequence.lux | 62 +++++++------- stdlib/source/test/lux/data/collection/set.lux | 22 ++--- .../test/lux/data/collection/set/ordered.lux | 32 +++---- stdlib/source/test/lux/data/collection/stack.lux | 12 +-- stdlib/source/test/lux/data/collection/tree.lux | 12 +-- .../test/lux/data/collection/tree/zipper.lux | 14 ++-- stdlib/source/test/lux/data/format/json.lux | 3 +- stdlib/source/test/lux/data/format/xml.lux | 8 +- stdlib/source/test/lux/data/lazy.lux | 10 +-- stdlib/source/test/lux/data/maybe.lux | 10 +-- stdlib/source/test/lux/data/name.lux | 10 ++- stdlib/source/test/lux/data/number/complex.lux | 5 +- stdlib/source/test/lux/data/number/i64.lux | 54 ++++++------ stdlib/source/test/lux/data/number/nat.lux | 6 +- stdlib/source/test/lux/data/number/ratio.lux | 7 +- stdlib/source/test/lux/data/sum.lux | 6 +- stdlib/source/test/lux/data/text.lux | 24 +++--- stdlib/source/test/lux/host.jvm.lux | 7 +- stdlib/source/test/lux/host.old.lux | 7 +- stdlib/source/test/lux/macro/poly/equivalence.lux | 3 +- stdlib/source/test/lux/macro/poly/json.lux | 3 +- stdlib/source/test/lux/math.lux | 19 +++-- stdlib/source/test/lux/math/infix.lux | 23 ++--- stdlib/source/test/lux/math/logic/fuzzy.lux | 10 +-- stdlib/source/test/lux/time/duration.lux | 3 +- .../test/lux/tool/compiler/default/syntax.lux | 16 ++-- .../test/lux/tool/compiler/phase/analysis/case.lux | 12 +-- .../lux/tool/compiler/phase/analysis/function.lux | 10 ++- .../lux/tool/compiler/phase/analysis/reference.lux | 6 +- .../lux/tool/compiler/phase/analysis/structure.lux | 30 +++---- .../lux/tool/compiler/phase/synthesis/case.lux | 8 +- .../lux/tool/compiler/phase/synthesis/function.lux | 26 +++--- .../tool/compiler/phase/synthesis/structure.lux | 16 ++-- stdlib/source/test/lux/type.lux | 14 ++-- stdlib/source/test/lux/type/check.lux | 12 +-- stdlib/source/test/lux/type/dynamic.lux | 7 +- stdlib/source/test/lux/type/implicit.lux | 6 +- stdlib/source/test/lux/type/resource.lux | 17 ++-- stdlib/source/test/lux/world/file.lux | 17 ++-- 74 files changed, 747 insertions(+), 662 deletions(-) (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/licentia.lux b/stdlib/source/test/licentia.lux index 7f623d26d..61bdbb0b2 100644 --- a/stdlib/source/test/licentia.lux +++ b/stdlib/source/test/licentia.lux @@ -7,9 +7,9 @@ [data ["." bit ("#;." equivalence)] ["." maybe ("#;." functor)] - [number - ["." nat ("#;." interval)]] ["." text] + [number + ["n" nat ("#@." interval)]] [collection ["." list ("#;." functor)]]] [math @@ -43,11 +43,11 @@ (def: period (Random (Period Nat)) (do r.monad - [start (r.filter (|>> (n/= nat;top) not) + [start (r.filter (|>> (n.= n@top) not) r.nat) - #let [wiggle-room (n/- start nat;top)] + #let [wiggle-room (n.- start n@top)] end (:: @ map - (|>> (n/% wiggle-room) (n/max 1)) + (|>> (n.% wiggle-room) (n.max 1)) r.nat)] (wrap {#time.start start #time.end end}))) @@ -105,7 +105,7 @@ (def: (variable-list max-size gen-element) (All [a] (-> Nat (Random a) (Random (List a)))) (do r.monad - [amount (:: @ map (n/% (n/max 1 max-size)) + [amount (:: @ map (n.% (n.max 1 max-size)) r.nat)] (r.list amount gen-element))) diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 580c02d2e..e99cdb85a 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -20,6 +20,7 @@ ["." name] [number ["." i64] + ["n" nat] ["i" int] ["r" rev] ["f" frac]]] @@ -157,11 +158,11 @@ [value random.i64] ($_ _.and (_.test "'inc' and 'dec' are opposites." - (and (|> value inc dec (n/= value)) - (|> value dec inc (n/= value)))) + (and (|> value inc dec (n.= value)) + (|> value dec inc (n.= value)))) (_.test "'inc' and 'dec' shift the number by 1." - (and (|> (inc value) (n/- value) (n/= 1)) - (|> value (n/- (dec value)) (n/= 1))))))) + (and (|> (inc value) (n.- value) (n.= 1)) + (|> value (n.- (dec value)) (n.= 1))))))) (def: (check-neighbors has-property? value) (All [a] (-> (Predicate (I64 a)) (I64 a) Bit)) @@ -230,15 +231,15 @@ Test ($_ _.and (do random.monad - [factor (random@map (|>> (n/% 10) (n/max 1)) random.nat) - iterations (random@map (n/% 100) random.nat) - #let [expected (n/* factor iterations)]] + [factor (random@map (|>> (n.% 10) (n.max 1)) random.nat) + iterations (random@map (n.% 100) random.nat) + #let [expected (n.* factor iterations)]] (_.test "Can write loops." - (n/= expected + (n.= expected (loop [counter 0 value 0] - (if (n/< iterations counter) - (recur (inc counter) (n/+ factor value)) + (if (n.< iterations counter) + (recur (inc counter) (n.+ factor value)) value))))) (do random.monad @@ -248,32 +249,32 @@ (_.test "Can create lists easily through macros." (and (case (list first second third) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) - (and (n/= first first') - (n/= second second') - (n/= third third')) + (and (n.= first first') + (n.= second second') + (n.= third third')) _ false) (case (list& first (list second third)) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) - (and (n/= first first') - (n/= second second') - (n/= third third')) + (and (n.= first first') + (n.= second second') + (n.= third third')) _ false) (case (list& first second (list third)) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) - (and (n/= first first') - (n/= second second') - (n/= third third')) + (and (n.= first first') + (n.= second second') + (n.= third third')) _ false)))) )) (template: (quadrance cat0 cat1) - (n/+ (n/* cat0 cat0) (n/* cat1 cat1))) + (n.+ (n.* cat0 cat0) (n.* cat1 cat1))) (def: templates Test @@ -281,7 +282,7 @@ [cat0 random.nat cat1 random.nat] (_.test "Template application is a stand-in for the templated code." - (n/= (n/+ (n/* cat0 cat0) (n/* cat1 cat1)) + (n.= (n.+ (n.* cat0 cat0) (n.* cat1 cat1)) (quadrance cat0 cat1))))) (def: cross-platform-support @@ -292,11 +293,11 @@ on-valid-host random.nat] ($_ _.and (_.test "Can provide default in case there is no particular host/platform support." - (n/= on-default + (n.= on-default (for {"" on-fake-host} on-default))) (_.test "Can pick code depending on the host/platform being targeted." - (n/= on-valid-host + (n.= on-valid-host (`` (for {(~~ (static @.old)) on-valid-host (~~ (static @.jvm)) on-valid-host (~~ (static @.js)) on-valid-host} @@ -312,7 +313,7 @@ (<| (_.context "Even or odd.") ($_ _.and (<| (_.context "Natural numbers.") - (..even-or-odd random.nat n/even? n/odd?)) + (..even-or-odd random.nat n.even? n.odd?)) (<| (_.context "Integers.") (..even-or-odd random.int i.even? i.odd?)))) (<| (_.context "Minimum and maximum.") @@ -322,7 +323,7 @@ (..minimum-and-maximum <=> [ ] [ ]))] [i.= i.< i.min i.> i.max random.int "Integers."] - [n/= n/< n/min n/> n/max random.nat "Natural numbers."] + [n.= n.< n.min n.> n.max random.nat "Natural numbers."] [r.= r.< r.min r.> r.max random.rev "Revolutions."] [f.= f.< f.min f.> f.max random.safe-frac "Fractions."] ))))) @@ -334,7 +335,7 @@ (..conversion <=>))] [i.= .nat .int (random@map (i.% +1,000,000) random.int)] - [n/= .int .nat (random@map (n/% 1,000,000) random.nat)] + [n.= .int .nat (random@map (n.% 1,000,000) random.nat)] [i.= i.frac f.int (random@map (i.% +1,000,000) random.int)] [f.= f.int i.frac (random@map (|>> (i.% +1,000,000) i.frac) random.int)] [r.= r.frac f.rev frac-rev] diff --git a/stdlib/source/test/lux/abstract/apply.lux b/stdlib/source/test/lux/abstract/apply.lux index b2d67d3e9..87c706f55 100644 --- a/stdlib/source/test/lux/abstract/apply.lux +++ b/stdlib/source/test/lux/abstract/apply.lux @@ -2,6 +2,8 @@ [lux #* [abstract/monad (#+ do)] [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [control @@ -19,7 +21,7 @@ (do r.monad [sample (:: @ map injection r.nat)] (_.test "Identity." - ((comparison n/=) + ((comparison n.=) (_;apply (injection function.identity) sample) sample)))) @@ -27,9 +29,9 @@ (All [f] (-> (Injection f) (Comparison f) (Apply f) Test)) (do r.monad [sample r.nat - increase (:: @ map n/+ r.nat)] + increase (:: @ map n.+ r.nat)] (_.test "Homomorphism." - ((comparison n/=) + ((comparison n.=) (_;apply (injection increase) (injection sample)) (injection (increase sample)))))) @@ -37,9 +39,9 @@ (All [f] (-> (Injection f) (Comparison f) (Apply f) Test)) (do r.monad [sample r.nat - increase (:: @ map n/+ r.nat)] + increase (:: @ map n.+ r.nat)] (_.test "Interchange." - ((comparison n/=) + ((comparison n.=) (_;apply (injection increase) (injection sample)) (_;apply (injection (function (_ f) (f sample))) (injection increase)))))) @@ -47,10 +49,10 @@ (All [f] (-> (Injection f) (Comparison f) (Apply f) Test)) (do r.monad [sample r.nat - increase (:: @ map n/+ r.nat) - decrease (:: @ map n/- r.nat)] + increase (:: @ map n.+ r.nat) + decrease (:: @ map n.- r.nat)] (_.test "Composition." - ((comparison n/=) + ((comparison n.=) (_$ _;apply (injection function.compose) (injection increase) diff --git a/stdlib/source/test/lux/abstract/fold.lux b/stdlib/source/test/lux/abstract/fold.lux index 99ac25c5b..334d43e50 100644 --- a/stdlib/source/test/lux/abstract/fold.lux +++ b/stdlib/source/test/lux/abstract/fold.lux @@ -3,7 +3,10 @@ ["_" test (#+ Test)] ["%" data/text/format (#+ format)] ["r" math/random] - [abstract/monad (#+ do)]] + [abstract/monad (#+ do)] + [data + [number + ["n" nat]]]] [// [functor (#+ Injection Comparison)]] {1 @@ -16,5 +19,5 @@ [subject r.nat parameter r.nat] (_.test "Can fold." - (n/= (/@fold n/+ parameter (injection subject)) - (n/+ parameter subject)))))) + (n.= (/@fold n.+ parameter (injection subject)) + (n.+ parameter subject)))))) diff --git a/stdlib/source/test/lux/abstract/functor.lux b/stdlib/source/test/lux/abstract/functor.lux index 4c7c87c63..388a66ffc 100644 --- a/stdlib/source/test/lux/abstract/functor.lux +++ b/stdlib/source/test/lux/abstract/functor.lux @@ -7,7 +7,10 @@ [equivalence (#+ Equivalence)] [monad (#+ do)]] [control - ["." function]]] + ["." function]] + [data + [number + ["n" nat]]]] {1 ["." / (#+ Functor)]}) @@ -24,7 +27,7 @@ (do r.monad [sample (:: @ map injection r.nat)] (_.test "Identity." - ((comparison n/=) + ((comparison n.=) (/@map function.identity sample) sample)))) @@ -32,9 +35,9 @@ (All [f] (-> (Injection f) (Comparison f) (Functor f) Test)) (do r.monad [sample r.nat - increase (:: @ map n/+ r.nat)] + increase (:: @ map n.+ r.nat)] (_.test "Homomorphism." - ((comparison n/=) + ((comparison n.=) (/@map increase (injection sample)) (injection (increase sample)))))) @@ -42,10 +45,10 @@ (All [f] (-> (Injection f) (Comparison f) (Functor f) Test)) (do r.monad [sample (:: @ map injection r.nat) - increase (:: @ map n/+ r.nat) - decrease (:: @ map n/- r.nat)] + increase (:: @ map n.+ r.nat) + decrease (:: @ map n.- r.nat)] (_.test "Composition." - ((comparison n/=) + ((comparison n.=) (|> sample (/@map increase) (/@map decrease)) (|> sample (/@map (|>> increase decrease))))))) diff --git a/stdlib/source/test/lux/abstract/interval.lux b/stdlib/source/test/lux/abstract/interval.lux index e4a489822..92f2a6faf 100644 --- a/stdlib/source/test/lux/abstract/interval.lux +++ b/stdlib/source/test/lux/abstract/interval.lux @@ -11,7 +11,7 @@ [pipe (#+ case>)]] [data [number - ["." nat]] + ["n" nat]] [text ["%" format (#+ format)]] [collection @@ -27,20 +27,20 @@ (Random (Interval Nat)) (do r.monad [bottom r.nat - top (|> r.nat (r.filter (|>> (n/= bottom) not)))] + top (|> r.nat (r.filter (|>> (n.= bottom) not)))] (if ( top bottom) - (wrap (/.between nat.enum bottom top)) - (wrap (/.between nat.enum top bottom)))))] + (wrap (/.between n.enum bottom top)) + (wrap (/.between n.enum top bottom)))))] - [inner n/<] - [outer n/>] + [inner n.<] + [outer n.>] ) (def: #export singleton (Random (Interval Nat)) (do r.monad [point r.nat] - (wrap (/.singleton nat.enum point)))) + (wrap (/.singleton n.enum point)))) (def: #export interval (Random (Interval Nat)) @@ -54,7 +54,7 @@ (do r.monad [bottom r.nat top r.nat - #let [interval (/.between nat.enum bottom top)]] + #let [interval (/.between n.enum bottom top)]] ($_ _.and (_.test "A boundary value belongs to its interval." (and (/.within? interval bottom) @@ -124,16 +124,16 @@ (def: location Test (do r.monad - [[l m r] (|> (r.set nat.hash 3 r.nat) + [[l m r] (|> (r.set n.hash 3 r.nat) (:: @ map (|>> set.to-list - (list.sort n/<) + (list.sort n.<) (case> (^ (list b t1 t2)) [b t1 t2] _ (undefined))))) - #let [left (/.singleton nat.enum l) - right (/.singleton nat.enum r)]] + #let [left (/.singleton n.enum l) + right (/.singleton n.enum r)]] ($_ _.and (_.test "'precedes?' and 'succeeds?' are symetric." (and (/.precedes? right left) @@ -146,36 +146,36 @@ (def: touch Test (do r.monad - [[b t1 t2] (|> (r.set nat.hash 3 r.nat) + [[b t1 t2] (|> (r.set n.hash 3 r.nat) (:: @ map (|>> set.to-list - (list.sort n/<) + (list.sort n.<) (case> (^ (list b t1 t2)) [b t1 t2] _ (undefined))))) - #let [int-left (/.between nat.enum t1 t2) - int-right (/.between nat.enum b t1)]] + #let [int-left (/.between n.enum t1 t2) + int-right (/.between n.enum b t1)]] ($_ _.and (_.test "An interval meets another if its top is the other's bottom." (/.meets? int-left int-right)) (_.test "Two intervals touch one another if any one meets the other." (/.touches? int-left int-right)) (_.test "Can check if 2 intervals start together." - (/.starts? (/.between nat.enum b t2) - (/.between nat.enum b t1))) + (/.starts? (/.between n.enum b t2) + (/.between n.enum b t1))) (_.test "Can check if 2 intervals finish together." - (/.finishes? (/.between nat.enum b t2) - (/.between nat.enum t1 t2))) + (/.finishes? (/.between n.enum b t2) + (/.between n.enum t1 t2))) ))) (def: overlap Test (do r.monad [some-interval ..interval - [x0 x1 x2 x3] (|> (r.set nat.hash 4 r.nat) + [x0 x1 x2 x3] (|> (r.set n.hash 4 r.nat) (:: @ map (|>> set.to-list - (list.sort n/<) + (list.sort n.<) (case> (^ (list x0 x1 x2 x3)) [x0 x1 x2 x3] @@ -186,30 +186,30 @@ (/.nested? some-interval some-interval)) (_.test "No interval overlaps with itself." (not (/.overlaps? some-interval some-interval))) - (let [small-inner (/.between nat.enum x1 x2) - large-inner (/.between nat.enum x0 x3)] + (let [small-inner (/.between n.enum x1 x2) + large-inner (/.between n.enum x0 x3)] (_.test "Inner intervals can be nested inside one another." (and (/.nested? large-inner small-inner) (not (/.nested? small-inner large-inner))))) - (let [left-inner (/.between nat.enum x0 x2) - right-inner (/.between nat.enum x1 x3)] + (let [left-inner (/.between n.enum x0 x2) + right-inner (/.between n.enum x1 x3)] (_.test "Inner intervals can overlap one another." (and (/.overlaps? left-inner right-inner) (/.overlaps? right-inner left-inner)))) - (let [small-outer (/.between nat.enum x2 x1) - large-outer (/.between nat.enum x3 x0)] + (let [small-outer (/.between n.enum x2 x1) + large-outer (/.between n.enum x3 x0)] (_.test "Outer intervals can be nested inside one another." (and (/.nested? small-outer large-outer) (not (/.nested? large-outer small-outer))))) - (let [left-inner (/.between nat.enum x0 x1) - right-inner (/.between nat.enum x2 x3) - outer (/.between nat.enum x0 x3)] + (let [left-inner (/.between n.enum x0 x1) + right-inner (/.between n.enum x2 x3) + outer (/.between n.enum x0 x3)] (_.test "Inners can be nested inside outers." (and (/.nested? outer left-inner) (/.nested? outer right-inner)))) - (let [left-inner (/.between nat.enum x0 x2) - right-inner (/.between nat.enum x1 x3) - outer (/.between nat.enum x1 x2)] + (let [left-inner (/.between n.enum x0 x2) + right-inner (/.between n.enum x1 x3) + outer (/.between n.enum x1 x2)] (_.test "Inners can overlap outers." (and (/.overlaps? outer left-inner) (/.overlaps? outer right-inner)))) diff --git a/stdlib/source/test/lux/abstract/monad.lux b/stdlib/source/test/lux/abstract/monad.lux index c420d6416..ecb292afb 100644 --- a/stdlib/source/test/lux/abstract/monad.lux +++ b/stdlib/source/test/lux/abstract/monad.lux @@ -1,6 +1,8 @@ (.module: [lux #* [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [control @@ -18,10 +20,10 @@ (do r.monad [sample r.nat morphism (:: @ map (function (_ diff) - (|>> (n/+ diff) _;wrap)) + (|>> (n.+ diff) _;wrap)) r.nat)] (_.test "Left identity." - ((comparison n/=) + ((comparison n.=) (|> (injection sample) (_;map morphism) _;join) (morphism sample))))) @@ -30,7 +32,7 @@ (do r.monad [sample r.nat] (_.test "Right identity." - ((comparison n/=) + ((comparison n.=) (|> (injection sample) (_;map _;wrap) _;join) (injection sample))))) @@ -39,13 +41,13 @@ (do r.monad [sample r.nat increase (:: @ map (function (_ diff) - (|>> (n/+ diff) _;wrap)) + (|>> (n.+ diff) _;wrap)) r.nat) decrease (:: @ map (function (_ diff) - (|>> (n/- diff) _;wrap)) + (|>> (n.- diff) _;wrap)) r.nat)] (_.test "Associativity." - ((comparison n/=) + ((comparison n.=) (|> (injection sample) (_;map increase) _;join (_;map decrease) _;join) (|> (injection sample) (_;map (|>> increase (_;map decrease) _;join)) _;join))))) diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux index cc7456292..cde83e09d 100644 --- a/stdlib/source/test/lux/control/concurrency/actor.lux +++ b/stdlib/source/test/lux/control/concurrency/actor.lux @@ -7,6 +7,8 @@ ["ex" exception] ["." io (#+ IO io)]] [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [math @@ -33,7 +35,7 @@ (message: #export Counter (count! {increment Nat} state self Nat) - (let [state' (n/+ increment state)] + (let [state' (n.+ increment state)] (promise;wrap (#try.Success [state' state'])))) (def: #export test @@ -69,9 +71,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 (#try.Success outcome) diff --git a/stdlib/source/test/lux/control/concurrency/atom.lux b/stdlib/source/test/lux/control/concurrency/atom.lux index 15d24b826..1cf645530 100644 --- a/stdlib/source/test/lux/control/concurrency/atom.lux +++ b/stdlib/source/test/lux/control/concurrency/atom.lux @@ -6,7 +6,10 @@ [math ["r" random]] [control - ["." io]]] + ["." io]] + [data + [number + ["n" nat]]]] {1 ["." /]}) @@ -20,17 +23,17 @@ #let [box (/.atom value)]] ($_ _.and (_.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 inc box)) - (n/= (inc swap-value) (io.run (/.read box))))) + (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/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux index f9cea5737..ab705bfce 100644 --- a/stdlib/source/test/lux/control/concurrency/frp.lux +++ b/stdlib/source/test/lux/control/concurrency/frp.lux @@ -6,7 +6,7 @@ ["." io (#+ IO io)]] [data [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor)]]] [math @@ -19,7 +19,7 @@ (def: #export test Test - (let [(^open "list@.") (list.equivalence nat.equivalence)] + (let [(^open "list@.") (list.equivalence n.equivalence)] (do r.monad [inputs (r.list 5 r.nat) sample r.nat] @@ -27,10 +27,10 @@ (wrap (do promise.monad [output (|> inputs (/.sequential 0) - (/.filter n/even?) + (/.filter n.even?) /.consume)] (_.assert "Can filter a channel's elements." - (list@= (list.filter n/even? inputs) + (list@= (list.filter n.even? inputs) output)))) (wrap (do promise.monad [output (|> inputs diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux index 05329d9f0..bd5d72d43 100644 --- a/stdlib/source/test/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux @@ -10,6 +10,8 @@ ["." atom (#+ Atom)]]] [data ["." maybe] + [number + ["n" nat]] ["." text ("#;." equivalence monoid) ["%" format (#+ format)]] [collection @@ -21,7 +23,7 @@ ## (def: (wait-many-times times semaphore) ## (-> Nat /.Semaphore (Promise Any)) ## (loop [steps times] -## (if (n/> 0 steps) +## (if (n.> 0 steps) ## (do promise.monad ## [_ (/.wait semaphore)] ## (recur (dec steps))) @@ -30,7 +32,7 @@ ## (context: "Semaphore." ## (<| (times 100) ## (do @ -## [open-positions (|> r.nat (:: @ map (|>> (n/% 10) (n/max 1))))] +## [open-positions (|> r.nat (:: @ map (|>> (n.% 10) (n.max 1))))] ## ($_ seq ## (let [semaphore (/.semaphore open-positions)] ## (wrap (do promise.monad @@ -51,8 +53,8 @@ ## (let [semaphore (/.semaphore open-positions)] ## (wrap (do promise.monad ## [_ (: (Promise Any) -## (loop [steps (n/* 2 open-positions)] -## (if (n/> 0 steps) +## (loop [steps (n.* 2 open-positions)] +## (if (n.> 0 steps) ## (do @ ## [_ (/.wait semaphore) ## _ (/.signal semaphore)] @@ -82,7 +84,7 @@ ## (context: "Mutex." ## (<| (times 100) ## (do @ -## [repetitions (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10))))] +## [repetitions (|> r.nat (:: @ map (|>> (n.% 100) (n.max 10))))] ## ($_ seq ## (let [mutex (/.mutex [])] ## (wrap (do promise.monad diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux index ca9d3c050..c84663a96 100644 --- a/stdlib/source/test/lux/control/concurrency/stm.lux +++ b/stdlib/source/test/lux/control/concurrency/stm.lux @@ -7,7 +7,7 @@ [data ["%" text/format (#+ format)] [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor)]]] [math @@ -43,29 +43,29 @@ (wrap (do promise.monad [output (/.commit (/.read (/.var 0)))] (_.assert "Can read STM vars." - (n/= 0 output)))) + (n.= 0 output)))) (wrap (do promise.monad [#let [_var (/.var 0)] output (/.commit (do /.monad [_ (/.write 5 _var)] (/.read _var)))] (_.assert "Can write STM vars." - (n/= 5 output)))) + (n.= 5 output)))) (wrap (do promise.monad [#let [_var (/.var 5)] output (/.commit (do /.monad - [_ (/.update (n/* 3) _var)] + [_ (/.update (n.* 3) _var)] (/.read _var)))] (_.assert "Can update STM vars." - (n/= 15 output)))) + (n.= 15 output)))) (wrap (do promise.monad [#let [_var (/.var 0) changes (io.run (read! (io.run (/.follow _var))))] _ (/.commit (/.write 5 _var)) - _ (/.commit (/.update (n/* 3) _var)) + _ (/.commit (/.update (n.* 3) _var)) changes (promise.future (atom.read changes))] (_.assert "Can follow all the changes to STM vars." - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = (list 5 15) (list.reverse changes))))) (wrap (let [_concurrency-var (/.var 0)] @@ -80,5 +80,5 @@ last-val (/.commit (/.read _concurrency-var))] (_.assert "Can modify STM vars concurrently from multiple threads." (|> process.parallelism - (n/* iterations-per-process) - (n/= last-val)))))))))) + (n.* iterations-per-process) + (n.= last-val)))))))))) diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux index b8d4b96d2..105dccd3f 100644 --- a/stdlib/source/test/lux/control/continuation.lux +++ b/stdlib/source/test/lux/control/continuation.lux @@ -10,7 +10,7 @@ ["$." monad]]}] [data [number - ["." nat]] + ["n" nat]] [text ["%" format (#+ format)]] [collection @@ -43,10 +43,10 @@ ($monad.spec ..injection ..comparison /.monad) (_.test "Can run continuations to compute their values." - (n/= sample (/.run (_;wrap sample)))) + (n.= sample (/.run (_;wrap sample)))) (_.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) @@ -54,21 +54,21 @@ [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) (inc idx)]) + (if (n.< 10 idx) + (restart [(n.+ 10 output) (inc idx)]) (wrap output)))))) (_.test "Can use delimited continuations with shifting." (let [(^open "_;.") /.monad - (^open "list;.") (list.equivalence nat.equivalence) + (^open "list;.") (list.equivalence n.equivalence) visit (: (-> (List Nat) (Cont (List Nat) (List Nat))) (function (visit xs) diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux index 46d495a4b..fde485472 100644 --- a/stdlib/source/test/lux/control/exception.lux +++ b/stdlib/source/test/lux/control/exception.lux @@ -2,6 +2,8 @@ [lux #* [abstract/monad (#+ do)] [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [math @@ -16,22 +18,22 @@ (def: #export test (do r.monad [right r.nat - wrong (r.filter (|>> (n/= right) not) r.nat)] + wrong (r.filter (|>> (n.= right) not) r.nat)] (<| (_.context (%.name (name-of /.Exception))) ($_ _.and (_.test "Can catch exceptions." - (n/= right + (n.= right (|> (/.throw an-exception []) (/.catch an-exception (function (_ ex) right)) (/.otherwise (function (_ ex) wrong))))) (_.test "Can catch multiple exceptions." - (n/= right + (n.= right (|> (/.throw another-exception []) (/.catch an-exception (function (_ ex) wrong)) (/.catch another-exception (function (_ ex) right)) (/.otherwise (function (_ ex) wrong))))) (_.test "Can handle uncaught exceptions." - (n/= right + (n.= right (|> (/.throw another-exception []) (/.catch an-exception (function (_ ex) wrong)) (/.otherwise (function (_ ex) right))))))))) diff --git a/stdlib/source/test/lux/control/io.lux b/stdlib/source/test/lux/control/io.lux index 4e000d39c..fb5d3e67b 100644 --- a/stdlib/source/test/lux/control/io.lux +++ b/stdlib/source/test/lux/control/io.lux @@ -9,7 +9,10 @@ [/ ["$." functor (#+ Injection Comparison)] ["$." apply] - ["$." monad]]}]] + ["$." monad]]}] + [data + [number + ["n" nat]]]] {1 ["." / (#+ IO) [// @@ -36,7 +39,7 @@ ($monad.spec ..injection ..comparison /.monad) (_.test "Can execute computations designated as I/O computations." - (n/= sample (/.run (/.io sample)))) + (n.= sample (/.run (/.io sample)))) (_.test "I/O operations won't execute unless they are explicitly run." (exec (/.exit exit-code) true)))))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index fc8de4828..58a35ae02 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -15,7 +15,7 @@ ["s" code]]] [data [number - ["." nat]] + ["n" nat]] ["." text ("#;." equivalence) ["%" format (#+ format)]] [collection @@ -76,17 +76,17 @@ Test (do r.monad [expected0 r.nat - variadic (:: @ map (|>> (n/max 1) (n/min 20)) r.nat) + variadic (:: @ map (|>> (n.max 1) (n.min 20)) r.nat) expected+ (r.list variadic r.nat) - even0 (r.filter n/even? r.nat) - odd0 (r.filter n/odd? r.nat) + even0 (r.filter n.even? r.nat) + odd0 (r.filter n.odd? r.nat) not0 r.bit] ($_ _.and (_.test "Can optionally succeed with some parser." (and (|> (list (code.nat expected0)) (/.run (/.maybe s.nat)) (match (#.Some actual) - (n/= expected0 actual))) + (n.= expected0 actual))) (|> (list (code.int (.int expected0))) (/.run (/.maybe s.nat)) (match #.None @@ -95,7 +95,7 @@ (and (|> (list;map code.nat expected+) (/.run (/.some s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = expected+ actual))) + (:: (list.equivalence n.equivalence) = expected+ actual))) (|> (list;map (|>> .int code.int) expected+) (/.run (/.some s.nat)) (match #.Nil @@ -104,23 +104,23 @@ (and (|> (list;map code.nat expected+) (/.run (/.many s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = expected+ actual))) + (:: (list.equivalence n.equivalence) = expected+ actual))) (|> (list (code.nat expected0)) (/.run (/.many s.nat)) (match (list actual) - (n/= expected0 actual))) + (n.= expected0 actual))) (|> (list;map (|>> .int code.int) expected+) (/.run (/.many s.nat)) fails?))) (_.test "Can use either parser." - (let [even (/.filter n/even? s.nat) - odd (/.filter n/odd? s.nat)] + (let [even (/.filter n.even? s.nat) + odd (/.filter n.odd? s.nat)] (and (|> (list (code.nat even0)) (/.run (/.either even odd)) - (match actual (n/= even0 actual))) + (match actual (n.= even0 actual))) (|> (list (code.nat odd0)) (/.run (/.either even odd)) - (match actual (n/= odd0 actual))) + (match actual (n.= odd0 actual))) (|> (list (code.bit not0)) (/.run (/.either even odd)) fails?)))) @@ -137,8 +137,8 @@ Test (do r.monad [failure (r.ascii 1) - variadic (:: @ map (|>> (n/max 1) (n/min 20)) r.nat) - times (:: @ map (n/% variadic) r.nat) + variadic (:: @ map (|>> (n.max 1) (n.min 20)) r.nat) + times (:: @ map (n.% variadic) r.nat) expected+ (r.list variadic r.nat) separator (r.ascii 1)] ($_ _.and @@ -150,7 +150,7 @@ (and (|> (list;map code.nat expected+) (/.run (/.exactly times s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = (list.take times expected+) actual))) (|> (list;map code.nat expected+) @@ -160,7 +160,7 @@ (and (|> (list;map code.nat expected+) (/.run (/.at-least times s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = expected+ actual))) (|> (list;map code.nat expected+) @@ -170,33 +170,33 @@ (and (|> (list;map code.nat expected+) (/.run (/.at-most times s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = (list.take times expected+) actual))) (|> (list;map code.nat expected+) (/.run (/.at-most (inc variadic) s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = expected+ actual))))) (_.test "Can apply a parser between N and M times." (and (|> (list;map code.nat expected+) (/.run (/.between times variadic s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = expected+ actual))) (|> (list;map code.nat (list.take times expected+)) (/.run (/.between times variadic s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = (list.take times expected+) actual))))) (_.test "Can parse while taking separators into account." (|> (list.interpose (code.text separator) (list;map code.nat expected+)) (/.run (/.sep-by (s.this! (code.text separator)) s.nat)) (match actual - (:: (list.equivalence nat.equivalence) = + (:: (list.equivalence n.equivalence) = expected+ actual)))) (_.test "Can obtain the whole of the remaining input." diff --git a/stdlib/source/test/lux/control/parser/cli.lux b/stdlib/source/test/lux/control/parser/cli.lux index b304a2ab2..c41a33878 100644 --- a/stdlib/source/test/lux/control/parser/cli.lux +++ b/stdlib/source/test/lux/control/parser/cli.lux @@ -11,7 +11,7 @@ ["p" parser]] [data [number - ["." nat ("#@." decimal)]] + ["n" nat ("#@." decimal)]] ["." text ("#@." equivalence)] [collection ["." list]]]] @@ -22,8 +22,8 @@ Test (<| (_.context (name.module (name-of /._))) (do r.monad - [num-args (|> r.nat (:: @ map (n/% 10))) - #let [gen-arg (:: @ map nat@encode r.nat)] + [num-args (|> r.nat (:: @ map (n.% 10))) + #let [gen-arg (:: @ map n@encode r.nat)] yes gen-arg #let [gen-ignore (r.filter (|>> (text@= yes) not) (r.unicode 5))] @@ -52,12 +52,12 @@ (#try.Success _) #0)))) (_.test "Can use custom token parsers." - (|> (/.run (/.parse nat@decode) (list yes)) + (|> (/.run (/.parse n@decode) (list yes)) (case> (#try.Failure _) #0 (#try.Success parsed) - (text@= (nat@encode parsed) + (text@= (n@encode parsed) yes)))) (_.test "Can query if there are any more inputs." (and (|> (/.run /.end (list)) diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index 8917e63fa..441f2f5da 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -10,6 +10,8 @@ ["p" parser]] [data ["." text ("#@." equivalence)] + [number + ["n" nat]] [collection ["." list]]] [math @@ -41,7 +43,7 @@ "") (case> (#.Right _) true _ false))) (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10)))) + [size (|> r.nat (:: @ map (|>> (n.% 100) (n.max 10)))) sample (r.unicode size) non-sample (|> (r.unicode size) (r.filter (|>> (text@= sample) not)))] diff --git a/stdlib/source/test/lux/control/pipe.lux b/stdlib/source/test/lux/control/pipe.lux index 4d4e03a79..0aecde080 100644 --- a/stdlib/source/test/lux/control/pipe.lux +++ b/stdlib/source/test/lux/control/pipe.lux @@ -6,6 +6,8 @@ [data ["." identity] ["." name] + [number + ["n" nat]] ["." text ("#@." equivalence) ["%" format (#+ format)]]] [math @@ -22,65 +24,65 @@ (do @ [another r.nat] (_.test "Can dismiss previous pipeline results and begin a new one." - (n/= (inc another) + (n.= (inc another) (|> sample - (n/* 3) - (n/+ 4) + (n.* 3) + (n.+ 4) (new> another [inc]))))) (_.test "Let-binding" - (n/= (n/+ sample sample) + (n.= (n.+ sample sample) (|> sample - (let> x [(n/+ x x)])))) + (let> x [(n.+ x x)])))) (_.test "'Conditional' branching." - (text@= (cond (n/= 0 sample) "zero" - (n/even? sample) "even" + (text@= (cond (n.= 0 sample) "zero" + (n.even? sample) "even" "odd") (|> sample - (cond> [(n/= 0)] [(new> "zero" [])] - [n/even?] [(new> "even" [])] + (cond> [(n.= 0)] [(new> "zero" [])] + [n.even?] [(new> "even" [])] [(new> "odd" [])])))) (_.test "'If' branching." - (text@= (if (n/even? sample) + (text@= (if (n.even? sample) "even" "odd") (|> sample - (if> [n/even?] + (if> [n.even?] [(new> "even" [])] [(new> "odd" [])])))) (_.test "'When' branching." - (n/= (if (n/even? sample) - (n/* 2 sample) + (n.= (if (n.even? sample) + (n.* 2 sample) sample) (|> sample - (when> [n/even?] - [(n/* 2)])))) + (when> [n.even?] + [(n.* 2)])))) (_.test "Can loop." - (n/= (n/* 10 sample) + (n.= (n.* 10 sample) (|> sample - (loop> [(n/= (n/* 10 sample)) not] - [(n/+ sample)])))) + (loop> [(n.= (n.* 10 sample)) not] + [(n.+ sample)])))) (_.test "Monads." - (n/= (inc (n/+ 4 (n/* 3 sample))) + (n.= (inc (n.+ 4 (n.* 3 sample))) (|> sample (do> identity.monad - [(n/* 3)] - [(n/+ 4)] + [(n.* 3)] + [(n.+ 4)] [inc])))) (_.test "Execution." - (n/= (n/* 10 sample) + (n.= (n.* 10 sample) (|> sample (exec> [%.nat (format "sample = ") log!]) - (n/* 10)))) + (n.* 10)))) (_.test "Tuple." (let [[left middle right] (|> sample (tuple> [inc] [dec] [%.nat]))] - (and (n/= (inc sample) left) - (n/= (dec sample) middle) + (and (n.= (inc sample) left) + (n.= (dec sample) middle) (text@= (%.nat sample) right)))) (_.test "Pattern-matching." - (text@= (case (n/% 10 sample) + (text@= (case (n.% 10 sample) 0 "zero" 1 "one" 2 "two" @@ -93,7 +95,7 @@ 9 "nine" _ "???") (|> sample - (n/% 10) + (n.% 10) (case> 0 "zero" 1 "one" 2 "two" diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux index 49cb23a48..434ec5896 100644 --- a/stdlib/source/test/lux/control/reader.lux +++ b/stdlib/source/test/lux/control/reader.lux @@ -9,6 +9,8 @@ ["$." apply] ["$." monad]]}] [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [math @@ -40,18 +42,18 @@ ($monad.spec ..injection ..comparison /.monad) (_.test "Can query the environment." - (n/= sample + (n.= sample (/.run sample /.ask))) (_.test "Can modify an environment locally." - (n/= (n/* factor sample) - (/.run sample (/.local (n/* factor) /.ask)))) + (n.= (n.* factor sample) + (/.run sample (/.local (n.* factor) /.ask)))) (let [(^open "io@.") io.monad] (_.test "Can add reader functionality to any monad." (|> (: (/.Reader Any (IO Nat)) (do (/.with io.monad) [a (/.lift (io@wrap sample)) b (wrap factor)] - (wrap (n/* b a)))) + (wrap (n.* b a)))) (/.run []) io.run - (n/= (n/* factor sample))))))))) + (n.= (n.* factor sample))))))))) diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux index 9ecf520c2..e7000fc48 100644 --- a/stdlib/source/test/lux/control/region.lux +++ b/stdlib/source/test/lux/control/region.lux @@ -6,6 +6,8 @@ [control ["." try (#+ Try)]] [data + [number + ["n" nat]] [text ["%" format (#+ format)]] [collection @@ -38,7 +40,7 @@ Test (<| (_.context (%.name (name-of /._))) (do r.monad - [expected-clean-ups (|> r.nat (:: @ map (|>> (n/% 100) (n/max 1))))] + [expected-clean-ups (|> r.nat (:: @ map (|>> (n.% 100) (n.max 1))))] ($_ _.and (_.test "Clean-up functions are always run when region execution is done." (thread.run @@ -56,7 +58,7 @@ (wrap []))) actual-clean-ups (thread.read clean-up-counter)] (wrap (and (success? outcome) - (n/= expected-clean-ups + (n.= expected-clean-ups actual-clean-ups)))))) (_.test "Can clean-up despite errors." (thread.run @@ -75,7 +77,7 @@ (wrap []))) actual-clean-ups (thread.read clean-up-counter)] (wrap (and (failure? outcome) - (n/= expected-clean-ups + (n.= expected-clean-ups actual-clean-ups)))))) (_.test "Errors can propagate from the cleaners." (thread.run @@ -92,9 +94,9 @@ (list.n/range 1 expected-clean-ups))] (wrap []))) actual-clean-ups (thread.read clean-up-counter)] - (wrap (and (or (n/= 0 expected-clean-ups) + (wrap (and (or (n.= 0 expected-clean-ups) (failure? outcome)) - (n/= expected-clean-ups + (n.= expected-clean-ups actual-clean-ups)))))) (_.test "Can lift operations." (thread.run @@ -107,6 +109,6 @@ (wrap []))) actual-clean-ups (thread.read clean-up-counter)] (wrap (and (success? outcome) - (n/= expected-clean-ups + (n.= expected-clean-ups actual-clean-ups)))))) )))) diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux index edbacddd6..6aebf504b 100644 --- a/stdlib/source/test/lux/control/security/policy.lux +++ b/stdlib/source/test/lux/control/security/policy.lux @@ -15,7 +15,9 @@ ["!" capability]]] [data ["." name] - ["." text ("#@." equivalence)]] + ["." text ("#@." equivalence)] + [number + ["n" nat]]] [math ["r" random]]] {1 @@ -81,7 +83,7 @@ (_.test "Can work with private values under the same label." (and (:: policy-0 = password password) - (n/= (:: text.hash hash raw-password) + (n.= (:: text.hash hash raw-password) (:: policy-0 hash password)))) (let [policy-1 (policy []) delegate (/.delegation (:: policy-0 can-downgrade) (:: policy-1 can-upgrade))] diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux index 778162d61..1d9899539 100644 --- a/stdlib/source/test/lux/control/state.lux +++ b/stdlib/source/test/lux/control/state.lux @@ -13,6 +13,8 @@ ["." io]] [data ["." product] + [number + ["n" nat]] [text ["%" format (#+ format)]]] [math @@ -25,7 +27,7 @@ (|> computation (/.run state) product.right - (n/= output))) + (n.= output))) (def: basics (do r.monad @@ -41,16 +43,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 (inc state)] (/.use 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))) ))) @@ -78,23 +80,23 @@ (def: loops Test (do r.monad - [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)))]] ($_ _.and (_.test "'while' will only execute if the condition is #1." (|> (/.while condition (/.update inc)) (/.run 0) (let> [state' output'] - (n/= limit state')))) + (n.= limit state')))) (_.test "'do-while' will execute at least once." (|> (/.do-while condition (/.update inc)) (/.run 0) (let> [state' output'] - (or (n/= limit state') - (and (n/= 0 limit) - (n/= 1 state')))))) + (or (n.= limit state') + (and (n.= 0 limit) + (n.= 1 state')))))) ))) (def: monad-transformer @@ -109,12 +111,12 @@ (do (/.with io.monad) [a (/.lift io.monad (io;wrap left)) b (wrap right)] - (wrap (n/+ a b)))) + (wrap (n.+ a b)))) (/.run' state) io.run (let> [state' output'] - (and (n/= state state') - (n/= (n/+ left right) output'))))) + (and (n.= state state') + (n.= (n.+ left right) output'))))) ))) (def: #export test diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux index 84bcfbcd4..7d6ed0ceb 100644 --- a/stdlib/source/test/lux/control/thread.lux +++ b/stdlib/source/test/lux/control/thread.lux @@ -9,6 +9,8 @@ ["$." apply] ["$." monad]]}] [data + [number + ["n" nat]] [text ["%" format (#+ format)]]] [math @@ -37,10 +39,10 @@ ($monad.spec ..injection ..comparison /.monad) (_.test "Can safely do mutation." - (n/= (n/* factor original) + (n.= (n.* factor original) (/.run (: (All [!] (Thread ! Nat)) (do /.monad [box (/.box original) - old (/.update (n/* factor) box)] + old (/.update (n.* factor) box)] (/.read box)))))) )))) diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux index 40015c5df..47e51b54b 100644 --- a/stdlib/source/test/lux/control/try.lux +++ b/stdlib/source/test/lux/control/try.lux @@ -15,7 +15,7 @@ [data ["%" text/format (#+ format)] [number - ["." nat]]] + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -40,24 +40,24 @@ Test (<| (_.context (%.name (name-of /._))) ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (..try r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (..try r.nat)) ($functor.spec ..injection ..comparison /.functor) ($apply.spec ..injection ..comparison /.apply) ($monad.spec ..injection ..comparison /.monad) (do r.monad [left r.nat right r.nat - #let [expected (n/+ left right) + #let [expected (n.+ left right) (^open "io@.") io.monad]] (_.test "Can add try functionality to any monad." (let [lift (/.lift io.monad)] (|> (do (/.with io.monad) [a (lift (io@wrap left)) b (wrap right)] - (wrap (n/+ a b))) + (wrap (n.+ a b))) io.run (case> (#/.Success actual) - (n/= expected actual) + (n.= expected actual) _ false))))) diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux index 5f510d6c0..d33cd3969 100644 --- a/stdlib/source/test/lux/control/writer.lux +++ b/stdlib/source/test/lux/control/writer.lux @@ -14,6 +14,8 @@ ["." io]] [data ["." product] + [number + ["n" nat]] ["." text ("#;." equivalence) ["%" format (#+ format)]]] [math @@ -51,7 +53,7 @@ (|> (io.run (do (/.with text.monoid io.monad) [a (lift (io;wrap left)) b (wrap right)] - (wrap (n/+ a b)))) + (wrap (n.+ a b)))) product.right - (n/= (n/+ left right))))) + (n.= (n.+ left right))))) )))) diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index 4b1ff0c54..9889fa0ae 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -13,7 +13,7 @@ [data [number ["." i64] - ["." nat]] + ["n" nat]] [collection ["." list]]]] {1 @@ -32,7 +32,7 @@ (-> Nat (Random Binary)) (let [output (/.create size)] (loop [idx 0] - (if (n/< size idx) + (if (n.< size idx) (do r.monad [byte r.nat] (exec (try.assume (/.write/8 idx byte output)) @@ -44,29 +44,29 @@ (let [binary (/.create bytes) cap (case bytes 8 (dec 0) - _ (|> 1 (i64.left-shift (n/* 8 bytes)) dec)) + _ (|> 1 (i64.left-shift (n.* 8 bytes)) dec)) capped-value (i64.and cap value)] (succeed (do try.monad [_ (write 0 value binary) output (read 0 binary)] - (wrap (n/= capped-value output)))))) + (wrap (n.= capped-value output)))))) (def: #export test Test (<| (_.context (%.name (name-of /._))) (do r.monad - [#let [gen-size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 8))))] + [#let [gen-size (|> r.nat (:: @ map (|>> (n.% 100) (n.max 8))))] binary-size gen-size random-binary (binary binary-size) value r.nat - #let [gen-idx (|> r.nat (:: @ map (n/% binary-size)))] + #let [gen-idx (|> r.nat (:: @ map (n.% binary-size)))] [from to] (r.and gen-idx gen-idx) - #let [[from to] [(n/min from to) (n/max from to)]]] + #let [[from to] [(n.min from to) (n.max from to)]]] ($_ _.and ($equivalence.spec /.equivalence (binary binary-size)) (_.test "Can get size of binary." - (|> random-binary /.size (n/= binary-size))) + (|> random-binary /.size (n.= binary-size))) (_.test "Can read/write 8-bit values." (bits-io 1 /.read/8 /.write/8 value)) (_.test "Can read/write 16-bit values." @@ -76,15 +76,15 @@ (_.test "Can read/write 64-bit values." (bits-io 8 /.read/64 /.write/64 value)) (_.test "Can slice binaries." - (let [slice-size (|> to (n/- from) inc) + (let [slice-size (|> to (n.- from) inc) random-slice (try.assume (/.slice from to random-binary)) idxs (list.n/range 0 (dec slice-size)) reader (function (_ binary idx) (/.read/8 idx binary))] - (and (n/= slice-size (/.size random-slice)) + (and (n.= slice-size (/.size random-slice)) (case [(monad.map try.monad (reader random-slice) idxs) - (monad.map try.monad (|>> (n/+ from) (reader random-binary)) idxs)] + (monad.map try.monad (|>> (n.+ from) (reader random-binary)) idxs)] [(#try.Success slice-vals) (#try.Success binary-vals)] - (:: (list.equivalence nat.equivalence) = slice-vals binary-vals) + (:: (list.equivalence n.equivalence) = slice-vals binary-vals) _ #0)))) diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index 50b1fcc71..c6dc407eb 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -15,7 +15,7 @@ [data ["." maybe] [number - ["." nat]] + ["n" nat]] [collection ["." list]]] [math @@ -30,7 +30,7 @@ (def: bounded-size (Random Nat) (|> r.nat - (:: r.monad map (|>> (n/% 100) (n/+ 1))))) + (:: r.monad map (|>> (n.% 100) (n.+ 1))))) (def: #export test Test @@ -38,8 +38,8 @@ (do r.monad [size bounded-size] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (r.array size r.nat)) - ($monoid.spec (/.equivalence nat.equivalence) /.monoid (r.array size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (r.array size r.nat)) + ($monoid.spec (/.equivalence n.equivalence) /.monoid (r.array size r.nat)) ($functor.spec ..injection /.equivalence /.functor) ($fold.spec ..injection /.equivalence /.fold) @@ -48,16 +48,16 @@ original (r.array size r.nat)] ($_ _.and (_.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." (let [clone (/.clone original)] - (and (:: (/.equivalence nat.equivalence) = original clone) + (and (:: (/.equivalence n.equivalence) = original clone) (not (is? original clone))))) (_.test "Full-range manual copies should give the same result as cloning." (let [copy (: (Array Nat) (/.new size))] (exec (/.copy size 0 original 0 copy) - (and (:: (/.equivalence nat.equivalence) = original copy) + (and (:: (/.equivalence n.equivalence) = original copy) (not (is? original copy)))))) (_.test "Array folding should go over all values." (let [manual-copy (: (Array Nat) @@ -68,17 +68,17 @@ (inc idx))) 0 original) - (:: (/.equivalence nat.equivalence) = original manual-copy)))) + (:: (/.equivalence n.equivalence) = original manual-copy)))) (_.test "Transformations between (full) arrays and lists shouldn't cause lose or change any values." (|> original /.to-list /.from-list - (:: (/.equivalence nat.equivalence) = original))) + (:: (/.equivalence n.equivalence) = original))) )) (do r.monad [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))]] ($_ _.and (_.test "Shouldn't be able to find a value in an unoccupied cell." @@ -87,31 +87,31 @@ #.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)))))) )) (do r.monad [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?))))] ($_ _.and (_.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))))) diff --git a/stdlib/source/test/lux/data/collection/bits.lux b/stdlib/source/test/lux/data/collection/bits.lux index b0f4dec0e..77e346116 100644 --- a/stdlib/source/test/lux/data/collection/bits.lux +++ b/stdlib/source/test/lux/data/collection/bits.lux @@ -8,6 +8,9 @@ {[0 #test] [/ ["$." equivalence]]}] + [data + [number + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -16,13 +19,13 @@ (def: (size min max) (-> Nat Nat (Random Nat)) (|> r.nat - (:: r.monad map (|>> (n/% max) (n/max min))))) + (:: r.monad map (|>> (n.% max) (n.max min))))) (def: #export bits (Random Bits) (do r.monad [size (size 1 1,000) - idx (|> r.nat (:: @ map (n/% size)))] + idx (|> r.nat (:: @ map (n.% size)))] (wrap (|> /.empty (/.set idx))))) (def: #export test @@ -32,7 +35,7 @@ ($equivalence.spec /.equivalence ..bits) (do r.monad [size (size 1 1,000) - idx (|> r.nat (:: @ map (n/% size))) + idx (|> r.nat (:: @ map (n.% size))) sample bits] ($_ _.and (_.test "Can set individual bits." @@ -44,14 +47,14 @@ (and (|> /.empty (/.flip idx) (/.get idx)) (|> /.empty (/.flip idx) (/.flip idx) (/.get idx) not))) (_.test "Bits (only) grow when (and as much as) necessary." - (and (n/= 0 (/.capacity /.empty)) + (and (n.= 0 (/.capacity /.empty)) (|> /.empty (/.set idx) /.capacity - (n/- idx) - (predicate.unite (n/>= 0) - (n/< /.chunk-size))))) + (n.- idx) + (predicate.unite (n.>= 0) + (n.< /.chunk-size))))) (_.test "Bits (must) shrink when (and as much as) possible." (let [grown (/.flip idx /.empty)] - (and (n/> 0 (/.capacity grown)) + (and (n.> 0 (/.capacity grown)) (is? /.empty (/.flip idx grown))))) (_.test "Intersection can be detected when there are set bits in common." (and (not (/.intersects? /.empty @@ -68,12 +71,12 @@ (is? /.empty (/.and sample (/.not sample)))) (_.test "'or' with one's opposite fully saturates a bit-set." - (n/= (/.size (/.or sample (/.not sample))) + (n.= (/.size (/.or sample (/.not sample))) (/.capacity sample))) (_.test "'xor' with oneself yields the empty bit-set." (is? /.empty (/.xor sample sample))) (_.test "'xor' with one's opposite fully saturates a bit-set." - (n/= (/.size (/.xor sample (/.not sample))) + (n.= (/.size (/.xor sample (/.not sample))) (/.capacity sample))) (_.test "Double negation results in original bit-set." (:: /.equivalence = sample (/.not (/.not sample)))) diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 4512c0bec..432909629 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -12,7 +12,7 @@ [data ["." maybe] [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor)]]] [math @@ -22,30 +22,30 @@ (def: injection (Injection (/.Dictionary Nat)) - (|>> [0] list (/.from-list nat.hash))) + (|>> [0] list (/.from-list n.hash))) (def: #export test Test (<| (_.context (%.name (name-of /.Dictionary))) (do r.monad - [#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.dictionary nat.hash size r.nat capped-nat) + dict (r.dictionary n.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? nat.equivalence (/.values dict) val)))))] + test-val (|> r.nat (r.filter (function (_ val) (not (list.member? n.equivalence (/.values dict) val)))))] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) - (r.dictionary nat.hash size r.nat r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) + (r.dictionary n.hash size r.nat r.nat)) ($functor.spec ..injection /.equivalence /.functor) (_.test "Size function should correctly represent Dictionary size." - (n/= size (/.size dict))) + (n.= size (/.size dict))) (_.test "Dictionaries of size 0 should be considered empty." - (if (n/= 0 size) + (if (n.= 0 size) (/.empty? dict) (not (/.empty? dict)))) (_.test "The functions 'entries', 'keys' and 'values' should be synchronized." - (:: (list.equivalence (eq.product nat.equivalence nat.equivalence)) = + (:: (list.equivalence (eq.product n.equivalence n.equivalence)) = (/.entries dict) (list.zip2 (/.keys dict) (/.values dict)))) @@ -63,18 +63,18 @@ _ #1)) (_.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) _ #1)) (_.test "Should be able to try-put and then get a value." (case (/.get non-key (/.try-put non-key test-val dict)) - (#.Some v) (n/= test-val v) + (#.Some v) (n.= test-val v) _ #1)) (_.test "Shouldn't be able to try-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 (/.try-put first-key test-val dict)) - (#.Some v) (not (n/= test-val v)) + (#.Some v) (not (n.= test-val v)) _ #1)))) (_.test "Removing a key should make it's value inaccessible." (let [base (/.put non-key test-val dict)] @@ -85,45 +85,45 @@ updt (/.update non-key inc base)] (case [(/.get non-key base) (/.get non-key updt)] [(#.Some x) (#.Some y)] - (n/= (inc x) y) + (n.= (inc x) y) _ #0))) (_.test "Additions and removals to a Dictionary should affect its size." (let [plus (/.put non-key test-val dict) base (/.remove non-key plus)] - (and (n/= (inc (/.size dict)) (/.size plus)) - (n/= (dec (/.size plus)) (/.size base))))) + (and (n.= (inc (/.size dict)) (/.size plus)) + (n.= (dec (/.size plus)) (/.size base))))) (_.test "A Dictionary should equal itself & going to<->from lists shouldn't change that." - (let [(^open ".") (/.equivalence nat.equivalence)] + (let [(^open ".") (/.equivalence n.equivalence)] (and (= dict dict) - (|> dict /.entries (/.from-list nat.hash) (= dict))))) + (|> dict /.entries (/.from-list n.hash) (= dict))))) (_.test "Merging a Dictionary to itself changes nothing." - (let [(^open ".") (/.equivalence nat.equivalence)] + (let [(^open ".") (/.equivalence n.equivalence)] (= dict (/.merge dict dict)))) (_.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 (inc v)])) - (/.from-list nat.hash)) - (^open ".") (/.equivalence nat.equivalence)] + (/.from-list n.hash)) + (^open ".") (/.equivalence n.equivalence)] (= 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/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 28119cd93..19b124c40 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -12,7 +12,7 @@ [data ["." product] [number - ["." nat]] + ["n" nat]] [collection ["." set] ["." list ("#@." functor)]]] @@ -41,31 +41,31 @@ Test (<| (_.context (%.name (name-of /.Dictionary))) (do r.monad - [size (|> r.nat (:: @ map (n/% 100))) - keys (r.set nat.hash size r.nat) - values (r.set nat.hash size r.nat) + [size (|> r.nat (:: @ map (n.% 100))) + keys (r.set n.hash size r.nat) + values (r.set n.hash size r.nat) extra-key (|> r.nat (r.filter (|>> (set.member? keys) not))) extra-value r.nat #let [pairs (list.zip2 (set.to-list keys) (set.to-list values)) - sample (/.from-list nat.order pairs) + sample (/.from-list n.order pairs) sorted-pairs (list.sort (function (_ [left _] [right _]) - (n/< left right)) + (n.< left right)) pairs) sorted-values (list@map product.right sorted-pairs) - (^open "/@.") (/.equivalence nat.equivalence)]] + (^open "/@.") (/.equivalence n.equivalence)]] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (..dictionary nat.order r.nat r.nat size)) + ($equivalence.spec (/.equivalence n.equivalence) (..dictionary n.order r.nat r.nat size)) (_.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)] [#.None #.None] #1 [(#.Some reference) (#.Some sample)] - (n/= reference sample) + (n.= reference sample) _ #0)) @@ -75,19 +75,19 @@ #1 [(#.Some reference) (#.Some sample)] - (n/= reference sample) + (n.= reference sample) _ #0)) (_.test "Converting dictionaries to/from lists cannot change their values." (|> sample - /.entries (/.from-list nat.order) + /.entries (/.from-list n.order) (/@= sample))) (_.test "Order is preserved." (let [(^open "list@.") (list.equivalence (: (Equivalence [Nat Nat]) (function (_ [kr vr] [ks vs]) - (and (n/= kr ks) - (n/= vr vs)))))] + (and (n.= kr ks) + (n.= vr vs)))))] (list@= (/.entries sample) sorted-pairs))) (_.test "Every key in a dictionary must be identifiable." @@ -102,7 +102,7 @@ (case [(/.get extra-key sample') (/.get extra-key sample'')] [(#.Some found) #.None] - (n/= extra-value found) + (n.= extra-value found) _ #0))) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 77d473fd6..954e3f15d 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -20,7 +20,7 @@ ["." product] ["." maybe] [number - ["." nat] + ["n" nat] ["." int]]] [math ["r" random]]] @@ -30,15 +30,15 @@ (def: bounded-size (r.Random Nat) (|> r.nat - (:: r.monad map (|>> (n/% 100) (n/+ 10))))) + (:: r.monad map (|>> (n.% 100) (n.+ 10))))) (def: signatures Test (do r.monad [size bounded-size] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (r.list size r.nat)) - ($monoid.spec (/.equivalence nat.equivalence) /.monoid (r.list size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (r.list size r.nat)) + ($monoid.spec (/.equivalence n.equivalence) /.monoid (r.list size r.nat)) ($fold.spec /@wrap /.equivalence /.fold) ($functor.spec /@wrap /.equivalence /.functor) ($apply.spec /@wrap /.equivalence /.apply) @@ -49,14 +49,14 @@ subject r.nat] (let [lift (/.lift io.monad) (^open "io@.") io.monad - expected (n/+ parameter subject)] + expected (n.+ parameter subject)] (_.test "Can add list functionality to any monad." (|> (io.run (do (/.with io.monad) [a (lift (io@wrap parameter)) b (wrap subject)] - (wrap (n/+ a b)))) + (wrap (n.+ a b)))) (case> (^ (list actual)) - (n/= expected actual) + (n.= expected actual) _ false))))) @@ -67,10 +67,10 @@ (<| (_.context (%.name (name-of .List))) (do r.monad [size bounded-size - #let [(^open "/@.") (/.equivalence nat.equivalence) + #let [(^open "/@.") (/.equivalence n.equivalence) (^open "/@.") /.functor (^open "/@.") /.monoid] - 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) @@ -79,31 +79,31 @@ ..signatures (_.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." (/@= sample (/.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 (bit.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 (bit.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? (bit.complement n/even?) sample)) - (/.empty? (/.filter (bit.complement n/even?) sample))) - (/.any? (bit.complement n/even?) sample))) + (if (/.every? n.even? sample) + (and (not (/.any? (bit.complement n.even?) sample)) + (/.empty? (/.filter (bit.complement n.even?) sample))) + (/.any? (bit.complement n.even?) sample))) (_.test "Any element of the list can be considered its member." (let [elem (maybe.assume (/.nth idx sample))] - (/.member? nat.equivalence sample elem))) + (/.member? n.equivalence sample elem))) (_.test "Appending the head and the tail should yield the original list." (let [head (maybe.assume (/.head sample)) tail (maybe.assume (/.tail sample))] @@ -116,7 +116,7 @@ (/@compose inits (list last))))) (_.test "Splitting a list into chunks and re-appending them should yield the original list." (let [[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 @@ -125,21 +125,21 @@ (/@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)))) (_.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 [zipped (/.zip2 sample other-sample) num-zipper (/.size zipped)] @@ -147,32 +147,32 @@ (|> zipped (/@map product.right) (/@= (/.take num-zipper other-sample)))))) (_.test "You can generate indices for any size, and they will be in ascending order." (let [indices (/.indices size)] - (and (n/= size (/.size indices)) + (and (n.= size (/.size indices)) (/@= indices - (/.sort n/< indices)) - (/.every? (n/= (dec size)) - (/.zip2-with n/+ + (/.sort n.< indices)) + (/.every? (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 [sample+ (/.interpose separator sample)] - (and (n/= (|> size (n/* 2) dec) + (and (n.= (|> size (n.* 2) dec) (/.size sample+)) - (|> sample+ /.as-pairs (/@map product.right) (/.every? (n/= separator)))))) + (|> sample+ /.as-pairs (/@map product.right) (/.every? (n.= separator)))))) (_.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? (bit.complement n/even?) sample))) + (and (n.even? found) + (/.any? n.even? sample) + (not (/.every? (bit.complement n.even?) sample))) #.None - (and (not (/.any? n/even? sample)) - (/.every? (bit.complement n/even?) sample)))) + (and (not (/.any? n.even? sample)) + (/.every? (bit.complement n.even?) sample)))) (_.test "You can iteratively construct a list, generating values until you're done." (/@= (/.n/range 0 (dec size)) - (/.iterate (function (_ n) (if (n/< size n) (#.Some (inc n)) #.None)) + (/.iterate (function (_ n) (if (n.< size n) (#.Some (inc n)) #.None)) 0))) (_.test "Can enumerate all elements in a list." (let [enum-sample (/.enumerate sample)] @@ -181,8 +181,8 @@ (/@= sample (/@map product.right enum-sample))))) (do r.monad - [from (|> r.nat (:: @ map (n/% 10))) - to (|> r.nat (:: @ map (n/% 10)))] + [from (|> r.nat (:: @ map (n.% 10))) + to (|> r.nat (:: @ map (n.% 10)))] (_.test "Ranges can be constructed forward and backwards." (and (/@= (/.n/range from to) (/.reverse (/.n/range to from))) diff --git a/stdlib/source/test/lux/data/collection/queue.lux b/stdlib/source/test/lux/data/collection/queue.lux index f9a32c0c8..64e9c5e56 100644 --- a/stdlib/source/test/lux/data/collection/queue.lux +++ b/stdlib/source/test/lux/data/collection/queue.lux @@ -10,7 +10,7 @@ ["$." functor (#+ Injection)]]}] [data [number - ["." nat]]] + ["n" nat]]] [math ["r" random]]] {1 @@ -24,25 +24,25 @@ Test (<| (_.context (%.name (name-of /.Queue))) (do r.monad - [size (:: @ map (n/% 100) r.nat) + [size (:: @ map (n.% 100) r.nat) sample (r.queue size r.nat) non-member (|> r.nat - (r.filter (|>> (/.member? nat.equivalence sample) not)))] + (r.filter (|>> (/.member? n.equivalence sample) not)))] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (r.queue size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (r.queue size r.nat)) ($functor.spec ..injection /.equivalence /.functor) (_.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/= (inc size) (/.size (/.push non-member sample))) + (and (n.= (inc size) (/.size (/.push non-member sample))) (or (/.empty? sample) - (n/= (dec size) (/.size (/.pop sample)))) - (n/= size (/.size (/.pop (/.push non-member sample)))))) + (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 "/;.") (/.equivalence nat.equivalence)] + (let [(^open "/;.") (/.equivalence n.equivalence)] (|> sample /.to-list /.from-list (/;= sample)))) @@ -51,14 +51,14 @@ #.None (/.empty? sample) (#.Some _) #1)) (_.test "I can query whether an element belongs to a queue." - (and (not (/.member? nat.equivalence sample non-member)) - (/.member? nat.equivalence (/.push non-member sample) + (and (not (/.member? n.equivalence sample non-member)) + (/.member? n.equivalence (/.push non-member sample) non-member) (case (/.peek sample) #.None (/.empty? sample) (#.Some first) - (and (/.member? nat.equivalence sample first) - (not (/.member? nat.equivalence (/.pop sample) first)))))) + (and (/.member? n.equivalence sample first) + (not (/.member? n.equivalence (/.pop sample) first)))))) )))) diff --git a/stdlib/source/test/lux/data/collection/queue/priority.lux b/stdlib/source/test/lux/data/collection/queue/priority.lux index 9464819a3..78e4bc2b8 100644 --- a/stdlib/source/test/lux/data/collection/queue/priority.lux +++ b/stdlib/source/test/lux/data/collection/queue/priority.lux @@ -7,7 +7,7 @@ [data ["." maybe] [number - ["." nat]]] + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -28,29 +28,29 @@ Test (<| (_.context (%.name (name-of /.Queue))) (do r.monad - [size (|> r.nat (:: @ map (n/% 100))) + [size (|> r.nat (:: @ map (n.% 100))) sample (..queue size) non-member-priority r.nat - non-member (|> r.nat (r.filter (|>> (/.member? nat.equivalence sample) not)))] + non-member (|> r.nat (r.filter (|>> (/.member? n.equivalence sample) not)))] ($_ _.and (_.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/= (inc size) + (and (n.= (inc size) (/.size (/.push non-member-priority non-member sample))) - (or (n/= 0 (/.size sample)) - (n/= (dec size) + (or (n.= 0 (/.size sample)) + (n.= (dec size) (/.size (/.pop sample)))))) (_.test "I can query whether an element belongs to a queue." - (and (and (not (/.member? nat.equivalence sample non-member)) - (/.member? nat.equivalence + (and (and (not (/.member? n.equivalence sample non-member)) + (/.member? n.equivalence (/.push non-member-priority non-member sample) non-member)) - (or (n/= 0 (/.size sample)) - (and (/.member? nat.equivalence + (or (n.= 0 (/.size sample)) + (and (/.member? n.equivalence sample (maybe.assume (/.peek sample))) - (not (/.member? nat.equivalence + (not (/.member? n.equivalence (/.pop sample) (maybe.assume (/.peek sample)))))))) )))) diff --git a/stdlib/source/test/lux/data/collection/row.lux b/stdlib/source/test/lux/data/collection/row.lux index 7afbafd59..80917c7eb 100644 --- a/stdlib/source/test/lux/data/collection/row.lux +++ b/stdlib/source/test/lux/data/collection/row.lux @@ -15,7 +15,7 @@ [data ["." maybe] [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." fold)]]] [math @@ -27,32 +27,32 @@ Test (<| (_.context (%.name (name-of /._))) (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10))))] + [size (|> r.nat (:: @ map (|>> (n.% 100) (n.max 10))))] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (r.row size r.nat)) - ($monoid.spec (/.equivalence nat.equivalence) /.monoid (r.row size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (r.row size r.nat)) + ($monoid.spec (/.equivalence n.equivalence) /.monoid (r.row size r.nat)) ($fold.spec /@wrap /.equivalence /.fold) ($functor.spec /@wrap /.equivalence /.functor) ($apply.spec /@wrap /.equivalence /.apply) ($monad.spec /@wrap /.equivalence /.monad) (do @ - [idx (|> r.nat (:: @ map (n/% size))) + [idx (|> r.nat (:: @ map (n.% size))) sample (r.row size r.nat) other-sample (r.row size r.nat) - non-member (|> r.nat (r.filter (|>> (/.member? nat.equivalence sample) not))) - #let [(^open "/@.") (/.equivalence nat.equivalence)]] + non-member (|> r.nat (r.filter (|>> (/.member? n.equivalence sample) not))) + #let [(^open "/@.") (/.equivalence n.equivalence)]] ($_ _.and (_.test (format (%.name (name-of /.size)) " " (%.name (name-of /.empty?))) (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 (format (%.name (name-of /.add)) " " (%.name (name-of /.pop))) - (and (n/= (inc size) (/.size (/.add non-member sample))) - (n/= (dec size) (/.size (/.pop sample))))) + (and (n.= (inc size) (/.size (/.add non-member sample))) + (n.= (dec size) (/.size (/.pop sample))))) (_.test (format (%.name (name-of /.put)) " " (%.name (name-of /.nth))) (|> sample @@ -64,13 +64,13 @@ (|> sample (/.put idx non-member) (/.update idx inc) (/.nth idx) maybe.assume - (n/= (inc non-member)))) + (n.= (inc non-member)))) (_.test (format (%.name (name-of /.to-list)) " " (%.name (name-of /.from-list))) (|> sample /.to-list /.from-list (/@= sample))) (_.test (%.name (name-of /.member?)) - (and (not (/.member? nat.equivalence sample non-member)) - (/.member? nat.equivalence (/.add non-member sample) non-member))) + (and (not (/.member? n.equivalence sample non-member)) + (/.member? n.equivalence (/.add non-member sample) non-member))) (_.test (%.name (name-of /.reverse)) (and (not (/@= sample (/.reverse sample))) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 2beb3599f..6e4f59930 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -9,7 +9,7 @@ [data ["." maybe] [number - ["." nat ("#@." decimal)]] + ["n" nat ("#@." decimal)]] ["." text ("#@." monoid)] [collection ["." list]]] @@ -22,80 +22,80 @@ Test (<| (_.context (%.name (name-of /.Sequence))) (do r.monad - [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))) - #let [(^open "list@.") (list.equivalence nat.equivalence) + cycle-sample-idx (|> r.nat (:: @ map (n.% 1000))) + #let [(^open "list@.") (list.equivalence n.equivalence) sample0 (/.iterate inc 0) sample1 (/.iterate inc offset)]] ($_ _.and (_.test "Can move along a sequence and take slices off it." (and (and (list@= (list.n/range 0 (dec size)) (/.take size sample0)) - (list@= (list.n/range offset (dec (n/+ offset size))) + (list@= (list.n/range offset (dec (n.+ offset size))) (/.take size (/.drop offset sample0))) (let [[drops takes] (/.split size sample0)] (and (list@= (list.n/range 0 (dec size)) drops) - (list@= (list.n/range size (dec (n/* 2 size))) + (list@= (list.n/range size (dec (n.* 2 size))) (/.take size takes))))) (and (list@= (list.n/range 0 (dec size)) - (/.take-while (n/< size) sample0)) - (list@= (list.n/range offset (dec (n/+ offset size))) - (/.take-while (n/< (n/+ offset size)) - (/.drop-while (n/< offset) sample0))) - (let [[drops takes] (/.split-while (n/< size) sample0)] + (/.take-while (n.< size) sample0)) + (list@= (list.n/range offset (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 (dec size)) drops) - (list@= (list.n/range size (dec (n/* 2 size))) - (/.take-while (n/< (n/* 2 size)) takes))))) + (list@= (list.n/range size (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 sequence." - (and (n/= offset (/.head sample1)) - (list@= (list.n/range (inc offset) (n/+ offset size)) + (and (n.= offset (/.head sample1)) + (list@= (list.n/range (inc offset) (n.+ offset size)) (/.take size (/.tail sample1))))) (_.test "Can filter sequences." - (and (n/= (n/* 2 offset) + (and (n.= (n.* 2 offset) (/.nth offset - (/.filter n/even? sample0))) - (let [[evens odds] (/.partition n/even? (/.iterate inc 0))] - (and (n/= (n/* 2 offset) + (/.filter n.even? sample0))) + (let [[evens odds] (/.partition n.even? (/.iterate inc 0))] + (and (n.= (n.* 2 offset) (/.nth offset evens)) - (n/= (inc (n/* 2 offset)) + (n.= (inc (n.* 2 offset)) (/.nth offset odds)))))) (_.test "Functor goes over 'all' elements in a sequence." (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) (/.take size back-again))))) (_.test "CoMonad produces a value for every element in a sequence." (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.equivalence text.equivalence)] (list@= (/.take size - (/@map nat@encode (/.iterate inc offset))) + (/@map n@encode (/.iterate inc offset))) (/.take size - (/.unfold (function (_ n) [(inc n) (nat@encode n)]) + (/.unfold (function (_ n) [(inc n) (n@encode n)]) offset))))) (_.test "Can cycle over the same elements as an infinite sequence." (|> (/.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/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux index 6e668af56..d742352ec 100644 --- a/stdlib/source/test/lux/data/collection/set.lux +++ b/stdlib/source/test/lux/data/collection/set.lux @@ -10,7 +10,7 @@ ["$." monoid]]}] [data [number - ["." nat]] + ["n" nat]] [collection ["." list]]] [math @@ -21,7 +21,7 @@ (def: gen-nat (r.Random Nat) (|> r.nat - (:: r.monad map (n/% 100)))) + (:: r.monad map (n.% 100)))) (def: #export test Test @@ -29,24 +29,24 @@ (do r.monad [size gen-nat] ($_ _.and - ($equivalence.spec /.equivalence (r.set nat.hash size r.nat)) - ($monoid.spec /.equivalence (/.monoid nat.hash) (r.set nat.hash size r.nat)) + ($equivalence.spec /.equivalence (r.set n.hash size r.nat)) + ($monoid.spec /.equivalence (/.monoid n.hash) (r.set n.hash size r.nat)) (do r.monad [sizeL gen-nat sizeR gen-nat - setL (r.set nat.hash sizeL gen-nat) - setR (r.set nat.hash sizeR gen-nat) + setL (r.set n.hash sizeL gen-nat) + setR (r.set n.hash sizeR gen-nat) non-member (|> gen-nat (r.filter (|>> (/.member? setL) not))) #let [(^open "/@.") /.equivalence]] ($_ _.and (_.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 - /.to-list (/.from-list nat.hash) + /.to-list (/.from-list n.hash) (/@= setL))) (_.test "Every set is a sub-set of the union of itself with another." (let [setLR (/.union setL setR)] @@ -58,10 +58,10 @@ (/.super? setLR setR)))) (_.test "Union with the empty set leaves a set unchanged." (/@= setL - (/.union (/.new nat.hash) + (/.union (/.new n.hash) setL))) (_.test "Intersection with the empty set results in the empty set." - (let [empty-set (/.new nat.hash)] + (let [empty-set (/.new n.hash)] (/@= empty-set (/.intersection empty-set setL)))) (_.test "After substracting a set A from another B, no member of A can be a member of B." diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux index fa7c00798..30ff8f6db 100644 --- a/stdlib/source/test/lux/data/collection/set/ordered.lux +++ b/stdlib/source/test/lux/data/collection/set/ordered.lux @@ -10,7 +10,7 @@ ["$." equivalence]]}] [data [number - ["." nat]] + ["n" nat]] [collection ["." list]]] [math @@ -22,7 +22,7 @@ (def: gen-nat (r.Random Nat) (|> r.nat - (:: r.monad map (n/% 100)))) + (:: r.monad map (n.% 100)))) (def: #export (set &order gen-value size) (All [a] (-> (Order a) (Random a) Nat (Random (Set a)))) @@ -44,29 +44,29 @@ (do r.monad [size gen-nat] ($_ _.and - ($equivalence.spec /.equivalence (..set nat.order r.nat size)) + ($equivalence.spec /.equivalence (..set n.order r.nat size)) )) (do r.monad [sizeL gen-nat sizeR gen-nat - listL (|> (r.set nat.hash sizeL gen-nat) (:: @ map //.to-list)) - listR (|> (r.set nat.hash sizeR gen-nat) (:: @ map //.to-list)) + listL (|> (r.set n.hash sizeL gen-nat) (:: @ map //.to-list)) + listR (|> (r.set n.hash sizeR gen-nat) (:: @ map //.to-list)) #let [(^open "/@.") /.equivalence - setL (/.from-list nat.order listL) - setR (/.from-list nat.order listR) - sortedL (list.sort n/< listL) + setL (/.from-list n.order listL) + setR (/.from-list n.order listR) + sortedL (list.sort n.< listL) minL (list.head sortedL) maxL (list.last sortedL)]] ($_ _.and (_.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] [#.None #.None] true [(#.Some reference) (#.Some sample)] - (n/= reference sample) + (n.= reference sample) _ false)) @@ -76,19 +76,19 @@ true [(#.Some reference) (#.Some sample)] - (n/= reference sample) + (n.= reference sample) _ false)) (_.test "Converting sets to/from lists can't change their values." (|> setL - /.to-list (/.from-list nat.order) + /.to-list (/.from-list n.order) (/@= setL))) (_.test "Order is preserved." (let [listL (/.to-list setL) - (^open "list@.") (list.equivalence nat.equivalence)] + (^open "list@.") (list.equivalence n.equivalence)] (list@= 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)] (and (/.sub? setLR setL) @@ -99,10 +99,10 @@ (/.super? setLR setR)))) (_.test "Union with the empty set leaves a set unchanged." (/@= setL - (/.union (/.new nat.order) + (/.union (/.new n.order) setL))) (_.test "Intersection with the empty set results in the empty set." - (let [empty-set (/.new nat.order)] + (let [empty-set (/.new n.order)] (/@= empty-set (/.intersection empty-set setL)))) (_.test "After substracting a set A from another B, no member of A can be a member of B." diff --git a/stdlib/source/test/lux/data/collection/stack.lux b/stdlib/source/test/lux/data/collection/stack.lux index 74ddf6c86..a71b128a8 100644 --- a/stdlib/source/test/lux/data/collection/stack.lux +++ b/stdlib/source/test/lux/data/collection/stack.lux @@ -11,7 +11,7 @@ [data ["." maybe] [number - ["." nat]]] + ["n" nat]]] [math ["r" random]]] {1 @@ -24,7 +24,7 @@ (def: gen-nat (r.Random Nat) (|> r.nat - (:: r.monad map (n/% 100)))) + (:: r.monad map (n.% 100)))) (def: #export test Test @@ -34,11 +34,11 @@ sample (r.stack size gen-nat) new-top gen-nat] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (r.stack size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (r.stack size r.nat)) ($functor.spec ..injection /.equivalence /.functor) (_.test (%.name (name-of /.size)) - (n/= size (/.size sample))) + (n.= size (/.size sample))) (_.test (%.name (name-of /.peek)) (case (/.peek sample) #.None (/.empty? sample) @@ -53,7 +53,7 @@ false) expected (case (/.pop sample) (#.Some sample') - (and (n/= (dec expected) (/.size sample')) + (and (n.= (dec expected) (/.size sample')) (not (/.empty? sample))) #.None @@ -61,7 +61,7 @@ (_.test (%.name (name-of /.push)) (and (is? sample (|> sample (/.push new-top) /.pop maybe.assume)) - (n/= (inc (/.size sample)) + (n.= (inc (/.size sample)) (/.size (/.push new-top sample))) (|> (/.push new-top sample) /.peek maybe.assume (is? new-top)))) diff --git a/stdlib/source/test/lux/data/collection/tree.lux b/stdlib/source/test/lux/data/collection/tree.lux index 1506494c8..f42bc4f4d 100644 --- a/stdlib/source/test/lux/data/collection/tree.lux +++ b/stdlib/source/test/lux/data/collection/tree.lux @@ -11,7 +11,7 @@ ["$." functor]]}] [data [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor fold)]]] [math @@ -39,8 +39,8 @@ (do r.monad [value gen-value #let [size (dec size)] - left (tree (n// 2 size) gen-value) - right (tree (n/+ (n/% 2 size) (n// 2 size)) + left (tree (n./ 2 size) gen-value) + right (tree (n.+ (n.% 2 size) (n./ 2 size)) gen-value)] (wrap (/.branch value (list left right)))) ))) @@ -49,15 +49,15 @@ Test (<| (_.context (%.name (name-of /.Tree))) (do r.monad - [size (:: @ map (|>> (n/% 100) (n/+ 1)) r.nat)] + [size (:: @ map (|>> (n.% 100) (n.+ 1)) r.nat)] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (..tree size r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (..tree size r.nat)) ($fold.spec /.leaf /.equivalence /.fold) ($functor.spec /.leaf /.equivalence /.functor) (do @ [sample (..tree size r.nat)] (_.test "Can flatten a tree to get all the nodes as a flat tree." - (n/= size + (n.= size (list.size (/.flatten sample))))) )))) diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 71d5a71cd..9ed7da62e 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -9,7 +9,7 @@ ["." maybe] ["." text] [number - ["." nat]] + ["n" nat]] [collection ["." list]]] [math @@ -24,14 +24,14 @@ Test (<| (_.context (%.name (name-of /.Zipper))) (do r.monad - [size (:: @ map (|>> (n/% 90) (n/+ 10)) r.nat) + [size (:: @ map (|>> (n.% 90) (n.+ 10)) r.nat) sample (//.tree size r.nat) mid-val r.nat new-val r.nat pre-val r.nat post-val r.nat - #let [(^open "tree@.") (tree.equivalence nat.equivalence) - (^open "list@.") (list.equivalence nat.equivalence)]] + #let [(^open "tree@.") (tree.equivalence n.equivalence) + (^open "list@.") (list.equivalence n.equivalence)]] ($_ _.and (_.test "Trees can be converted to/from zippers." (|> sample @@ -86,14 +86,14 @@ (case> (#.Some _) false #.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." (let [root (/.zip sample)] (list@= (tree.flatten sample) (loop [zipper (/.start root)] (let [zipper' (/.next zipper)] (#.Cons (/.value zipper) - (if (:: (/.equivalence nat.equivalence) = root zipper') + (if (:: (/.equivalence n.equivalence) = root zipper') (list) (recur zipper')))))))) (_.test "Backwards zipper traversal yield reverse tree flatten." @@ -101,7 +101,7 @@ (list@= (list.reverse (tree.flatten sample)) (loop [zipper (/.end root)] (#.Cons (/.value zipper) - (if (:: (/.equivalence nat.equivalence) = root zipper) + (if (:: (/.equivalence n.equivalence) = root zipper) (list) (recur (/.prev zipper)))))))) (_.test "Can remove nodes (except start nodes)." diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux index 4ccd4e337..6f16a0088 100644 --- a/stdlib/source/test/lux/data/format/json.lux +++ b/stdlib/source/test/lux/data/format/json.lux @@ -18,6 +18,7 @@ ["." maybe] ["." text] [number + ["n" nat] ["." frac]] [collection [row (#+ row)] @@ -50,7 +51,7 @@ (Random JSON) (r.rec (function (_ recur) (do r.monad - [size (:: @ map (n/% 2) r.nat)] + [size (:: @ map (n.% 2) r.nat)] ($_ r.or (:: @ wrap []) r.bit diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux index a7236ede6..a3dc6b0e0 100644 --- a/stdlib/source/test/lux/data/format/xml.lux +++ b/stdlib/source/test/lux/data/format/xml.lux @@ -17,6 +17,8 @@ ["." name] ["." maybe] ["." text ("#@." equivalence)] + [number + ["n" nat]] [collection ["." dictionary] ["." list ("#@." functor)]]] @@ -34,12 +36,12 @@ (def: char (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 (Random Nat)) - (let [constraint (|>> (n/% top) (n/max bottom))] + (let [constraint (|>> (n.% top) (n.max bottom))] (r@map constraint r.nat))) (def: (text bottom top) @@ -73,7 +75,7 @@ (do r.monad [text (..text 1 10) - num-children (|> r.nat (:: @ map (n/% 5))) + num-children (|> r.nat (:: @ map (n.% 5))) children (r.list num-children (..text 1 10)) tag xml-identifier^ attr xml-identifier^ diff --git a/stdlib/source/test/lux/data/lazy.lux b/stdlib/source/test/lux/data/lazy.lux index cfc096326..a52326bef 100644 --- a/stdlib/source/test/lux/data/lazy.lux +++ b/stdlib/source/test/lux/data/lazy.lux @@ -12,7 +12,7 @@ [data ["%" text/format (#+ format)] [number - ["." nat]]] + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -37,16 +37,16 @@ (do r.monad [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)]] ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (..lazy r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (..lazy r.nat)) ($functor.spec ..injection ..comparison /.functor) ($apply.spec ..injection ..comparison /.apply) ($monad.spec ..injection ..comparison /.monad) (_.test "Freezing does not alter the expected value." - (n/= expected + (n.= expected (/.thaw lazy))) (_.test "Lazy values only evaluate once." (and (not (is? expected diff --git a/stdlib/source/test/lux/data/maybe.lux b/stdlib/source/test/lux/data/maybe.lux index 60d154a7a..18d2f4248 100644 --- a/stdlib/source/test/lux/data/maybe.lux +++ b/stdlib/source/test/lux/data/maybe.lux @@ -16,7 +16,7 @@ ["." text ["%" format (#+ format)]] [number - ["." nat]]] + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -30,7 +30,7 @@ Test (<| (_.context (%.name (name-of .Maybe))) ($_ _.and - ($equivalence.spec (/.equivalence nat.equivalence) (..maybe r.nat)) + ($equivalence.spec (/.equivalence n.equivalence) (..maybe r.nat)) ($functor.spec /@wrap /.equivalence /.functor) ($apply.spec /@wrap /.equivalence /.apply) ($monad.spec /@wrap /.equivalence /.monad) @@ -38,15 +38,15 @@ (do r.monad [left r.nat right r.nat - #let [expected (n/+ left right)]] + #let [expected (n.+ left right)]] (let [lift (/.lift io.monad)] (_.test "Can add maybe functionality to any monad." (|> (io.run (do (/.with io.monad) [a (lift (io@wrap left)) b (wrap right)] - (wrap (n/+ a b)))) + (wrap (n.+ a b)))) (case> (#.Some actual) - (n/= expected actual) + (n.= expected actual) _ false))))) diff --git a/stdlib/source/test/lux/data/name.lux b/stdlib/source/test/lux/data/name.lux index 63acad50b..6190ab19a 100644 --- a/stdlib/source/test/lux/data/name.lux +++ b/stdlib/source/test/lux/data/name.lux @@ -10,6 +10,8 @@ [control pipe] [data + [number + ["n" nat]] ["." text ("#@." equivalence) ["%" format (#+ format)]]] [math @@ -31,12 +33,12 @@ (<| (_.context (%.name (name-of .Name))) (do r.monad [## First Name - sizeM1 (|> r.nat (:: @ map (n/% 100))) - sizeS1 (|> r.nat (:: @ map (|>> (n/% 100) (n/max 1)))) + sizeM1 (|> r.nat (:: @ map (n.% 100))) + sizeS1 (|> r.nat (:: @ map (|>> (n.% 100) (n.max 1)))) (^@ name1 [module1 short1]) (..name sizeM1 sizeS1) ## Second Name - sizeM2 (|> r.nat (:: @ map (n/% 100))) - sizeS2 (|> r.nat (:: @ map (|>> (n/% 100) (n/max 1)))) + sizeM2 (|> r.nat (:: @ map (n.% 100))) + sizeS2 (|> r.nat (:: @ map (|>> (n.% 100) (n.max 1)))) (^@ name2 [module2 short2]) (..name sizeM2 sizeS2)] ($_ _.and ($equivalence.spec /.equivalence (..name sizeM1 sizeS1)) diff --git a/stdlib/source/test/lux/data/number/complex.lux b/stdlib/source/test/lux/data/number/complex.lux index 1aa14e5be..5890ce0d4 100644 --- a/stdlib/source/test/lux/data/number/complex.lux +++ b/stdlib/source/test/lux/data/number/complex.lux @@ -11,6 +11,7 @@ ["$." codec]]}] [data [number + ["n" nat] ["." int] ["f" frac]] [collection @@ -34,7 +35,7 @@ (def: dimension (Random Frac) (do r.monad - [factor (|> r.nat (:: @ map (|>> (n/% 1000) (n/max 1)))) + [factor (|> r.nat (:: @ map (|>> (n.% 1000) (n.max 1)))) measure (|> r.safe-frac (r.filter (f.> +0.0)))] (wrap (f.* (|> factor .int int.frac) measure)))) @@ -184,7 +185,7 @@ Test (do r.monad [sample ..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 (/.roots degree) diff --git a/stdlib/source/test/lux/data/number/i64.lux b/stdlib/source/test/lux/data/number/i64.lux index fbfecf07a..838746854 100644 --- a/stdlib/source/test/lux/data/number/i64.lux +++ b/stdlib/source/test/lux/data/number/i64.lux @@ -16,7 +16,7 @@ ["r" random]]] {1 ["." / - ["." // #_ + ["/#" // #_ ["#." nat]]]}) (def: #export test @@ -24,21 +24,21 @@ (<| (_.context (name.module (name-of /._))) (do r.monad [pattern r.nat - idx (:: @ map (n/% /.width) r.nat)] + idx (:: @ map (//nat.% /.width) r.nat)] ($_ _.and ($equivalence.spec /.equivalence r.i64) ($monoid.spec //nat.equivalence /.disjunction r.nat) ($monoid.spec //nat.equivalence /.conjunction r.nat) (_.test "Clearing and settings bits should alter the count." - (and (n/= (dec (/.count (/.set idx pattern))) - (/.count (/.clear idx pattern))) + (and (//nat.= (dec (/.count (/.set idx pattern))) + (/.count (/.clear idx pattern))) (|> (/.count pattern) - (n/- (/.count (/.clear idx pattern))) - (n/<= 1)) + (//nat.- (/.count (/.clear idx pattern))) + (//nat.<= 1)) (|> (/.count (/.set idx pattern)) - (n/- (/.count pattern)) - (n/<= 1)))) + (//nat.- (/.count pattern)) + (//nat.<= 1)))) (_.test "Can query whether a bit is set." (and (or (and (/.set? idx pattern) (not (/.set? idx (/.clear idx pattern)))) @@ -50,38 +50,38 @@ (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) - (/.count (/.not pattern))))) + (//nat.= /.width + (//nat.+ (/.count pattern) + (/.count (/.not pattern))))) (_.test "Can do simple binary logic." - (and (n/= 0 - (/.and pattern - (/.not pattern))) - (n/= (/.not 0) - (/.or pattern - (/.not pattern))) - (n/= (/.not 0) - (/.xor pattern - (/.not pattern))) - (n/= 0 - (/.xor pattern - pattern)))) + (and (//nat.= 0 + (/.and pattern + (/.not pattern))) + (//nat.= (/.not 0) + (/.or pattern + (/.not pattern))) + (//nat.= (/.not 0) + (/.xor pattern + (/.not pattern))) + (//nat.= 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)) + (//nat.= pattern)) (|> pattern (/.rotate-right idx) (/.rotate-left idx) - (n/= pattern)))) + (//nat.= pattern)))) (_.test "Rotate as many spaces as the bit-pattern's width leaves the pattern unchanged." (and (|> pattern (/.rotate-left /.width) - (n/= pattern)) + (//nat.= pattern)) (|> pattern (/.rotate-right /.width) - (n/= pattern)))) + (//nat.= pattern)))) (_.test "Shift right respect the sign of ints." (let [value (.int pattern)] (if (i.< +0 value) diff --git a/stdlib/source/test/lux/data/number/nat.lux b/stdlib/source/test/lux/data/number/nat.lux index 9a7f5907c..2a96ef9d5 100644 --- a/stdlib/source/test/lux/data/number/nat.lux +++ b/stdlib/source/test/lux/data/number/nat.lux @@ -40,10 +40,10 @@ )) (_.test "Alternate notations." - (and (n/= (bin "11001001") + (and (/.= (bin "11001001") (bin "11,00,10,01")) - (n/= (oct "615243") + (/.= (oct "615243") (oct "615,243")) - (n/= (hex "deadBEEF") + (/.= (hex "deadBEEF") (hex "dead,BEEF")))) )))) diff --git a/stdlib/source/test/lux/data/number/ratio.lux b/stdlib/source/test/lux/data/number/ratio.lux index f2162681d..fa3d6a01e 100644 --- a/stdlib/source/test/lux/data/number/ratio.lux +++ b/stdlib/source/test/lux/data/number/ratio.lux @@ -10,6 +10,9 @@ ["$." order] ["$." monoid] ["$." codec]]}] + [data + [number + ["n" nat]]] [math ["r" random (#+ Random)]]] {1 @@ -17,13 +20,13 @@ (def: part (Random Nat) - (|> r.nat (:: r.monad map (|>> (n/% 1,000,000) (n/max 1))))) + (|> r.nat (:: r.monad map (|>> (n.% 1,000,000) (n.max 1))))) (def: #export ratio (Random Ratio) (do r.monad [numerator ..part - denominator (r.filter (|>> (n/= 0) not) ..part)] + denominator (r.filter (|>> (n.= 0) not) ..part)] (wrap (/.ratio numerator denominator)))) (def: #export test diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux index 29e02de04..b90206fe7 100644 --- a/stdlib/source/test/lux/data/sum.lux +++ b/stdlib/source/test/lux/data/sum.lux @@ -6,6 +6,8 @@ pipe] [data ["." text] + [number + ["n" nat]] [collection ["." list]]]] {1 @@ -30,10 +32,10 @@ (/.rights (: (List (| Text Text)) (list (0 "0") (1 "1") (0 "2")))))))) (_.test "Can apply a function to an Either value depending on the case." - (and (n/= 10 (/.either (function (_ _) 10) + (and (n.= 10 (/.either (function (_ _) 10) (function (_ _) 20) (: (| Text Text) (0 "")))) - (n/= 20 (/.either (function (_ _) 10) + (n.= 20 (/.either (function (_ _) 10) (function (_ _) 20) (: (| Text Text) (1 "")))))) )))) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index 8adabf715..b3cd2e735 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -11,6 +11,8 @@ [control pipe] [data + [number + ["n" nat]] [collection ["." list]]] [math @@ -21,7 +23,7 @@ (def: bounded-size (r.Random Nat) (|> r.nat - (:: r.monad map (|>> (n/% 20) (n/+ 1))))) + (:: r.monad map (|>> (n.% 20) (n.+ 1))))) (def: #export test Test @@ -31,17 +33,17 @@ ($order.spec /.order (r.ascii 2)) (do r.monad - [size (:: @ map (n/% 10) r.nat) + [size (:: @ map (n.% 10) r.nat) sample (r.unicode size)] ($_ _.and (_.test "Can get the size of text." - (n/= size (/.size sample))) + (n.= size (/.size sample))) (_.test "Text with size 0 is considered 'empty'." - (or (not (n/= 0 size)) + (or (not (n.= 0 size)) (/.empty? sample))))) (do r.monad [size bounded-size - idx (:: @ map (n/% size) r.nat) + idx (:: @ map (n.% size) r.nat) sample (r.unicode size)] (_.test "Character locations." (|> sample @@ -54,11 +56,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)) @@ -114,7 +116,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) @@ -125,7 +127,7 @@ (^open "/@.") /.equivalence]] ($_ _.and (_.test "Can split text multiple times 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/source/test/lux/host.jvm.lux b/stdlib/source/test/lux/host.jvm.lux index d1753e7a1..8ff26e2e9 100644 --- a/stdlib/source/test/lux/host.jvm.lux +++ b/stdlib/source/test/lux/host.jvm.lux @@ -6,6 +6,7 @@ [data ["." text ("#;." equivalence)] [number + ["n" nat] ["i" int]]] [math ["r" random]] @@ -121,12 +122,12 @@ (def: arrays Test (do r.monad - [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] ($_ _.and (_.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)] diff --git a/stdlib/source/test/lux/host.old.lux b/stdlib/source/test/lux/host.old.lux index 19e8ae9ba..9258aa5de 100644 --- a/stdlib/source/test/lux/host.old.lux +++ b/stdlib/source/test/lux/host.old.lux @@ -6,6 +6,7 @@ [data ["." text ("#;." equivalence)] [number + ["n" nat] ["i" int]]] [math ["r" random]] @@ -114,12 +115,12 @@ (def: arrays Test (do r.monad - [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] ($_ _.and (_.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)] diff --git a/stdlib/source/test/lux/macro/poly/equivalence.lux b/stdlib/source/test/lux/macro/poly/equivalence.lux index adf150aee..7b9d0b97c 100644 --- a/stdlib/source/test/lux/macro/poly/equivalence.lux +++ b/stdlib/source/test/lux/macro/poly/equivalence.lux @@ -11,6 +11,7 @@ ["." bit] ["." maybe] [number + ["n" nat] ["i" int]] ["." text] [collection @@ -49,7 +50,7 @@ (def: gen-record (Random Record) (do random.monad - [size (:: @ map (n/% 2) random.nat) + [size (:: @ map (n.% 2) random.nat) #let [gen-int (|> random.int (:: @ map (|>> i.abs (i.% +1,000,000))))]] ($_ random.and random.bit diff --git a/stdlib/source/test/lux/macro/poly/json.lux b/stdlib/source/test/lux/macro/poly/json.lux index 0921cce9e..8a72e0e2b 100644 --- a/stdlib/source/test/lux/macro/poly/json.lux +++ b/stdlib/source/test/lux/macro/poly/json.lux @@ -20,6 +20,7 @@ ["." maybe] ["." text] [number + ["n" nat] ["." frac]] [format [json (#+)]] @@ -89,7 +90,7 @@ (def: gen-record (Random Record) (do r.monad - [size (:: @ map (n/% 2) r.nat)] + [size (:: @ map (n.% 2) r.nat)] ($_ r.and r.bit r.frac diff --git a/stdlib/source/test/lux/math.lux b/stdlib/source/test/lux/math.lux index ffe990c50..17ed2086c 100644 --- a/stdlib/source/test/lux/math.lux +++ b/stdlib/source/test/lux/math.lux @@ -7,6 +7,7 @@ [data ["." bit ("#@." equivalence)] [number + ["n" nat] ["." int] ["f" frac]]]] {1 @@ -71,21 +72,21 @@ (|> sample /.exp /.log (within? +0.000000000000001 sample))))) (<| (_.context "Greatest-Common-Divisor and Least-Common-Multiple") (do r.monad - [#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] ($_ _.and (_.test "GCD" - (let [gcd (/.n/gcd x y)] - (and (n/= 0 (n/% gcd x)) - (n/= 0 (n/% gcd y)) - (n/>= 1 gcd)))) + (let [gcd (n.gcd x y)] + (and (n.= 0 (n.% gcd x)) + (n.= 0 (n.% gcd y)) + (n.>= 1 gcd)))) (_.test "LCM" - (let [lcm (/.n/lcm x y)] - (and (n/= 0 (n/% x lcm)) - (n/= 0 (n/% y lcm)) - (n/<= (n/* x y) lcm)))) + (let [lcm (n.lcm x y)] + (and (n.= 0 (n.% x lcm)) + (n.= 0 (n.% y lcm)) + (n.<= (n.* x y) lcm)))) ))) /infix.test diff --git a/stdlib/source/test/lux/math/infix.lux b/stdlib/source/test/lux/math/infix.lux index e2850f549..8085d5f98 100644 --- a/stdlib/source/test/lux/math/infix.lux +++ b/stdlib/source/test/lux/math/infix.lux @@ -7,6 +7,7 @@ [data ["." bit ("#@." equivalence)] [number + ["n" nat] ["f" frac]]]] {1 ["." / @@ -22,23 +23,23 @@ angle r.frac] ($_ _.and (_.test "Constant values don't change." - (n/= subject + (n.= subject (/.infix subject))) (_.test "Can call binary functions." - (n/= (//.n/gcd parameter subject) - (/.infix [subject //.n/gcd parameter]))) + (n.= (n.gcd parameter subject) + (/.infix [subject n.gcd parameter]))) (_.test "Can call unary functions." (f.= (//.sin angle) (/.infix [//.sin angle]))) (_.test "Can use regular syntax in the middle of infix code." - (n/= (//.n/gcd extra (n/* parameter subject)) - (/.infix [(n/* parameter subject) //.n/gcd extra]))) + (n.= (n.gcd extra (n.* parameter subject)) + (/.infix [(n.* parameter subject) n.gcd extra]))) (_.test "Can use non-numerical functions/macros as operators." - (bit@= (and (n/< parameter subject) (n/< extra parameter)) - (/.infix [[subject n/< parameter] and [parameter n/< extra]]))) + (bit@= (and (n.< parameter subject) (n.< extra parameter)) + (/.infix [[subject n.< parameter] and [parameter n.< extra]]))) (_.test "Can combine bit operations in special ways via special keywords." - (and (bit@= (and (n/< parameter subject) (n/< extra parameter)) - (/.infix [#and subject n/< parameter n/< extra])) - (bit@= (and (n/< parameter subject) (n/> extra parameter)) - (/.infix [#and subject n/< parameter n/> extra])))) + (and (bit@= (and (n.< parameter subject) (n.< extra parameter)) + (/.infix [#and subject n.< parameter n.< extra])) + (bit@= (and (n.< parameter subject) (n.> extra parameter)) + (/.infix [#and subject n.< parameter n.> extra])))) )))) diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux index 35dff4a03..e53028522 100644 --- a/stdlib/source/test/lux/math/logic/fuzzy.lux +++ b/stdlib/source/test/lux/math/logic/fuzzy.lux @@ -8,7 +8,7 @@ [data ["." bit ("#@." equivalence)] [number - ["." nat] + ["n" nat] ["r" rev]] [collection ["." list] @@ -142,12 +142,12 @@ (def: predicates-and-sets Test (do random.monad - [#let [set-10 (set.from-list nat.hash (list.n/range 0 10))] - sample (|> random.nat (:: @ map (n/% 20)))] + [#let [set-10 (set.from-list n.hash (list.n/range 0 10))] + sample (|> random.nat (:: @ map (n.% 20)))] ($_ _.and (_.test (%.name (name-of /.from-predicate)) - (bit@= (r.= //.true (/.membership sample (/.from-predicate n/even?))) - (n/even? sample))) + (bit@= (r.= //.true (/.membership sample (/.from-predicate n.even?))) + (n.even? sample))) (_.test (%.name (name-of /.from-set)) (bit@= (r.= //.true (/.membership sample (/.from-set set-10))) (set.member? set-10 sample))) diff --git a/stdlib/source/test/lux/time/duration.lux b/stdlib/source/test/lux/time/duration.lux index 9eea2e03b..fe196cb29 100644 --- a/stdlib/source/test/lux/time/duration.lux +++ b/stdlib/source/test/lux/time/duration.lux @@ -12,6 +12,7 @@ ["$." codec]]}] [data [number + ["n" nat] ["i" int]]] [math ["r" random (#+ Random)]]] @@ -39,7 +40,7 @@ (do r.monad [sample (|> duration (:: @ map (/.frame /.day))) frame duration - factor (|> r.nat (:: @ map (|>> (n/% 10) (n/max 1)))) + factor (|> r.nat (:: @ map (|>> (n.% 10) (n.max 1)))) #let [(^open "/@.") /.order]] ($_ _.and (_.test "Can scale a duration." diff --git a/stdlib/source/test/lux/tool/compiler/default/syntax.lux b/stdlib/source/test/lux/tool/compiler/default/syntax.lux index 1b9e5c7a4..2b53cbfdb 100644 --- a/stdlib/source/test/lux/tool/compiler/default/syntax.lux +++ b/stdlib/source/test/lux/tool/compiler/default/syntax.lux @@ -3,7 +3,9 @@ [abstract/monad (#+ do)] [data ["%" text/format (#+ format)] - ["." name]] + ["." name] + [number + ["n" nat]]] ["r" math/random (#+ Random) ("#@." monad)] ["_" test (#+ Test)] [control @@ -29,7 +31,7 @@ (def: name-part^ (Random Text) (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 20) (n/max 1))))] + [size (|> r.nat (:: @ map (|>> (n.% 20) (n.max 1))))] (r.ascii/lower-alpha size))) (def: name^ @@ -48,7 +50,7 @@ textual^ (: (Random Code) ($_ r.either (do r.monad - [size (|> r.nat (r@map (n/% 20)))] + [size (|> r.nat (r@map (n.% 20)))] (|> (r.ascii/upper-alpha size) (r@map code.text))) (|> name^ (r@map code.identifier)) (|> name^ (r@map code.tag)))) @@ -59,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^ (: (Random Code) ($_ r.either (|> multi^ (r@map code.form)) (|> multi^ (r@map code.tuple)) (do r.monad - [size (|> r.nat (r@map (n/% 3)))] + [size (|> r.nat (r@map (n.% 3)))] (|> (r.list size (r.and code^ code^)) (r@map code.record)))))] ($_ r.either @@ -110,9 +112,9 @@ (def: comment-text^ (Random Text) - (let [char-gen (|> r.nat (r.filter (|>> (n/= (`` (char (~~ (static text.new-line))))) not)))] + (let [char-gen (|> r.nat (r.filter (|>> (n.= (`` (char (~~ (static text.new-line))))) not)))] (do r.monad - [size (|> r.nat (r@map (n/% 20)))] + [size (|> r.nat (r@map (n.% 20)))] (r.text char-gen size)))) (def: comment^ diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/case.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/case.lux index 30b446bb5..1a74a3cf2 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/analysis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/case.lux @@ -12,6 +12,8 @@ ["." product] ["." maybe] ["." text ("#@." equivalence)] + [number + ["n" nat]] [collection ["." list ("#@." monad)] ["." set]]] @@ -116,12 +118,12 @@ ($_ r.either (r@map product.right _primitive.primitive) (do r.monad - [choice (|> r.nat (:: @ map (n/% (list.size variant-tags)))) + [choice (|> r.nat (:: @ map (n.% (list.size variant-tags)))) #let [choiceT (maybe.assume (list.nth choice variant-tags)) choiceC (maybe.assume (list.nth choice primitivesC))]] (wrap (` ((~ choiceT) (~ choiceC))))) (do r.monad - [size (|> r.nat (:: @ map (n/% 3))) + [size (|> r.nat (:: @ map (n.% 3))) elems (r.list size input)] (wrap (code.tuple elems))) (r@wrap (code.record (list.zip2 record-tags primitivesC))) @@ -137,7 +139,7 @@ [module-name (r.unicode 5) variant-name (r.unicode 5) record-name (|> (r.unicode 5) (r.filter (|>> (text@= variant-name) not))) - size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) + size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) variant-tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list)) record-tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list)) primitivesTC (r.list size _primitive.primitive) @@ -178,7 +180,7 @@ _structure.check-fails))) (do @ [redundant-patterns (exhaustive-branches false variantTC inputC) - redundancy-idx (|> r.nat (:: @ map (n/% (list.size redundant-patterns)))) + redundancy-idx (|> r.nat (:: @ map (n.% (list.size redundant-patterns)))) #let [redundant-branchesC (<| (list@map (branch outputC)) list.concat (list (list.take redundancy-idx redundant-patterns) @@ -190,7 +192,7 @@ (do @ [[heterogeneousT heterogeneousC] (r.filter (|>> product.left (check.checks? outputT) not) _primitive.primitive) - heterogeneous-idx (|> r.nat (:: @ map (n/% (list.size exhaustive-patterns)))) + heterogeneous-idx (|> r.nat (:: @ map (n.% (list.size exhaustive-patterns)))) #let [heterogeneous-branchesC (list.concat (list (list.take heterogeneous-idx exhaustive-branchesC) (list (let [[_pattern _body] (maybe.assume (list.nth heterogeneous-idx exhaustive-branchesC))] [_pattern heterogeneousC])) diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux index 7d5046571..721e17b14 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux @@ -13,6 +13,8 @@ ["." maybe] ["." product] ["." text ("#@." equivalence)] + [number + ["n" nat]] [collection ["." list ("#@." functor)]]] ["." type] @@ -38,7 +40,7 @@ (///.run _primitive.state) (case> (#try.Success applyA) (let [[funcA argsA] (////analysis.application applyA)] - (n/= num-args (list.size argsA))) + (n.= num-args (list.size argsA))) (#try.Failure _) false))) @@ -74,9 +76,9 @@ (def: apply (do r.monad - [full-args (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) - partial-args (|> r.nat (:: @ map (n/% full-args))) - var-idx (|> r.nat (:: @ map (|>> (n/% full-args) (n/max 1)))) + [full-args (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) + partial-args (|> r.nat (:: @ map (n.% full-args))) + var-idx (|> r.nat (:: @ map (|>> (n.% full-args) (n.max 1)))) inputsTC (r.list full-args _primitive.primitive) #let [inputsT (list@map product.left inputsTC) inputsC (list@map product.right inputsTC)] diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux index 777fe152f..1c23b1c8a 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux @@ -9,7 +9,9 @@ pipe ["." try (#+ Try)]] [data - ["." text ("#@." equivalence)]] + ["." text ("#@." equivalence)] + [number + ["n" nat]]] ["." type ("#@." equivalence)] [macro ["." code]]] @@ -74,7 +76,7 @@ (///.run _primitive.state) (case> (^ (#try.Success [inferredT (#////analysis.Reference (////reference.local var))])) (and (type@= expectedT inferredT) - (n/= 0 var)) + (n.= 0 var)) _ false))) diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux index 08344f23e..ad2233b26 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux @@ -14,6 +14,8 @@ ["." product] ["." maybe] ["." text] + [number + ["n" nat]] [collection ["." list ("#@." functor)] ["." set]]] @@ -48,13 +50,13 @@ (def: (check-sum' tag size variant) (-> Tag Nat (Variant Analysis) Bit) - (let [expected//right? (n/= (dec size) tag) + (let [expected//right? (n.= (dec size) tag) expected//lefts (if expected//right? (dec tag) tag) actual//right? (get@ #////analysis.right? variant) actual//lefts (get@ #////analysis.lefts variant)] - (and (n/= expected//lefts + (and (n.= expected//lefts actual//lefts) (bit@= expected//right? actual//right?)))) @@ -93,7 +95,7 @@ (|>> (case> (^ (////analysis.tuple elems)) (|> elems list.size - (n/= size)) + (n.= size)) _ false))) @@ -112,10 +114,10 @@ (def: sum (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) - choice (|> r.nat (:: @ map (n/% size))) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) + choice (|> r.nat (:: @ map (n.% size))) primitives (r.list size _primitive.primitive) - +choice (|> r.nat (:: @ map (n/% (inc size)))) + +choice (|> r.nat (:: @ map (n.% (inc size)))) [_ +valueC] _primitive.primitive #let [variantT (type.variant (list@map product.left primitives)) [valueT valueC] (maybe.assume (list.nth choice primitives)) @@ -154,7 +156,7 @@ (/.sum _primitive.phase +choice +valueC)) check-succeeds)) (_.test "Can analyse through universal quantification." - (let [check-outcome (if (not (n/= choice +choice)) + (let [check-outcome (if (not (n.= choice +choice)) check-succeeds check-fails)] (|> (//type.with-type (type.univ-q 1 +variantT) @@ -164,9 +166,9 @@ (def: product (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) primitives (r.list size _primitive.primitive) - choice (|> r.nat (:: @ map (n/% size))) + choice (|> r.nat (:: @ map (n.% size))) [_ +valueC] _primitive.primitive #let [tupleT (type.tuple (list@map product.left primitives)) [singletonT singletonC] (|> primitives (list.nth choice) maybe.assume) @@ -224,10 +226,10 @@ (def: variant (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list)) - choice (|> r.nat (:: @ map (n/% size))) - other-choice (|> r.nat (:: @ map (n/% size)) (r.filter (|>> (n/= choice) not))) + choice (|> r.nat (:: @ map (n.% size))) + other-choice (|> r.nat (:: @ map (n.% size)) (r.filter (|>> (n.= choice) not))) primitives (r.list size _primitive.primitive) module-name (r.unicode 5) type-name (r.unicode 5) @@ -270,12 +272,12 @@ (def: record (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list)) primitives (r.list size _primitive.primitive) module-name (r.unicode 5) type-name (r.unicode 5) - choice (|> r.nat (:: @ map (n/% size))) + choice (|> r.nat (:: @ map (n.% size))) #let [varT (#.Parameter 1) tagsC (list@map (|>> [module-name] code.tag) tags) primitivesT (list@map product.left primitives) diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux index d2d310fa1..13418eba0 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux @@ -2,7 +2,9 @@ [lux #* [abstract ["." monad (#+ do)]] [data - ["." name]] + ["." name] + [number + ["n" nat]]] ["r" math/random (#+ Random) ("#@." monad)] ["_" test (#+ Test)] [control @@ -25,7 +27,7 @@ Test (do r.monad [maskedA //primitive.primitive - temp (|> r.nat (:: @ map (n/% 100))) + temp (|> r.nat (:: @ map (n.% 100))) #let [maskA (////analysis.control/case [maskedA [[(#////analysis.Bind temp) @@ -54,7 +56,7 @@ //.phase (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.branch/let [inputS registerS outputS]))) - (and (n/= registerA registerS) + (and (n.= registerA registerS) (//primitive.corresponds? inputA inputS) (//primitive.corresponds? outputA outputS)) diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux index 368b692e9..db6c38eca 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux @@ -12,7 +12,7 @@ ["." product] ["." maybe] [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor fold)] ["dict" dictionary (#+ Dictionary)] @@ -48,12 +48,12 @@ (def: (pick scope-size) (-> Nat (Random Nat)) - (|> r.nat (:: r.monad map (n/% scope-size)))) + (|> r.nat (:: r.monad map (n.% scope-size)))) (def: function-with-environment (Random [Arity Analysis Variable]) (do r.monad - [num-locals (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10)))) + [num-locals (|> r.nat (:: @ map (|>> (n.% 100) (n.max 10)))) #let [indices (list.n/range 0 (dec num-locals)) local-env (list@map (|>> #////reference.Local) indices) foreign-env (list@map (|>> #////reference.Foreign) indices)] @@ -64,14 +64,14 @@ resolver (list@fold (function (_ [idx var] resolver) (dict.put idx var resolver)) (: (Dictionary Nat Variable) - (dict.new nat.hash)) + (dict.new n.hash)) (list.enumerate current-env))] (do @ [nest? r.bit] (if nest? (do @ - [num-picks (:: @ map (n/max 1) (pick (inc current-env/size))) - picks (|> (r.set nat.hash num-picks (pick current-env/size)) + [num-picks (:: @ map (n.max 1) (pick (inc current-env/size))) + picks (|> (r.set n.hash num-picks (pick current-env/size)) (:: @ map set.to-list)) [arity bodyA predictionA] (recur (inc arity) (list@map (function (_ pick) @@ -102,10 +102,10 @@ (#////analysis.Function (list) bodyA) predictionA])) (do r.monad - [chosen (|> r.nat (:: @ map (|>> (n/% 100) (n/max 2))))] + [chosen (|> r.nat (:: @ map (|>> (n.% 100) (n.max 2))))] (wrap [arity (#////analysis.Reference (////reference.local chosen)) - (|> chosen (n/+ (dec arity)) #////reference.Local)]))))) + (|> chosen (n.+ (dec arity)) #////reference.Local)]))))) (def: abstraction Test @@ -119,17 +119,17 @@ //.phase (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity output]))) - (and (n/= arity//constant arity) + (and (n.= arity//constant arity) (//primitive.corresponds? prediction//constant output)) _ - (n/= 0 arity//constant)))) + (n.= 0 arity//constant)))) (_.test "Folded functions provide direct access to environment variables." (|> function//environment //.phase (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))]))) - (and (n/= arity//environment arity) + (and (n.= arity//environment arity) (variable@= prediction//environment output)) _ @@ -139,7 +139,7 @@ //.phase (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))]))) - (and (n/= arity//local arity) + (and (n.= arity//local arity) (variable@= prediction//local output)) _ @@ -149,7 +149,7 @@ (def: application Test (do r.monad - [arity (|> r.nat (:: @ map (|>> (n/% 10) (n/max 1)))) + [arity (|> r.nat (:: @ map (|>> (n.% 10) (n.max 1)))) funcA //primitive.primitive argsA (r.list arity //primitive.primitive)] ($_ _.and diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux index 76405c771..087756562 100644 --- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux @@ -12,6 +12,8 @@ [data ["." bit ("#@." equivalence)] ["." product] + [number + ["n" nat]] [collection ["." list]]]] ["." // #_ @@ -29,9 +31,9 @@ (def: variant Test (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/+ 2)))) - tagA (|> r.nat (:: @ map (n/% size))) - #let [right? (n/= (dec size) tagA) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.+ 2)))) + tagA (|> r.nat (:: @ map (n.% size))) + #let [right? (n.= (dec size) tagA) lefts (if right? (dec tagA) tagA)] @@ -42,8 +44,8 @@ (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.variant [leftsS right?S valueS]))) (let [tagS (if right?S (inc leftsS) leftsS)] - (and (n/= tagA tagS) - (|> tagS (n/= (dec size)) (bit@= right?S)) + (and (n.= tagA tagS) + (|> tagS (n.= (dec size)) (bit@= right?S)) (//primitive.corresponds? memberA valueS))) _ @@ -52,14 +54,14 @@ (def: tuple Test (do r.monad - [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2)))) + [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2)))) membersA (r.list size //primitive.primitive)] (_.test "Can synthesize tuple." (|> (////analysis.tuple membersA) //.phase (///.run [///bundle.empty ////synthesis.init]) (case> (^ (#try.Success (////synthesis.tuple membersS))) - (and (n/= size (list.size membersS)) + (and (n.= size (list.size membersS)) (list.every? (product.uncurry //primitive.corresponds?) (list.zip2 membersA membersS))) diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux index c3931c331..f129f1c5a 100644 --- a/stdlib/source/test/lux/type.lux +++ b/stdlib/source/test/lux/type.lux @@ -8,6 +8,8 @@ pipe] [data ["." maybe] + [number + ["n" nat]] [collection ["." list]]]] {1 @@ -21,7 +23,7 @@ (def: short (r.Random Text) (do r.monad - [size (|> r.nat (:: @ map (n/% 10)))] + [size (|> r.nat (:: @ map (n.% 10)))] (r.unicode size))) (def: name @@ -82,7 +84,7 @@ (/.un-name base) (/.un-name aliased)))))) (do r.monad - [size (|> r.nat (:: @ map (n/% 3))) + [size (|> r.nat (:: @ map (n.% 3))) members (|> ..type (r.filter (function (_ type) (case type @@ -108,7 +110,7 @@ )) ))) (do r.monad - [size (|> r.nat (:: @ map (n/% 3))) + [size (|> r.nat (:: @ map (n.% 3))) members (M.seq @ (list.repeat size ..type)) extra (|> ..type (r.filter (function (_ type) @@ -128,10 +130,10 @@ (_.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)))) )) (do r.monad - [size (|> r.nat (:: @ map (n/% 3))) + [size (|> r.nat (:: @ map (n.% 3))) extra (|> ..type (r.filter (function (_ type) (case type @@ -145,7 +147,7 @@ (~~ (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/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux index d3d0570a1..2184de475 100644 --- a/stdlib/source/test/lux/type/check.lux +++ b/stdlib/source/test/lux/type/check.lux @@ -12,7 +12,7 @@ ["." maybe] ["." text ("#@." equivalence)] [number - ["." nat]] + ["n" nat]] [collection ["." list ("#@." functor)] ["." set]]] @@ -189,7 +189,7 @@ (/.check .Bit var)))) ) (do r.monad - [num-connections (|> r.nat (:: @ map (n/% 100))) + [num-connections (|> r.nat (:: @ map (n.% 100))) boundT (|> ..type (r.filter (|>> (case> (#.Var _) #0 _ #1)))) pick-pcg (r.and r.nat r.nat)] ($_ _.and @@ -201,10 +201,10 @@ tailR (/.ring tail-id)] (/.assert "" (let [same-rings? (:: set.equivalence = headR tailR) - expected-size? (n/= (inc num-connections) (set.size headR)) + expected-size? (n.= (inc num-connections) (set.size headR)) same-vars? (|> (set.to-list headR) - (list.sort n/<) - (:: (list.equivalence nat.equivalence) = (list.sort n/< (#.Cons head-id ids))))] + (list.sort n.<) + (:: (list.equivalence n.equivalence) = (list.sort n.< (#.Cons head-id ids))))] (and same-rings? expected-size? same-vars?)))))) @@ -237,7 +237,7 @@ headRR-post (/.ring head-idR)] (/.assert "" (let [same-rings? (:: set.equivalence = headRL-post headRR-post) - expected-size? (n/= (n/* 2 (inc num-connections)) + expected-size? (n.= (n.* 2 (inc num-connections)) (set.size headRL-post)) union? (:: set.equivalence = headRL-post (set.union headRL-pre headRR-pre))] (and same-rings? diff --git a/stdlib/source/test/lux/type/dynamic.lux b/stdlib/source/test/lux/type/dynamic.lux index b84a6f0a3..960a8ab9d 100644 --- a/stdlib/source/test/lux/type/dynamic.lux +++ b/stdlib/source/test/lux/type/dynamic.lux @@ -5,7 +5,10 @@ ["r" math/random (#+ Random)] ["_" test (#+ Test)] [control - ["." try]]] + ["." try]] + [data + [number + ["n" nat]]]] {1 ["." / (#+ Dynamic :dynamic :check)]}) @@ -19,7 +22,7 @@ (_.test "Can check dynamic values." (case (:check Nat value) (#try.Success actual) - (n/= expected actual) + (n.= expected actual) (#try.Failure _) false)) diff --git a/stdlib/source/test/lux/type/implicit.lux b/stdlib/source/test/lux/type/implicit.lux index 34b8b68c9..14b7c9524 100644 --- a/stdlib/source/test/lux/type/implicit.lux +++ b/stdlib/source/test/lux/type/implicit.lux @@ -10,7 +10,7 @@ [data ["." bit ("#@." equivalence)] [number - ["." nat]] + ["n" nat]] [collection ["." list]]]] {1 @@ -24,8 +24,8 @@ y r.nat] ($_ _.and (_.test "Can automatically select first-order structures." - (let [(^open "list@.") (list.equivalence nat.equivalence)] - (and (bit@= (:: nat.equivalence = x y) + (let [(^open "list@.") (list.equivalence n.equivalence)] + (and (bit@= (:: n.equivalence = x y) (/.::: = x y)) (list@= (list.n/range 1 10) (/.::: map inc (list.n/range 0 9))) diff --git a/stdlib/source/test/lux/type/resource.lux b/stdlib/source/test/lux/type/resource.lux index 637f0a564..298b95ad7 100644 --- a/stdlib/source/test/lux/type/resource.lux +++ b/stdlib/source/test/lux/type/resource.lux @@ -7,7 +7,10 @@ [monad [indexed (#+ do)]]] [control - ["." io]]] + ["." io]] + [data + [number + ["n" nat]]]] {1 ["." / (#+ Res)]}) @@ -16,7 +19,7 @@ (<| (_.context (%.name (name-of /._))) ($_ _.and (_.test "Can produce and consume keys in an ordered manner." - (<| (n/= (n/+ 123 456)) + (<| (n.= (n.+ 123 456)) io.run /.run-sync (do /.sync @@ -24,9 +27,9 @@ res|right (/.ordered-sync 456) right (/.read-sync res|right) left (/.read-sync res|left)] - (wrap (n/+ left right))))) + (wrap (n.+ left right))))) (_.test "Can exchange commutative keys." - (<| (n/= (n/+ 123 456)) + (<| (n.= (n.+ 123 456)) io.run /.run-sync (do /.sync @@ -35,9 +38,9 @@ _ (/.exchange-sync [1 0]) left (/.read-sync res|left) right (/.read-sync res|right)] - (wrap (n/+ left right))))) + (wrap (n.+ left right))))) (_.test "Can group and un-group keys." - (<| (n/= (n/+ 123 456)) + (<| (n.= (n.+ 123 456)) io.run /.run-sync (do /.sync @@ -47,5 +50,5 @@ _ (/.un-group-sync 2) right (/.read-sync res|right) left (/.read-sync res|left)] - (wrap (n/+ left right))))) + (wrap (n.+ left right))))) ))) diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index 91f7ba0be..d13a024e7 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -15,6 +15,7 @@ ["." binary (#+ Binary)] ["." text] [number + ["n" nat] ["i" int]] [collection ["." list]]] @@ -68,7 +69,7 @@ Test (<| (_.context (%.name (name-of /._))) (do r.monad - [file-size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10)))) + [file-size (|> r.nat (:: @ map (|>> (n.% 100) (n.max 10)))) dataL (_binary.binary file-size) dataR (_binary.binary file-size) new-modified (|> r.int (:: @ map (|>> i.abs @@ -86,7 +87,7 @@ _ (!.use (:: file over-write) dataL) read-size (!.use (:: file size) []) _ (!.use (:: file delete) [])] - (wrap (n/= file-size read-size))))] + (wrap (n.= file-size read-size))))] (_.assert "Can read file size." (try.default #0 result)))) (wrap (do promise.monad @@ -99,7 +100,7 @@ content (!.use (:: file content) []) read-size (!.use (:: file size) []) _ (!.use (:: file delete) [])] - (wrap (and (n/= (n/* 2 file-size) read-size) + (wrap (and (n.= (n.* 2 file-size) read-size) (:: binary.equivalence = dataL (try.assume (binary.slice 0 (dec file-size) content))) @@ -135,7 +136,7 @@ read-size (!.use (:: file size) []) _ (!.use (:: file delete) []) _ (!.use (:: dir discard) [])] - (wrap (n/= file-size read-size))))] + (wrap (n.= file-size read-size))))] (_.assert "Can create files inside of directories." (try.default #0 result)))) (wrap (do promise.monad @@ -156,10 +157,10 @@ _ (!.use (:: file delete) []) _ (!.use (:: inner-dir discard) []) _ (!.use (:: dir discard) [])] - (wrap (and (and (n/= 0 (list.size pre-files)) - (n/= 0 (list.size pre-directories))) - (and (n/= 1 (list.size post-files)) - (n/= 1 (list.size post-directories)))))))] + (wrap (and (and (n.= 0 (list.size pre-files)) + (n.= 0 (list.size pre-directories))) + (and (n.= 1 (list.size post-files)) + (n.= 1 (list.size post-directories)))))))] (_.assert "Can list files/directories inside a directory." (try.default #0 result)))) (wrap (do promise.monad -- cgit v1.2.3