aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2017-10-16 19:28:04 -0400
committerEduardo Julian2017-10-16 19:28:04 -0400
commitfecfb6c1dd653e491e541233395ea4a7d8ae7409 (patch)
tree1083a8cbe6f8277a75fc7813f9a403a4db9e5732 /stdlib/test
parentb2b8a0ffda0661511d8aec5634aad314b1e6c710 (diff)
- Re-named "Result" type back to "Error".
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux.lux44
-rw-r--r--stdlib/test/test/lux/cli.lux8
-rw-r--r--stdlib/test/test/lux/concurrency/actor.lux6
-rw-r--r--stdlib/test/test/lux/concurrency/atom.lux8
-rw-r--r--stdlib/test/test/lux/concurrency/promise.lux2
-rw-r--r--stdlib/test/test/lux/concurrency/stm.lux2
-rw-r--r--stdlib/test/test/lux/control/cont.lux6
-rw-r--r--stdlib/test/test/lux/control/exception.lux20
-rw-r--r--stdlib/test/test/lux/control/interval.lux34
-rw-r--r--stdlib/test/test/lux/control/parser.lux18
-rw-r--r--stdlib/test/test/lux/control/pipe.lux2
-rw-r--r--stdlib/test/test/lux/control/state.lux18
-rw-r--r--stdlib/test/test/lux/data/bit.lux6
-rw-r--r--stdlib/test/test/lux/data/bool.lux4
-rw-r--r--stdlib/test/test/lux/data/coll/array.lux26
-rw-r--r--stdlib/test/test/lux/data/coll/list.lux32
-rw-r--r--stdlib/test/test/lux/data/coll/priority-queue.lux16
-rw-r--r--stdlib/test/test/lux/data/coll/queue.lux10
-rw-r--r--stdlib/test/test/lux/data/coll/seq.lux24
-rw-r--r--stdlib/test/test/lux/data/coll/set.lux14
-rw-r--r--stdlib/test/test/lux/data/coll/stack.lux10
-rw-r--r--stdlib/test/test/lux/data/coll/stream.lux14
-rw-r--r--stdlib/test/test/lux/data/coll/vector.lux12
-rw-r--r--stdlib/test/test/lux/data/error.lux (renamed from stdlib/test/test/lux/data/result.lux)18
-rw-r--r--stdlib/test/test/lux/data/format/json.lux6
-rw-r--r--stdlib/test/test/lux/data/format/xml.lux18
-rw-r--r--stdlib/test/test/lux/data/ident.lux14
-rw-r--r--stdlib/test/test/lux/data/number.lux108
-rw-r--r--stdlib/test/test/lux/data/number/complex.lux16
-rw-r--r--stdlib/test/test/lux/data/number/ratio.lux14
-rw-r--r--stdlib/test/test/lux/data/text/lexer.lux24
-rw-r--r--stdlib/test/test/lux/host.js.lux2
-rw-r--r--stdlib/test/test/lux/macro/code.lux2
-rw-r--r--stdlib/test/test/lux/macro/syntax.lux6
-rw-r--r--stdlib/test/test/lux/math/logic/continuous.lux6
-rw-r--r--stdlib/test/test/lux/math/logic/fuzzy.lux36
-rw-r--r--stdlib/test/test/lux/time/date.lux6
-rw-r--r--stdlib/test/test/lux/time/duration.lux6
-rw-r--r--stdlib/test/test/lux/time/instant.lux6
-rw-r--r--stdlib/test/test/lux/type.lux56
-rw-r--r--stdlib/test/test/lux/type/auto.lux6
-rw-r--r--stdlib/test/test/lux/world/blob.lux28
-rw-r--r--stdlib/test/test/lux/world/file.lux26
-rw-r--r--stdlib/test/test/lux/world/net/tcp.lux4
-rw-r--r--stdlib/test/test/lux/world/net/udp.lux4
-rw-r--r--stdlib/test/tests.lux2
46 files changed, 375 insertions, 375 deletions
diff --git a/stdlib/test/test/lux.lux b/stdlib/test/test/lux.lux
index 546d7f14f..5ff53793c 100644
--- a/stdlib/test/test/lux.lux
+++ b/stdlib/test/test/lux.lux
@@ -4,7 +4,7 @@
(lux (control ["M" monad #+ do Monad])
[io]
[math]
- ["R" math/random]
+ ["r" math/random]
(data [maybe]
[text "T/" Eq<Text>]
text/format)
@@ -12,9 +12,9 @@
(macro ["s" syntax #+ syntax:])))
(context: "Value identity."
- [size (|> R;nat (:: @ map (|>. (n.% +100) (n.max +10))))
- x (R;text size)
- y (R;text size)]
+ [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10))))
+ x (r;text size)
+ y (r;text size)]
($_ seq
(test "Every value is identical to itself, and the 'id' function doesn't change values in any way."
(and (is x x)
@@ -44,8 +44,8 @@
(and (|> value inc even?)
(|> value dec even?)))))]
- ["Nat" R;nat n.inc n.dec n.even? n.odd? n.= n.< n.>]
- ["Int" R;int i.inc i.dec i.even? i.odd? i.= i.< i.>]
+ ["Nat" r;nat n.inc n.dec n.even? n.odd? n.= n.< n.>]
+ ["Int" r;int i.inc i.dec i.even? i.odd? i.= i.< i.>]
)
(do-template [category rand-gen = < > <= >= min max]
@@ -68,10 +68,10 @@
(>= y (max x y)))
)))]
- ["Int" R;int i.= i.< i.> i.<= i.>= i.min i.max]
- ["Nat" R;nat n.= n.< n.> n.<= n.>= n.min n.max]
- ["Frac" R;frac f.= f.< f.> f.<= f.>= f.min f.max]
- ["Deg" R;deg d.= d.< d.> d.<= d.>= d.min d.max]
+ ["Int" r;int i.= i.< i.> i.<= i.>= i.min i.max]
+ ["Nat" r;nat n.= n.< n.> n.<= n.>= n.min n.max]
+ ["Frac" r;frac f.= f.< f.> f.<= f.>= f.min f.max]
+ ["Deg" r;deg d.= d.< d.> d.<= d.>= d.min d.max]
)
(do-template [category rand-gen = + - * / <%> > <0> <1> <factor> %x <cap> <prep>]
@@ -104,7 +104,7 @@
[x (:: @ map <cap> rand-gen)
y (|> rand-gen
(:: @ map <cap>)
- (R;filter (|>. (= <0>) not)))
+ (r;filter (|>. (= <0>) not)))
#let [r (<%> y x)
x' (- r x)]]
(test ""
@@ -116,10 +116,10 @@
(|> x' (/ y) (* y) (= x'))))
))]
- ["Nat" R;nat n.= n.+ n.- n.* n./ n.% n.> +0 +1 +1000000 %n (n.% +1000) id]
- ["Int" R;int i.= i.+ i.- i.* i./ i.% i.> 0 1 1000000 %i (i.% 1000) id]
- ["Frac" R;frac f.= f.+ f.- f.* f./ f.% f.> 0.0 1.0 1000000.0 %r id math;floor]
- ["Deg" R;deg d.= d.+ d.- d.* d./ d.% d.> .0 (_lux_proc ["deg" "max-value"] []) (_lux_proc ["deg" "max-value"] []) %f id id]
+ ["Nat" r;nat n.= n.+ n.- n.* n./ n.% n.> +0 +1 +1000000 %n (n.% +1000) id]
+ ["Int" r;int i.= i.+ i.- i.* i./ i.% i.> 0 1 1000000 %i (i.% 1000) id]
+ ["Frac" r;frac f.= f.+ f.- f.* f./ f.% f.> 0.0 1.0 1000000.0 %r id math;floor]
+ ["Deg" r;deg d.= d.+ d.- d.* d./ d.% d.> .0 (_lux_proc ["deg" "max-value"] []) (_lux_proc ["deg" "max-value"] []) %f id id]
)
(do-template [category rand-gen -> <- = <cap> %a %z]
@@ -129,11 +129,11 @@
(test ""
(|> value -> <- (= value))))]
- ["Int->Nat" R;int int-to-nat nat-to-int i.= (i.% 1000000) %i %n]
- ["Nat->Int" R;nat nat-to-int int-to-nat n.= (n.% +1000000) %n %i]
- ["Int->Frac" R;int int-to-frac frac-to-int i.= (i.% 1000000) %i %r]
- ["Frac->Int" R;frac frac-to-int int-to-frac f.= math;floor %r %i]
- ## [R;frac frac-to-deg deg-to-frac f.= (f.% 1.0) %r %f]
+ ["Int->Nat" r;int int-to-nat nat-to-int i.= (i.% 1000000) %i %n]
+ ["Nat->Int" r;nat nat-to-int int-to-nat n.= (n.% +1000000) %n %i]
+ ["Int->Frac" r;int int-to-frac frac-to-int i.= (i.% 1000000) %i %r]
+ ["Frac->Int" r;frac frac-to-int int-to-frac f.= math;floor %r %i]
+ ## [r;frac frac-to-deg deg-to-frac f.= (f.% 1.0) %r %f]
)
(context: "Simple macros and constructs"
@@ -173,8 +173,8 @@
(i.+ (i.* x x) (i.* y y)))
(context: "Templates"
- [x R;int
- y R;int]
+ [x r;int
+ y r;int]
(test "Template application is a stand-in for the templated code."
(i.= (i.+ (i.* x x) (i.* y y))
(hypotenuse x y))))
diff --git a/stdlib/test/test/lux/cli.lux b/stdlib/test/test/lux/cli.lux
index fb7301359..6c6b113ea 100644
--- a/stdlib/test/test/lux/cli.lux
+++ b/stdlib/test/test/lux/cli.lux
@@ -11,14 +11,14 @@
[sum]
(coll [list]))
["&" cli]
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "CLI"
- [num-args (|> R;nat (:: @ map (n.% +10)))
+ [num-args (|> r;nat (:: @ map (n.% +10)))
#let [(^open "Nat/") number;Codec<Text,Nat>
- gen-arg (:: @ map Nat/encode R;nat)]
- option-name (R;text +5)
+ gen-arg (:: @ map Nat/encode r;nat)]
+ option-name (r;text +5)
singleton gen-arg]
($_ seq
(test "Can read any argument."
diff --git a/stdlib/test/test/lux/concurrency/actor.lux b/stdlib/test/test/lux/concurrency/actor.lux
index 41618cb64..f5d230833 100644
--- a/stdlib/test/test/lux/concurrency/actor.lux
+++ b/stdlib/test/test/lux/concurrency/actor.lux
@@ -5,7 +5,7 @@
["ex" exception])
(data [number]
text/format
- ["R" result])
+ ["E" error])
(concurrency ["P" promise "P/" Monad<Promise>]
["T" task]
["&" actor #+ actor: message:]))
@@ -79,9 +79,9 @@
(n.= +3 output-3))))]
(test "Can send messages to actors."
(case result
- (#R;Success outcome)
+ (#E;Success outcome)
outcome
- (#R;Error error)
+ (#E;Error error)
false)))
))
diff --git a/stdlib/test/test/lux/concurrency/atom.lux b/stdlib/test/test/lux/concurrency/atom.lux
index d841a4e84..538e7d676 100644
--- a/stdlib/test/test/lux/concurrency/atom.lux
+++ b/stdlib/test/test/lux/concurrency/atom.lux
@@ -6,13 +6,13 @@
(coll [list "" Functor<List>])
text/format)
(concurrency ["&" atom])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Atoms"
- [value R;nat
- swap-value R;nat
- set-value R;nat
+ [value r;nat
+ swap-value r;nat
+ set-value r;nat
#let [box (&;atom value)]]
($_ seq
(test "Can obtain the value of an atom."
diff --git a/stdlib/test/test/lux/concurrency/promise.lux b/stdlib/test/test/lux/concurrency/promise.lux
index 21e2aa7db..7b8f3fdd3 100644
--- a/stdlib/test/test/lux/concurrency/promise.lux
+++ b/stdlib/test/test/lux/concurrency/promise.lux
@@ -6,7 +6,7 @@
(data [number]
text/format)
(concurrency ["&" promise "&/" Monad<Promise>])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Promises"
diff --git a/stdlib/test/test/lux/concurrency/stm.lux b/stdlib/test/test/lux/concurrency/stm.lux
index ade1700b5..52361b85a 100644
--- a/stdlib/test/test/lux/concurrency/stm.lux
+++ b/stdlib/test/test/lux/concurrency/stm.lux
@@ -8,7 +8,7 @@
text/format)
(concurrency ["&" stm]
[promise])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: iterations/processes Int 100)
diff --git a/stdlib/test/test/lux/control/cont.lux b/stdlib/test/test/lux/control/cont.lux
index 926525942..ea86ccb05 100644
--- a/stdlib/test/test/lux/control/cont.lux
+++ b/stdlib/test/test/lux/control/cont.lux
@@ -8,13 +8,13 @@
[number]
[product]
(coll [list]))
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Continuations"
- [sample R;nat
+ [sample r;nat
#let [(^open "&/") &;Monad<Cont>]
- elems (R;list +3 R;nat)]
+ elems (r;list +3 r;nat)]
($_ seq
(test "Can run continuations to compute their values."
(n.= sample (&;run (&/wrap sample))))
diff --git a/stdlib/test/test/lux/control/exception.lux b/stdlib/test/test/lux/control/exception.lux
index 5680b95f1..fc552b69c 100644
--- a/stdlib/test/test/lux/control/exception.lux
+++ b/stdlib/test/test/lux/control/exception.lux
@@ -3,11 +3,11 @@
(lux [io]
(control ["M" monad #+ do Monad]
["&" exception #+ exception:])
- (data ["E" result]
+ (data ["E" error]
[text]
text/format
[number])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(exception: Some-Exception)
@@ -17,13 +17,13 @@
(exception: Unknown-Exception)
(context: "Exceptions"
- [should-throw? R;bool
- which? R;bool
- should-catch? R;bool
- default-val R;nat
- some-val R;nat
- another-val R;nat
- otherwise-val R;nat
+ [should-throw? r;bool
+ which? r;bool
+ should-catch? r;bool
+ default-val r;nat
+ some-val r;nat
+ another-val r;nat
+ otherwise-val r;nat
#let [this-ex (if should-catch?
(if which?
Some-Exception
@@ -36,7 +36,7 @@
another-val)
otherwise-val)
default-val)
- actual (|> (: (E;Result Nat)
+ actual (|> (: (E;Error Nat)
(if should-throw?
(&;throw this-ex "Uh-oh...")
(&;return default-val)))
diff --git a/stdlib/test/test/lux/control/interval.lux b/stdlib/test/test/lux/control/interval.lux
index 8cf46012c..2ba5198bc 100644
--- a/stdlib/test/test/lux/control/interval.lux
+++ b/stdlib/test/test/lux/control/interval.lux
@@ -5,15 +5,15 @@
pipe
["&" interval])
[io]
- ["R" math/random]
+ ["r" math/random]
(data text/format
[number]
["S" coll/set]
["L" coll/list])))
(context: "Equality."
- [bottom R;int
- top R;int
+ [bottom r;int
+ top r;int
#let [(^open "&/") &;Eq<Interval>]]
($_ seq
(test "Every interval is equal to itself."
@@ -25,8 +25,8 @@
(&/= self self))))))
(context: "Boundaries"
- [bottom R;int
- top R;int
+ [bottom r;int
+ top r;int
#let [interval (&;between number;Enum<Int> bottom top)]]
($_ seq
(test "Every boundary value belongs to it's interval."
@@ -53,10 +53,10 @@
(do-template [<name> <cmp>]
[(def: <name>
- (R;Random (&;Interval Int))
- (do R;Monad<Random>
- [bottom R;int
- top (|> R;int (R;filter (|>. (i.= bottom) not)))]
+ (r;Random (&;Interval Int))
+ (do r;Monad<Random>
+ [bottom r;int
+ top (|> r;int (r;filter (|>. (i.= bottom) not)))]
(if (<cmp> top bottom)
(wrap (&;between number;Enum<Int> bottom top))
(wrap (&;between number;Enum<Int> top bottom)))))]
@@ -66,14 +66,14 @@
)
(def: gen-singleton
- (R;Random (&;Interval Int))
- (do R;Monad<Random>
- [point R;int]
+ (r;Random (&;Interval Int))
+ (do r;Monad<Random>
+ [point r;int]
(wrap (&;singleton number;Enum<Int> point))))
(def: gen-interval
- (R;Random (&;Interval Int))
- ($_ R;either
+ (r;Random (&;Interval Int))
+ ($_ r;either
gen-inner
gen-outer
gen-singleton))
@@ -129,7 +129,7 @@
))
(context: "Positioning/location"
- [[l m r] (|> (R;set number;Hash<Int> +3 R;int)
+ [[l m r] (|> (r;set number;Hash<Int> +3 r;int)
(:: @ map (|>. S;to-list
(L;sort i.<)
(case> (^ (list b t1 t2))
@@ -149,7 +149,7 @@
))
(context: "Touching intervals"
- [[b t1 t2] (|> (R;set number;Hash<Int> +3 R;int)
+ [[b t1 t2] (|> (r;set number;Hash<Int> +3 r;int)
(:: @ map (|>. S;to-list
(L;sort i.<)
(case> (^ (list b t1 t2))
@@ -174,7 +174,7 @@
(context: "Nesting & overlap"
[some-interval gen-interval
- [x0 x1 x2 x3] (|> (R;set number;Hash<Int> +4 R;int)
+ [x0 x1 x2 x3] (|> (r;set number;Hash<Int> +4 r;int)
(:: @ map (|>. S;to-list
(L;sort i.<)
(case> (^ (list x0 x1 x2 x3))
diff --git a/stdlib/test/test/lux/control/parser.lux b/stdlib/test/test/lux/control/parser.lux
index ae3fc2041..0f6b4a4b1 100644
--- a/stdlib/test/test/lux/control/parser.lux
+++ b/stdlib/test/test/lux/control/parser.lux
@@ -10,7 +10,7 @@
[number]
[bool]
[ident]
- ["R" result])
+ ["E" error])
["r" math/random]
[macro]
(macro [code]
@@ -19,15 +19,15 @@
## [Utils]
(def: (should-fail input)
- (All [a] (-> (R;Result a) Bool))
+ (All [a] (-> (E;Error a) Bool))
(case input
- (#R;Error _) true
+ (#E;Error _) true
_ false))
(def: (enforced? parser input)
(All [s] (-> (&;Parser s Unit) s Bool))
(case (&;run input parser)
- (#R;Success [_ []])
+ (#E;Success [_ []])
true
_
@@ -36,7 +36,7 @@
(def: (found? parser input)
(All [s] (-> (&;Parser s Bool) s Bool))
(case (&;run input parser)
- (#R;Success [_ true])
+ (#E;Success [_ true])
true
_
@@ -45,16 +45,16 @@
(def: (is? Eq<a> test parser input)
(All [s a] (-> (Eq a) a (&;Parser s a) s Bool))
(case (&;run input parser)
- (#R;Success [_ output])
+ (#E;Success [_ output])
(:: Eq<a> = test output)
_
false))
(def: (fails? input)
- (All [a] (-> (R;Result a) Bool))
+ (All [a] (-> (E;Error a) Bool))
(case input
- (#R;Error _)
+ (#E;Error _)
true
_
@@ -62,7 +62,7 @@
(syntax: (match pattern input)
(wrap (list (` (case (~ input)
- (^ (#R;Success [(~' _) (~ pattern)]))
+ (^ (#E;Success [(~' _) (~ pattern)]))
true
(~' _)
diff --git a/stdlib/test/test/lux/control/pipe.lux b/stdlib/test/test/lux/control/pipe.lux
index 37f76e9af..23e6cfe60 100644
--- a/stdlib/test/test/lux/control/pipe.lux
+++ b/stdlib/test/test/lux/control/pipe.lux
@@ -8,7 +8,7 @@
[product]
identity
[text "T/" Eq<Text>])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Pipes"
diff --git a/stdlib/test/test/lux/control/state.lux b/stdlib/test/test/lux/control/state.lux
index 87731de60..1447e61c3 100644
--- a/stdlib/test/test/lux/control/state.lux
+++ b/stdlib/test/test/lux/control/state.lux
@@ -8,7 +8,7 @@
text/format
[number]
[product])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: (with-conditions [state output] computation)
@@ -19,8 +19,8 @@
(n.= output)))
(context: "Basics"
- [state R;nat
- value R;nat]
+ [state r;nat
+ value r;nat]
($_ seq
(test "Can get the state as a value."
(with-conditions [state state]
@@ -45,8 +45,8 @@
))
(context: "Structures"
- [state R;nat
- value R;nat]
+ [state r;nat
+ value r;nat]
($_ seq
(test "Can use functor."
(with-conditions [state (n.inc state)]
@@ -69,9 +69,9 @@
))
(context: "Monad transformer"
- [state R;nat
- left R;nat
- right R;nat]
+ [state r;nat
+ left r;nat
+ right r;nat]
(let [(^open "io/") io;Monad<IO>]
(test "Can add state functionality to any monad."
(|> (: (&;State' io;IO Nat Nat)
@@ -87,7 +87,7 @@
))
(context: "Loops"
- [limit (|> R;nat (:: @ map (n.% +10)))
+ [limit (|> r;nat (:: @ map (n.% +10)))
#let [condition (do &;Monad<State>
[state &;get]
(wrap (n.< limit state)))]]
diff --git a/stdlib/test/test/lux/data/bit.lux b/stdlib/test/test/lux/data/bit.lux
index 53bebe088..8bbe8e599 100644
--- a/stdlib/test/test/lux/data/bit.lux
+++ b/stdlib/test/test/lux/data/bit.lux
@@ -4,12 +4,12 @@
(control ["M" monad #+ do Monad])
(data ["&" bit]
number)
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Bitwise operations."
- [pattern R;nat
- idx (:: @ map (n.% &;width) R;nat)]
+ [pattern r;nat
+ idx (:: @ map (n.% &;width) r;nat)]
($_ seq
(test "Clearing and settings bits should alter the count."
(and (n.< (&;count (&;set idx pattern))
diff --git a/stdlib/test/test/lux/data/bool.lux b/stdlib/test/test/lux/data/bool.lux
index bbc867581..69366a3d2 100644
--- a/stdlib/test/test/lux/data/bool.lux
+++ b/stdlib/test/test/lux/data/bool.lux
@@ -3,11 +3,11 @@
(lux (control ["M" monad #+ do Monad])
[io]
(data bool)
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Boolean operations."
- [value R;bool]
+ [value r;bool]
(test "" (and (not (and value (not value)))
(or value (not value))
diff --git a/stdlib/test/test/lux/data/coll/array.lux b/stdlib/test/test/lux/data/coll/array.lux
index d5fde5a64..e32bf2e0f 100644
--- a/stdlib/test/test/lux/data/coll/array.lux
+++ b/stdlib/test/test/lux/data/coll/array.lux
@@ -7,17 +7,17 @@
[list])
[number]
[maybe])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: bounded-size
- (R;Random Nat)
- (|> R;nat
- (:: R;Monad<Random> map (|>. (n.% +100) (n.+ +1)))))
+ (r;Random Nat)
+ (|> r;nat
+ (:: r;Monad<Random> map (|>. (n.% +100) (n.+ +1)))))
(context: "Arrays and their copies"
[size bounded-size
- original (R;array size R;nat)
+ original (r;array size r;nat)
#let [clone (@;clone original)
copy (: (Array Nat)
(@;new size))
@@ -49,9 +49,9 @@
(context: "Array mutation"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- array (|> (R;array size R;nat)
- (R;filter (|>. @;to-list (list;any? n.odd?))))
+ idx (:: @ map (n.% size) r;nat)
+ array (|> (r;array size r;nat)
+ (r;filter (|>. @;to-list (list;any? n.odd?))))
#let [value (maybe;assume (@;read idx array))]]
($_ seq
(test "Shouldn't be able to find a value in an unoccupied cell."
@@ -75,8 +75,8 @@
(context: "Finding values."
[size bounded-size
- array (|> (R;array size R;nat)
- (R;filter (|>. @;to-list (list;any? n.even?))))]
+ array (|> (r;array size r;nat)
+ (r;filter (|>. @;to-list (list;any? n.even?))))]
($_ seq
(test "Can find values inside arrays."
(|> (@;find n.even? array)
@@ -92,7 +92,7 @@
(context: "Functor"
[size bounded-size
- array (R;array size R;nat)]
+ array (r;array size r;nat)]
(let [(^open) @;Functor<Array>
(^open) (@;Eq<Array> number;Eq<Nat>)]
($_ seq
@@ -109,8 +109,8 @@
(context: "Monoid"
[sizeL bounded-size
sizeR bounded-size
- left (R;array sizeL R;nat)
- right (R;array sizeR R;nat)
+ left (r;array sizeL r;nat)
+ right (r;array sizeR r;nat)
#let [(^open) @;Monoid<Array>
(^open) (@;Eq<Array> number;Eq<Nat>)
fusion (compose left right)]]
diff --git a/stdlib/test/test/lux/data/coll/list.lux b/stdlib/test/test/lux/data/coll/list.lux
index a3d091625..2b5146a65 100644
--- a/stdlib/test/test/lux/data/coll/list.lux
+++ b/stdlib/test/test/lux/data/coll/list.lux
@@ -9,21 +9,21 @@
[bool]
[product]
[maybe])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: bounded-size
- (R;Random Nat)
- (|> R;nat
- (:: R;Monad<Random> map (|>. (n.% +100) (n.+ +10)))))
+ (r;Random Nat)
+ (|> r;nat
+ (:: r;Monad<Random> map (|>. (n.% +100) (n.+ +10)))))
(context: "Lists: Part 1"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- sample (R;list 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)
- separator R;nat
+ other-sample (r;list other-size r;nat)
+ separator r;nat
#let [(^open) (&;Eq<List> number;Eq<Nat>)
(^open "&/") &;Functor<List>]]
($_ seq
@@ -63,11 +63,11 @@
(context: "Lists: Part 2"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- sample (R;list 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)
- separator R;nat
+ other-sample (r;list other-size r;nat)
+ separator r;nat
#let [(^open) (&;Eq<List> number;Eq<Nat>)
(^open "&/") &;Functor<List>]]
($_ seq
@@ -122,11 +122,11 @@
(context: "Lists: Part 3"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- sample (R;list 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)
- separator R;nat
+ other-sample (r;list other-size r;nat)
+ separator r;nat
#let [(^open) (&;Eq<List> number;Eq<Nat>)
(^open "&/") &;Functor<List>]]
($_ seq
diff --git a/stdlib/test/test/lux/data/coll/priority-queue.lux b/stdlib/test/test/lux/data/coll/priority-queue.lux
index 51b9aee5e..07a2200a3 100644
--- a/stdlib/test/test/lux/data/coll/priority-queue.lux
+++ b/stdlib/test/test/lux/data/coll/priority-queue.lux
@@ -5,25 +5,25 @@
(data (coll ["&" priority-queue])
[number]
[maybe])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: (gen-queue size)
- (-> Nat (R;Random (&;Queue Nat)))
- (do R;Monad<Random>
- [inputs (R;list size R;nat)]
+ (-> Nat (r;Random (&;Queue Nat)))
+ (do r;Monad<Random>
+ [inputs (r;list size r;nat)]
(monad;fold @ (function [head tail]
(do @
- [priority R;nat]
+ [priority r;nat]
(wrap (&;push priority head tail))))
&;empty
inputs)))
(context: "Queues"
- [size (|> R;nat (:: @ map (n.% +100)))
+ [size (|> r;nat (:: @ map (n.% +100)))
sample (gen-queue size)
- non-member-priority R;nat
- non-member (|> R;nat (R;filter (|>. (&;member? number;Eq<Nat> sample) not)))]
+ non-member-priority r;nat
+ non-member (|> r;nat (r;filter (|>. (&;member? number;Eq<Nat> sample) not)))]
($_ seq
(test "I can query the size of a queue (and empty queues have size 0)."
(n.= size (&;size sample)))
diff --git a/stdlib/test/test/lux/data/coll/queue.lux b/stdlib/test/test/lux/data/coll/queue.lux
index 08c905e95..ddccc282b 100644
--- a/stdlib/test/test/lux/data/coll/queue.lux
+++ b/stdlib/test/test/lux/data/coll/queue.lux
@@ -4,14 +4,14 @@
(control [monad #+ do Monad])
(data (coll ["&" queue])
[number])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Queues"
- [size (:: @ map (n.% +100) R;nat)
- sample (R;queue size R;nat)
- non-member (|> R;nat
- (R;filter (. not (&;member? number;Eq<Nat> sample))))]
+ [size (:: @ map (n.% +100) r;nat)
+ sample (r;queue size r;nat)
+ non-member (|> r;nat
+ (r;filter (. not (&;member? number;Eq<Nat> sample))))]
($_ seq
(test "I can query the size of a queue (and empty queues have size 0)."
(if (n.= +0 size)
diff --git a/stdlib/test/test/lux/data/coll/seq.lux b/stdlib/test/test/lux/data/coll/seq.lux
index c6d25a0d8..801c5c2f1 100644
--- a/stdlib/test/test/lux/data/coll/seq.lux
+++ b/stdlib/test/test/lux/data/coll/seq.lux
@@ -11,20 +11,20 @@
[bool]
[product]
maybe)
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: bounded-size
- (R;Random Nat)
- (|> R;nat
- (:: R;Monad<Random> map (|>. (n.% +100) (n.+ +10) (n.max +1)))))
+ (r;Random Nat)
+ (|> r;nat
+ (:: r;Monad<Random> map (|>. (n.% +100) (n.+ +10) (n.max +1)))))
(context: "Seqs: Part 1"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- sample (|> (R;list size R;nat)
+ idx (:: @ map (n.% size) r;nat)
+ sample (|> (r;list size r;nat)
(:: @ map &;from-list))
- extra R;nat
+ extra r;nat
#let [(^open "&/") (&;Eq<Seq> number;Eq<Nat>)]]
($_ seq
(test "Can convert to/from list."
@@ -75,7 +75,7 @@
(context: "Seqs: Part 2"
[size bounded-size
- sample (|> (R;list size R;nat)
+ sample (|> (r;list size r;nat)
(:: @ map &;from-list))
#let [(^open "&/") (&;Eq<Seq> number;Eq<Nat>)
(^open "&/") &;Functor<Seq>]]
@@ -97,13 +97,13 @@
(context: "Seqs: Part 3"
[size bounded-size
- idx (:: @ map (n.% size) R;nat)
- sample (|> (R;list size R;nat)
+ idx (:: @ map (n.% size) r;nat)
+ sample (|> (r;list size r;nat)
(:: @ map &;from-list))
other-size bounded-size
- other-sample (|> (R;list other-size R;nat)
+ other-sample (|> (r;list other-size r;nat)
(:: @ map &;from-list))
- elem R;nat
+ elem r;nat
#let [(^open "&/") (&;Eq<Seq> number;Eq<Nat>)
(^open "&/") &;Monad<Seq>]]
($_ seq
diff --git a/stdlib/test/test/lux/data/coll/set.lux b/stdlib/test/test/lux/data/coll/set.lux
index 0aafdd580..38ca47f81 100644
--- a/stdlib/test/test/lux/data/coll/set.lux
+++ b/stdlib/test/test/lux/data/coll/set.lux
@@ -5,21 +5,21 @@
(data (coll ["&" set]
[list "" Fold<List>])
[number])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: gen-nat
- (R;Random Nat)
- (|> R;nat
- (:: R;Monad<Random> map (n.% +100))))
+ (r;Random Nat)
+ (|> r;nat
+ (:: r;Monad<Random> map (n.% +100))))
(context: "Sets"
[sizeL gen-nat
sizeR gen-nat
- setL (R;set number;Hash<Nat> sizeL gen-nat)
- setR (R;set number;Hash<Nat> sizeR gen-nat)
+ setL (r;set number;Hash<Nat> sizeL gen-nat)
+ setR (r;set number;Hash<Nat> sizeR gen-nat)
non-member (|> gen-nat
- (R;filter (. not (&;member? setL))))
+ (r;filter (. not (&;member? setL))))
#let [(^open "&/") &;Eq<Set>]]
($_ seq
(test "I can query the size of a set."
diff --git a/stdlib/test/test/lux/data/coll/stack.lux b/stdlib/test/test/lux/data/coll/stack.lux
index 981d73197..fc7e2f4b2 100644
--- a/stdlib/test/test/lux/data/coll/stack.lux
+++ b/stdlib/test/test/lux/data/coll/stack.lux
@@ -6,17 +6,17 @@
[list "" Fold<List>])
[number]
[maybe])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: gen-nat
- (R;Random Nat)
- (|> R;nat
- (:: R;Monad<Random> map (n.% +100))))
+ (r;Random Nat)
+ (|> r;nat
+ (:: r;Monad<Random> map (n.% +100))))
(context: "Stacks"
[size gen-nat
- sample (R;stack size gen-nat)
+ sample (r;stack size gen-nat)
new-top gen-nat]
($_ seq
(test "Can query the size of a stack."
diff --git a/stdlib/test/test/lux/data/coll/stream.lux b/stdlib/test/test/lux/data/coll/stream.lux
index 053228278..a5a978f49 100644
--- a/stdlib/test/test/lux/data/coll/stream.lux
+++ b/stdlib/test/test/lux/data/coll/stream.lux
@@ -10,16 +10,16 @@
(coll [list]
["&" stream])
[number "Nat/" Codec<Text,Nat>])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Streams"
- [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)))
+ [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;Eq<List> number;Eq<Nat>)
sample0 (&;iterate n.inc +0)
sample1 (&;iterate n.inc offset)]]
diff --git a/stdlib/test/test/lux/data/coll/vector.lux b/stdlib/test/test/lux/data/coll/vector.lux
index e605805a8..23fe64464 100644
--- a/stdlib/test/test/lux/data/coll/vector.lux
+++ b/stdlib/test/test/lux/data/coll/vector.lux
@@ -8,15 +8,15 @@
text/format
[number]
[maybe])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "Vectors"
- [size (|> R;nat (:: @ map (|>. (n.% +100) (n.max +1))))
- idx (|> R;nat (:: @ map (n.% size)))
- sample (R;vector size R;nat)
- other-sample (R;vector size R;nat)
- non-member (|> R;nat (R;filter (. not (&;member? number;Eq<Nat> sample))))
+ [size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1))))
+ idx (|> r;nat (:: @ map (n.% size)))
+ sample (r;vector size r;nat)
+ other-sample (r;vector size r;nat)
+ non-member (|> r;nat (r;filter (. not (&;member? number;Eq<Nat> sample))))
#let [(^open "&/") (&;Eq<Vector> number;Eq<Nat>)
(^open "&/") &;Monad<Vector>
(^open "&/") &;Fold<Vector>
diff --git a/stdlib/test/test/lux/data/result.lux b/stdlib/test/test/lux/data/error.lux
index efd1009c8..a72a45403 100644
--- a/stdlib/test/test/lux/data/result.lux
+++ b/stdlib/test/test/lux/data/error.lux
@@ -4,18 +4,18 @@
(control ["M" monad #+ do Monad]
pipe)
(data text/format
- ["&" result]))
+ ["&" error]))
lux/test)
-(context: "Results"
- (let [(^open "&/") &;Monad<Result>]
+(context: "Errors"
+ (let [(^open "&/") &;Monad<Error>]
($_ seq
(test "Functor correctly handles both cases."
- (and (|> (: (&;Result Int) (#&;Success 10))
+ (and (|> (: (&;Error Int) (#&;Success 10))
(&/map i.inc)
(case> (#&;Success 11) true _ false))
- (|> (: (&;Result Int) (#&;Error "YOLO"))
+ (|> (: (&;Error Int) (#&;Error "YOLO"))
(&/map i.inc)
(case> (#&;Error "YOLO") true _ false))
))
@@ -29,13 +29,13 @@
(case> (#&;Error "YOLO") true _ false))))
(test "Monad correctly handles both cases."
- (and (|> (do &;Monad<Result>
+ (and (|> (do &;Monad<Error>
[f (wrap i.+)
a (wrap 10)
b (wrap 20)]
(wrap (f a b)))
(case> (#&;Success 30) true _ false))
- (|> (do &;Monad<Result>
+ (|> (do &;Monad<Error>
[f (wrap i.+)
a (#&;Error "YOLO")
b (wrap 20)]
@@ -47,8 +47,8 @@
(context: "Monad transformer"
(let [lift (&;lift io;Monad<IO>)
(^open "io/") io;Monad<IO>]
- (test "Can add result functionality to any monad."
- (|> (io;run (do (&;ResultT io;Monad<IO>)
+ (test "Can add error functionality to any monad."
+ (|> (io;run (do (&;ErrorT io;Monad<IO>)
[a (lift (io/wrap 123))
b (wrap 456)]
(wrap (i.+ a b))))
diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux
index 2eca6febd..89244d6fe 100644
--- a/stdlib/test/test/lux/data/format/json.lux
+++ b/stdlib/test/test/lux/data/format/json.lux
@@ -8,7 +8,7 @@
["p" parser])
(data [text "Text/" Monoid<Text>]
text/format
- ["R" result]
+ ["E" error]
[bool]
[maybe]
[number "i/" Number<Int>]
@@ -166,8 +166,8 @@
(^open "@/") Codec<JSON,Record>]]
(test "Can encode/decode arbitrary types."
(|> sample @/encode @/decode
- (case> (#R;Success result)
+ (case> (#E;Success result)
(@/= sample result)
- (#R;Error error)
+ (#E;Error error)
false))))
diff --git a/stdlib/test/test/lux/data/format/xml.lux b/stdlib/test/test/lux/data/format/xml.lux
index b43aee394..0a4179040 100644
--- a/stdlib/test/test/lux/data/format/xml.lux
+++ b/stdlib/test/test/lux/data/format/xml.lux
@@ -7,7 +7,7 @@
(data [text "text/" Eq<Text>]
text/format
[ident]
- ["R" result]
+ ["E" error]
[maybe]
(format ["&" xml])
(coll [dict]
@@ -84,28 +84,28 @@
(L/map (|>. #&;Text) children))]]
($_ seq
(test "Can parse text."
- (R;default false
- (do R;Monad<Result>
+ (E;default false
+ (do E;Monad<Error>
[output (&;run (#&;Text text)
&;text)]
(wrap (text/= text output)))))
(test "Can parse attributes."
- (R;default false
- (do R;Monad<Result>
+ (E;default false
+ (do E;Monad<Error>
[output (|> (&;attr attr)
(p;before &;ignore)
(&;run node))]
(wrap (text/= value output)))))
(test "Can parse nodes."
- (R;default false
- (do R;Monad<Result>
+ (E;default false
+ (do E;Monad<Error>
[_ (|> (&;node tag)
(p;before &;ignore)
(&;run node))]
(wrap true))))
(test "Can parse children."
- (R;default false
- (do R;Monad<Result>
+ (E;default false
+ (do E;Monad<Error>
[outputs (|> (&;children (p;some &;text))
(&;run node))]
(wrap (:: (list;Eq<List> text;Eq<Text>) =
diff --git a/stdlib/test/test/lux/data/ident.lux b/stdlib/test/test/lux/data/ident.lux
index 6ca00d09f..cae265a45 100644
--- a/stdlib/test/test/lux/data/ident.lux
+++ b/stdlib/test/test/lux/data/ident.lux
@@ -6,23 +6,23 @@
(data ["&" ident]
[text "Text/" Eq<Text>]
text/format)
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: (gen-part size)
- (-> Nat (R;Random Text))
- (|> (R;text size) (R;filter (. not (text;contains? ";")))))
+ (-> Nat (r;Random Text))
+ (|> (r;text size) (r;filter (. not (text;contains? ";")))))
(context: "Idents"
[## First Ident
- sizeM1 (|> R;nat (:: @ map (n.% +100)))
- sizeN1 (|> R;nat (:: @ map (|>. (n.% +100) (n.max +1))))
+ sizeM1 (|> r;nat (:: @ map (n.% +100)))
+ sizeN1 (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1))))
module1 (gen-part sizeM1)
name1 (gen-part sizeN1)
#let [ident1 [module1 name1]]
## Second Ident
- sizeM2 (|> R;nat (:: @ map (n.% +100)))
- sizeN2 (|> R;nat (:: @ map (|>. (n.% +100) (n.max +1))))
+ sizeM2 (|> r;nat (:: @ map (n.% +100)))
+ sizeN2 (|> r;nat (:: @ map (|>. (n.% +100) (n.max +1))))
module2 (gen-part sizeM2)
name2 (gen-part sizeN2)
#let [ident2 [module2 name2]]
diff --git a/stdlib/test/test/lux/data/number.lux b/stdlib/test/test/lux/data/number.lux
index c33d06856..1a33fdc2c 100644
--- a/stdlib/test/test/lux/data/number.lux
+++ b/stdlib/test/test/lux/data/number.lux
@@ -6,7 +6,7 @@
(data number
[text "Text/" Monoid<Text> Eq<Text>]
text/format)
- ["R" math/random])
+ ["r" math/random])
lux/test)
(do-template [category rand-gen <Eq> <Order>]
@@ -18,10 +18,10 @@
(:: <Order> < y x)
(:: <Order> > y x)))))]
- ["Nat" R;nat Eq<Nat> Order<Nat>]
- ["Int" R;int Eq<Int> Order<Int>]
- ["Frac" R;frac Eq<Frac> Order<Frac>]
- ["Deg" R;deg Eq<Deg> Order<Deg>]
+ ["Nat" r;nat Eq<Nat> Order<Nat>]
+ ["Int" r;int Eq<Int> Order<Int>]
+ ["Frac" r;frac Eq<Frac> Order<Frac>]
+ ["Deg" r;deg Eq<Deg> Order<Deg>]
)
(do-template [category rand-gen <Number> <Order>]
@@ -39,10 +39,10 @@
(= x (* (signum x)
(abs x)))))))]
- ## ["Nat" R;nat Number<Nat>]
- ["Int" R;int Number<Int> Order<Int>]
- ["Frac" R;frac Number<Frac> Order<Frac>]
- ["Deg" R;deg Number<Deg> Order<Deg>]
+ ## ["Nat" r;nat Number<Nat>]
+ ["Int" r;int Number<Int> Order<Int>]
+ ["Frac" r;frac Number<Frac> Order<Frac>]
+ ["Deg" r;deg Number<Deg> Order<Deg>]
)
(do-template [category rand-gen <Enum> <Number> <Order>]
@@ -61,28 +61,28 @@
(|> x (:: <Enum> succ) (:: <Enum> pred)))
))))]
- ["Nat" R;nat Enum<Nat> Number<Nat> Order<Nat>]
- ["Int" R;int Enum<Int> Number<Int> Order<Int>]
+ ["Nat" r;nat Enum<Nat> Number<Nat> Order<Nat>]
+ ["Int" r;int Enum<Int> Number<Int> Order<Int>]
)
(do-template [category rand-gen <Number> <Order> <Interval> <test>]
[(context: (format "[" category "] " "Interval")
- [x (|> rand-gen (R;filter <test>))
+ [x (|> rand-gen (r;filter <test>))
#let [(^open) <Number>
(^open) <Order>]]
(test "" (and (<= x (:: <Interval> bottom))
(>= x (:: <Interval> top)))))]
- ["Nat" R;nat Number<Nat> Order<Nat> Interval<Nat> (function [_] true)]
- ["Int" R;int Number<Int> Order<Int> Interval<Int> (function [_] true)]
+ ["Nat" r;nat Number<Nat> Order<Nat> Interval<Nat> (function [_] true)]
+ ["Int" r;int Number<Int> Order<Int> Interval<Int> (function [_] true)]
## Both min and max values will be positive (thus, greater than zero)
- ["Frac" R;frac Number<Frac> Order<Frac> Interval<Frac> (f.> 0.0)]
- ["Deg" R;deg Number<Deg> Order<Deg> Interval<Deg> (function [_] true)]
+ ["Frac" r;frac Number<Frac> Order<Frac> Interval<Frac> (f.> 0.0)]
+ ["Deg" r;deg Number<Deg> Order<Deg> Interval<Deg> (function [_] true)]
)
(do-template [category rand-gen <Number> <Order> <Monoid> <cap> <test>]
[(context: (format "[" category "] " "Monoid")
- [x (|> rand-gen (:: @ map (|>. (:: <Number> abs) <cap>)) (R;filter <test>))
+ [x (|> rand-gen (:: @ map (|>. (:: <Number> abs) <cap>)) (r;filter <test>))
#let [(^open) <Number>
(^open) <Order>
(^open) <Monoid>]]
@@ -91,22 +91,22 @@
(= x (compose x identity))
(= identity (compose identity identity)))))]
- ["Nat/Add" R;nat Number<Nat> Order<Nat> Add@Monoid<Nat> (n.% +1000) (function [_] true)]
- ["Nat/Mul" R;nat Number<Nat> Order<Nat> Mul@Monoid<Nat> (n.% +1000) (function [_] true)]
- ["Nat/Min" R;nat Number<Nat> Order<Nat> Min@Monoid<Nat> (n.% +1000) (function [_] true)]
- ["Nat/Max" R;nat Number<Nat> Order<Nat> Max@Monoid<Nat> (n.% +1000) (function [_] true)]
- ["Int/Add" R;int Number<Int> Order<Int> Add@Monoid<Int> (i.% 1000) (function [_] true)]
- ["Int/Mul" R;int Number<Int> Order<Int> Mul@Monoid<Int> (i.% 1000) (function [_] true)]
- ["Int/Min" R;int Number<Int> Order<Int> Min@Monoid<Int> (i.% 1000) (function [_] true)]
- ["Int/Max" R;int Number<Int> Order<Int> Max@Monoid<Int> (i.% 1000) (function [_] true)]
- ["Frac/Add" R;frac Number<Frac> Order<Frac> Add@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
- ["Frac/Mul" R;frac Number<Frac> Order<Frac> Mul@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
- ["Frac/Min" R;frac Number<Frac> Order<Frac> Min@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
- ["Frac/Max" R;frac Number<Frac> Order<Frac> Max@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
- ["Deg/Add" R;deg Number<Deg> Order<Deg> Add@Monoid<Deg> (d.% .125) (function [_] true)]
- ## ["Deg/Mul" R;deg Number<Deg> Order<Deg> Mul@Monoid<Deg> (d.% .125) (function [_] true)]
- ["Deg/Min" R;deg Number<Deg> Order<Deg> Min@Monoid<Deg> (d.% .125) (function [_] true)]
- ["Deg/Max" R;deg Number<Deg> Order<Deg> Max@Monoid<Deg> (d.% .125) (function [_] true)]
+ ["Nat/Add" r;nat Number<Nat> Order<Nat> Add@Monoid<Nat> (n.% +1000) (function [_] true)]
+ ["Nat/Mul" r;nat Number<Nat> Order<Nat> Mul@Monoid<Nat> (n.% +1000) (function [_] true)]
+ ["Nat/Min" r;nat Number<Nat> Order<Nat> Min@Monoid<Nat> (n.% +1000) (function [_] true)]
+ ["Nat/Max" r;nat Number<Nat> Order<Nat> Max@Monoid<Nat> (n.% +1000) (function [_] true)]
+ ["Int/Add" r;int Number<Int> Order<Int> Add@Monoid<Int> (i.% 1000) (function [_] true)]
+ ["Int/Mul" r;int Number<Int> Order<Int> Mul@Monoid<Int> (i.% 1000) (function [_] true)]
+ ["Int/Min" r;int Number<Int> Order<Int> Min@Monoid<Int> (i.% 1000) (function [_] true)]
+ ["Int/Max" r;int Number<Int> Order<Int> Max@Monoid<Int> (i.% 1000) (function [_] true)]
+ ["Frac/Add" r;frac Number<Frac> Order<Frac> Add@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
+ ["Frac/Mul" r;frac Number<Frac> Order<Frac> Mul@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
+ ["Frac/Min" r;frac Number<Frac> Order<Frac> Min@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
+ ["Frac/Max" r;frac Number<Frac> Order<Frac> Max@Monoid<Frac> (f.% 1000.0) (f.> 0.0)]
+ ["Deg/Add" r;deg Number<Deg> Order<Deg> Add@Monoid<Deg> (d.% .125) (function [_] true)]
+ ## ["Deg/Mul" r;deg Number<Deg> Order<Deg> Mul@Monoid<Deg> (d.% .125) (function [_] true)]
+ ["Deg/Min" r;deg Number<Deg> Order<Deg> Min@Monoid<Deg> (d.% .125) (function [_] true)]
+ ["Deg/Max" r;deg Number<Deg> Order<Deg> Max@Monoid<Deg> (d.% .125) (function [_] true)]
)
(do-template [<category> <rand-gen> <Eq> <Codec>]
@@ -122,30 +122,30 @@
(#;Left _)
false))))]
- ["Nat/Binary" R;nat Eq<Nat> Binary@Codec<Text,Nat>]
- ["Nat/Octal" R;nat Eq<Nat> Octal@Codec<Text,Nat>]
- ["Nat/Decimal" R;nat Eq<Nat> Codec<Text,Nat>]
- ["Nat/Hex" R;nat Eq<Nat> Hex@Codec<Text,Nat>]
-
- ["Int/Binary" R;int Eq<Int> Binary@Codec<Text,Int>]
- ["Int/Octal" R;int Eq<Int> Octal@Codec<Text,Int>]
- ["Int/Decimal" R;int Eq<Int> Codec<Text,Int>]
- ["Int/Hex" R;int Eq<Int> Hex@Codec<Text,Int>]
-
- ["Deg/Binary" R;deg Eq<Deg> Binary@Codec<Text,Deg>]
- ["Deg/Octal" R;deg Eq<Deg> Octal@Codec<Text,Deg>]
- ["Deg/Decimal" R;deg Eq<Deg> Codec<Text,Deg>]
- ["Deg/Hex" R;deg Eq<Deg> Hex@Codec<Text,Deg>]
-
- ["Frac/Binary" R;frac Eq<Frac> Binary@Codec<Text,Frac>]
- ["Frac/Octal" R;frac Eq<Frac> Octal@Codec<Text,Frac>]
- ["Frac/Decimal" R;frac Eq<Frac> Codec<Text,Frac>]
- ["Frac/Hex" R;frac Eq<Frac> Hex@Codec<Text,Frac>]
+ ["Nat/Binary" r;nat Eq<Nat> Binary@Codec<Text,Nat>]
+ ["Nat/Octal" r;nat Eq<Nat> Octal@Codec<Text,Nat>]
+ ["Nat/Decimal" r;nat Eq<Nat> Codec<Text,Nat>]
+ ["Nat/Hex" r;nat Eq<Nat> Hex@Codec<Text,Nat>]
+
+ ["Int/Binary" r;int Eq<Int> Binary@Codec<Text,Int>]
+ ["Int/Octal" r;int Eq<Int> Octal@Codec<Text,Int>]
+ ["Int/Decimal" r;int Eq<Int> Codec<Text,Int>]
+ ["Int/Hex" r;int Eq<Int> Hex@Codec<Text,Int>]
+
+ ["Deg/Binary" r;deg Eq<Deg> Binary@Codec<Text,Deg>]
+ ["Deg/Octal" r;deg Eq<Deg> Octal@Codec<Text,Deg>]
+ ["Deg/Decimal" r;deg Eq<Deg> Codec<Text,Deg>]
+ ["Deg/Hex" r;deg Eq<Deg> Hex@Codec<Text,Deg>]
+
+ ["Frac/Binary" r;frac Eq<Frac> Binary@Codec<Text,Frac>]
+ ["Frac/Octal" r;frac Eq<Frac> Octal@Codec<Text,Frac>]
+ ["Frac/Decimal" r;frac Eq<Frac> Codec<Text,Frac>]
+ ["Frac/Hex" r;frac Eq<Frac> Hex@Codec<Text,Frac>]
)
(context: "Can convert frac values to/from their bit patterns."
- [raw R;frac
- factor (|> R;nat (:: @ map (|>. (n.% +1000) (n.max +1))))
+ [raw r;frac
+ factor (|> r;nat (:: @ map (|>. (n.% +1000) (n.max +1))))
#let [sample (|> factor nat-to-int int-to-frac (f.* raw))]]
(test "Can convert frac values to/from their bit patterns."
(|> sample frac-to-bits bits-to-frac (f.= sample))))
diff --git a/stdlib/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux
index 78155e061..5fb5f6cfe 100644
--- a/stdlib/test/test/lux/data/number/complex.lux
+++ b/stdlib/test/test/lux/data/number/complex.lux
@@ -11,7 +11,7 @@
(coll [list "List/" Fold<List> Functor<List>])
[product])
[math]
- ["R" math/random])
+ ["r" math/random])
lux/test)
## Based on org.apache.commons.math4.complex.Complex
@@ -29,16 +29,16 @@
(f.< margin imgn-dist))))
(def: gen-dim
- (R;Random Frac)
- (do R;Monad<Random>
- [factor (|> R;nat (:: @ map (|>. (n.% +1000) (n.max +1))))
- measure (|> R;frac (R;filter (f.> 0.0)))]
+ (r;Random Frac)
+ (do r;Monad<Random>
+ [factor (|> r;nat (:: @ map (|>. (n.% +1000) (n.max +1))))
+ measure (|> r;frac (r;filter (f.> 0.0)))]
(wrap (f.* (|> factor nat-to-int int-to-frac)
measure))))
(def: gen-complex
- (R;Random &;Complex)
- (do R;Monad<Random>
+ (r;Random &;Complex)
+ (do r;Monad<Random>
[real gen-dim
imaginary gen-dim]
(wrap (&;complex real imaginary))))
@@ -180,7 +180,7 @@
(context: "Complex roots"
[sample gen-complex
- degree (|> R;nat (:: @ map (|>. (n.max +1) (n.% +5))))]
+ degree (|> r;nat (:: @ map (|>. (n.max +1) (n.% +5))))]
(test "Can calculate the N roots for any complex number."
(|> sample
(&;nth-roots degree)
diff --git a/stdlib/test/test/lux/data/number/ratio.lux b/stdlib/test/test/lux/data/number/ratio.lux
index a2eb4f53d..20090fc8c 100644
--- a/stdlib/test/test/lux/data/number/ratio.lux
+++ b/stdlib/test/test/lux/data/number/ratio.lux
@@ -9,20 +9,20 @@
["&" number/ratio "&/" Number<Ratio>]
(coll [list "List/" Fold<List> Functor<List>])
[product])
- ["R" math/random])
+ ["r" math/random])
lux/test)
(def: gen-part
- (R;Random Nat)
- (|> R;nat (:: R;Monad<Random> map (|>. (n.% +1000) (n.max +1)))))
+ (r;Random Nat)
+ (|> r;nat (:: r;Monad<Random> map (|>. (n.% +1000) (n.max +1)))))
(def: gen-ratio
- (R;Random &;Ratio)
- (do R;Monad<Random>
+ (r;Random &;Ratio)
+ (do r;Monad<Random>
[numerator gen-part
denominator (|> gen-part
- (R;filter (|>. (n.= +0) not))
- (R;filter (. not (n.= numerator))))]
+ (r;filter (|>. (n.= +0) not))
+ (r;filter (. not (n.= numerator))))]
(wrap (&;ratio numerator denominator))))
(context: "Normalization"
diff --git a/stdlib/test/test/lux/data/text/lexer.lux b/stdlib/test/test/lux/data/text/lexer.lux
index 37f915e6c..39c171442 100644
--- a/stdlib/test/test/lux/data/text/lexer.lux
+++ b/stdlib/test/test/lux/data/text/lexer.lux
@@ -4,8 +4,8 @@
pipe
["p" parser])
[io]
- (data ["R" result]
- [text "T/" Eq<Text>]
+ (data ["E" error]
+ [text "text/" Eq<Text>]
text/format
["&" text/lexer]
(coll [list]))
@@ -14,40 +14,40 @@
## [Utils]
(def: (should-fail input)
- (All [a] (-> (R;Result a) Bool))
+ (All [a] (-> (E;Error a) Bool))
(case input
(#;Left _) true
_ false))
(def: (should-passT test input)
- (-> Text (R;Result Text) Bool)
+ (-> Text (E;Error Text) Bool)
(case input
(#;Right output)
- (T/= test output)
+ (text/= test output)
_
false))
(def: (should-passL test input)
- (-> (List Text) (R;Result (List Text)) Bool)
- (let [(^open "L/") (list;Eq<List> text;Eq<Text>)]
+ (-> (List Text) (E;Error (List Text)) Bool)
+ (let [(^open "list/") (list;Eq<List> text;Eq<Text>)]
(case input
(#;Right output)
- (L/= test output)
+ (list/= test output)
_
false)))
(def: (should-passE test input)
- (-> (Either Text Text) (R;Result (Either Text Text)) Bool)
+ (-> (Either Text Text) (E;Error (Either Text Text)) Bool)
(case input
(#;Right output)
(case [test output]
[(#;Left test) (#;Left output)]
- (T/= test output)
+ (text/= test output)
[(#;Right test) (#;Right output)]
- (T/= test output)
+ (text/= test output)
_
false)
@@ -73,7 +73,7 @@
[size (|> r;nat (:: @ map (|>. (n.% +100) (n.max +10))))
sample (r;text size)
non-sample (|> (r;text size)
- (r;filter (|>. (T/= sample) not)))]
+ (r;filter (|>. (text/= sample) not)))]
($_ seq
(test "Can find literal text fragments."
(and (|> (&;run sample
diff --git a/stdlib/test/test/lux/host.js.lux b/stdlib/test/test/lux/host.js.lux
index 93e90bbfe..c7d65343a 100644
--- a/stdlib/test/test/lux/host.js.lux
+++ b/stdlib/test/test/lux/host.js.lux
@@ -4,7 +4,7 @@
(control ["M" monad #+ do Monad])
(data text/format)
["&" host]
- ["R" math/random])
+ ["r" math/random])
lux/test)
(context: "JavaScript operations"
diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux
index ff21fd0c9..64bdf5f1c 100644
--- a/stdlib/test/test/lux/macro/code.lux
+++ b/stdlib/test/test/lux/macro/code.lux
@@ -5,7 +5,7 @@
(data [text "T/" Eq<Text>]
text/format
[number])
- ["R" math/random]
+ ["r" math/random]
(macro ["&" code]))
lux/test)
diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux
index e988a0103..b159bf999 100644
--- a/stdlib/test/test/lux/macro/syntax.lux
+++ b/stdlib/test/test/lux/macro/syntax.lux
@@ -9,8 +9,8 @@
[number]
[bool]
[ident]
- ["E" result])
- ["R" math/random]
+ ["E" error])
+ ["r" math/random]
[macro]
(macro [code]
["s" syntax #+ syntax: Syntax]))
@@ -45,7 +45,7 @@
false))
(def: (fails? input)
- (All [a] (-> (E;Result a) Bool))
+ (All [a] (-> (E;Error a) Bool))
(case input
(#;Left _)
true
diff --git a/stdlib/test/test/lux/math/logic/continuous.lux b/stdlib/test/test/lux/math/logic/continuous.lux
index 4b2af88f3..1c6ed01a4 100644
--- a/stdlib/test/test/lux/math/logic/continuous.lux
+++ b/stdlib/test/test/lux/math/logic/continuous.lux
@@ -2,13 +2,13 @@
lux
(lux [io]
(control [monad #+ do Monad])
- ["R" math/random]
+ ["r" math/random]
["&" math/logic/continuous])
lux/test)
(context: "Operations"
- [left R;deg
- right R;deg]
+ [left r;deg
+ right r;deg]
($_ seq
(test "AND is the minimum."
(let [result (&;~and left right)]
diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux
index 5f10696c1..41a8f090a 100644
--- a/stdlib/test/test/lux/math/logic/fuzzy.lux
+++ b/stdlib/test/test/lux/math/logic/fuzzy.lux
@@ -7,14 +7,14 @@
[bool "B/" Eq<Bool>]
[number]
text/format)
- ["R" math/random]
+ ["r" math/random]
(math/logic ["&" fuzzy]
continuous))
lux/test)
(do-template [<desc> <hash> <gen> <triangle> <lt> <lte> <gt> <gte>]
[(context: (format "[" <desc> "] " "Triangles")
- [values (R;set <hash> +3 <gen>)
+ [values (r;set <hash> +3 <gen>)
#let [[x y z] (case (set;to-list values)
(^ (list x y z))
[x y z]
@@ -48,13 +48,13 @@
(<gte> top sample))))
))]
- ["Frac" number;Hash<Frac> R;frac &;f.triangle f.< f.<= f.> f.>=]
- ["Deg" number;Hash<Deg> R;deg &;d.triangle d.< d.<= d.> d.>=]
+ ["Frac" number;Hash<Frac> r;frac &;f.triangle f.< f.<= f.> f.>=]
+ ["Deg" number;Hash<Deg> r;deg &;d.triangle d.< d.<= d.> d.>=]
)
(do-template [<desc> <hash> <gen> <trapezoid> <lt> <lte> <gt> <gte>]
[(context: (format "[" <desc> "] " "Trapezoids")
- [values (R;set <hash> +4 <gen>)
+ [values (r;set <hash> +4 <gen>)
#let [[w x y z] (case (set;to-list values)
(^ (list w x y z))
[w x y z]
@@ -94,29 +94,29 @@
(<gte> top sample))))
))]
- ["Frac" number;Hash<Frac> R;frac &;f.trapezoid f.< f.<= f.> f.>=]
- ["Deg" number;Hash<Deg> R;deg &;d.trapezoid d.< d.<= d.> d.>=]
+ ["Frac" number;Hash<Frac> r;frac &;f.trapezoid f.< f.<= f.> f.>=]
+ ["Deg" number;Hash<Deg> r;deg &;d.trapezoid d.< d.<= d.> d.>=]
)
(context: "Gaussian"
- [deviation (|> R;frac (R;filter (f.> 0.0)))
- center R;frac
+ [deviation (|> r;frac (r;filter (f.> 0.0)))
+ center r;frac
#let [gaussian (&;gaussian deviation center)]]
(test "The center value will always have maximum membership."
(d.= ~true (&;membership center gaussian))))
(def: gen-triangle
- (R;Random (&;Fuzzy Frac))
- (do R;Monad<Random>
- [x R;frac
- y R;frac
- z R;frac]
+ (r;Random (&;Fuzzy Frac))
+ (do r;Monad<Random>
+ [x r;frac
+ y r;frac
+ z r;frac]
(wrap (&;f.triangle x y z))))
(context: "Combinators"
[left gen-triangle
right gen-triangle
- sample R;frac]
+ sample r;frac]
($_ seq
(test "Union membership as as high as membership in any of its members."
(let [combined (&;union left right)
@@ -147,7 +147,7 @@
(context: "From predicates and sets"
[#let [set-10 (set;from-list number;Hash<Nat> (list;n.range +0 +10))]
- sample (|> R;nat (:: @ map (n.% +20)))]
+ sample (|> r;nat (:: @ map (n.% +20)))]
($_ seq
(test "Values that satisfy a predicate have membership = 1.
Values that don't have membership = 0."
@@ -162,8 +162,8 @@
(context: "Thresholds"
[fuzzy gen-triangle
- sample R;frac
- threshold R;deg
+ sample r;frac
+ threshold r;deg
#let [vip-fuzzy (&;cut threshold fuzzy)
member? (&;to-predicate threshold fuzzy)]]
($_ seq
diff --git a/stdlib/test/test/lux/time/date.lux b/stdlib/test/test/lux/time/date.lux
index a73001026..baac8d22c 100644
--- a/stdlib/test/test/lux/time/date.lux
+++ b/stdlib/test/test/lux/time/date.lux
@@ -3,7 +3,7 @@
(lux [io]
(control [monad #+ do Monad]
[pipe])
- (data ["R" result])
+ (data ["E" error])
(math ["r" random "r/" Monad<Random>])
(time ["@;" instant]
["@" date]))
@@ -118,8 +118,8 @@
(|> sample
@/encode
@/decode
- (pipe;case> (#R;Success decoded)
+ (pipe;case> (#E;Success decoded)
(@/= sample decoded)
- (#R;Error error)
+ (#E;Error error)
false))))
diff --git a/stdlib/test/test/lux/time/duration.lux b/stdlib/test/test/lux/time/duration.lux
index 4a674420e..be0637ab7 100644
--- a/stdlib/test/test/lux/time/duration.lux
+++ b/stdlib/test/test/lux/time/duration.lux
@@ -2,7 +2,7 @@
lux
(lux [io]
(control [monad #+ do Monad])
- (data ["R" result])
+ (data ["E" error])
(math ["r" random])
(time ["@" duration]))
lux/test)
@@ -66,7 +66,7 @@
#let [(^open "@/") @;Eq<Duration>
(^open "@/") @;Codec<Text,Duration>]]
(test "Can encode/decode durations."
- (R;default false
- (do R;Monad<Result>
+ (E;default false
+ (do E;Monad<Error>
[decoded (|> sample @/encode @/decode)]
(wrap (@/= sample decoded))))))
diff --git a/stdlib/test/test/lux/time/instant.lux b/stdlib/test/test/lux/time/instant.lux
index c686de5b7..df59f0743 100644
--- a/stdlib/test/test/lux/time/instant.lux
+++ b/stdlib/test/test/lux/time/instant.lux
@@ -5,7 +5,7 @@
pipe)
(data [text]
text/format
- ["R" result]
+ ["E" error]
[number "Int/" Number<Int>])
(math ["r" random])
(time ["@" instant]
@@ -75,8 +75,8 @@
(|> sample
@/encode
@/decode
- (case> (#R;Success decoded)
+ (case> (#E;Success decoded)
(@/= sample decoded)
- (#R;Error error)
+ (#E;Error error)
false))))
diff --git a/stdlib/test/test/lux/type.lux b/stdlib/test/test/lux/type.lux
index 8c149e3f4..617921e33 100644
--- a/stdlib/test/test/lux/type.lux
+++ b/stdlib/test/test/lux/type.lux
@@ -8,39 +8,39 @@
[number]
[maybe]
(coll [list]))
- ["R" math/random]
+ ["r" math/random]
["&" type])
lux/test)
## [Utils]
(def: gen-name
- (R;Random Text)
- (do R;Monad<Random>
- [size (|> R;nat (:: @ map (n.% +10)))]
- (R;text size)))
+ (r;Random Text)
+ (do r;Monad<Random>
+ [size (|> r;nat (:: @ map (n.% +10)))]
+ (r;text size)))
(def: gen-ident
- (R;Random Ident)
- (R;seq gen-name gen-name))
+ (r;Random Ident)
+ (r;seq gen-name gen-name))
(def: gen-type
- (R;Random Type)
- (let [(^open "R/") R;Monad<Random>]
- (R;rec (function [gen-type]
- ($_ R;alt
- (R;seq gen-name (R/wrap (list)))
+ (r;Random Type)
+ (let [(^open "R/") r;Monad<Random>]
+ (r;rec (function [gen-type]
+ ($_ r;alt
+ (r;seq gen-name (R/wrap (list)))
(R/wrap [])
(R/wrap [])
- (R;seq gen-type gen-type)
- (R;seq gen-type gen-type)
- (R;seq gen-type gen-type)
- R;nat
- R;nat
- R;nat
- (R;seq (R/wrap (list)) gen-type)
- (R;seq (R/wrap (list)) gen-type)
- (R;seq gen-type gen-type)
- (R;seq gen-ident gen-type)
+ (r;seq gen-type gen-type)
+ (r;seq gen-type gen-type)
+ (r;seq gen-type gen-type)
+ r;nat
+ r;nat
+ r;nat
+ (r;seq (R/wrap (list)) gen-type)
+ (r;seq (R/wrap (list)) gen-type)
+ (r;seq gen-type gen-type)
+ (r;seq gen-ident gen-type)
)))))
## [Tests]
@@ -79,9 +79,9 @@
(&;un-name aliased)))))))
(context: "Type construction [structs]"
- [size (|> R;nat (:: @ map (n.% +3)))
+ [size (|> r;nat (:: @ map (n.% +3)))
members (|> gen-type
- (R;filter (function [type]
+ (r;filter (function [type]
(case type
(^or (#;Sum _) (#;Product _))
false
@@ -108,10 +108,10 @@
)))
(context: "Type construction [parameterized]"
- [size (|> R;nat (:: @ map (n.% +3)))
+ [size (|> r;nat (:: @ map (n.% +3)))
members (M;seq @ (list;repeat size gen-type))
extra (|> gen-type
- (R;filter (function [type]
+ (r;filter (function [type]
(case type
(^or (#;Function _) (#;Apply _))
false
@@ -132,9 +132,9 @@
))
(context: "Type construction [higher order]"
- [size (|> R;nat (:: @ map (n.% +3)))
+ [size (|> r;nat (:: @ map (n.% +3)))
extra (|> gen-type
- (R;filter (function [type]
+ (r;filter (function [type]
(case type
(^or (#;UnivQ _) (#;ExQ _))
false
diff --git a/stdlib/test/test/lux/type/auto.lux b/stdlib/test/test/lux/type/auto.lux
index f12d97c75..55e374c50 100644
--- a/stdlib/test/test/lux/type/auto.lux
+++ b/stdlib/test/test/lux/type/auto.lux
@@ -10,14 +10,14 @@
[bool "B/" Eq<Bool>]
maybe
(coll [list]))
- ["R" math/random]
+ ["r" math/random]
[type]
type/auto)
lux/test)
(context: "Automatic structure selection"
- [x R;nat
- y R;nat]
+ [x r;nat
+ y r;nat]
($_ seq
(test "Can automatically select first-order structures."
(let [(^open "L/") (list;Eq<List> number;Eq<Nat>)]
diff --git a/stdlib/test/test/lux/world/blob.lux b/stdlib/test/test/lux/world/blob.lux
index 23dcd889c..5a616f3e4 100644
--- a/stdlib/test/test/lux/world/blob.lux
+++ b/stdlib/test/test/lux/world/blob.lux
@@ -4,19 +4,19 @@
(control [monad #+ do]
[pipe])
(data [bit]
- ["R" result]
+ ["E" error]
(coll [list]))
(world ["@" blob])
["r" math/random])
lux/test)
(def: (succeed result)
- (-> (R;Result Bool) Bool)
+ (-> (E;Error Bool) Bool)
(case result
- (#R;Error _)
+ (#E;Error _)
false
- (#R;Success output)
+ (#E;Success output)
output))
(def: #export (blob size)
@@ -28,7 +28,7 @@
(if (n.< size idx)
(do @
[byte r;nat]
- (exec (R;assume (@;write-8 idx byte blob))
+ (exec (E;assume (@;write-8 idx byte blob))
(recur (n.inc idx))))
(wrap blob))))))
@@ -52,39 +52,39 @@
value-32 (n.% (bit;shift-left +32 +1) value)
value-64 value
slice-size (|> to (n.- from) n.inc)
- random-slice (R;assume (@;slice from to random-blob))]]
+ random-slice (E;assume (@;slice from to random-blob))]]
($_ seq
(test "Has equality."
(and (:: @;Eq<Blob> = clean-blob clean-blob)
(:: @;Eq<Blob> =
- (R;assume (@;slice from to clean-blob))
- (R;assume (@;slice from to clean-blob)))))
+ (E;assume (@;slice from to clean-blob))
+ (E;assume (@;slice from to clean-blob)))))
(test "Can get size of blob."
(n.= blob-size size))
(test "Can read/write 8-bit values."
(succeed
- (do R;Monad<Result>
+ (do E;Monad<Error>
[_ (@;write-8 idx value-8 clean-blob)
output-8 (@;read-8 idx clean-blob)]
(wrap (n.= value-8 output-8)))))
(test "Can read/write 16-bit values."
(or (n.>= size (n.+ +1 idx))
(succeed
- (do R;Monad<Result>
+ (do E;Monad<Error>
[_ (@;write-16 idx value-16 clean-blob)
output-16 (@;read-16 idx clean-blob)]
(wrap (n.= value-16 output-16))))))
(test "Can read/write 32-bit values."
(or (n.>= size (n.+ +3 idx))
(succeed
- (do R;Monad<Result>
+ (do E;Monad<Error>
[_ (@;write-32 idx value-32 clean-blob)
output-32 (@;read-32 idx clean-blob)]
(wrap (n.= value-32 output-32))))))
(test "Can read/write 64-bit values."
(or (n.>= size (n.+ +7 idx))
(succeed
- (do R;Monad<Result>
+ (do E;Monad<Error>
[_ (@;write-64 idx value-64 clean-blob)
output-64 (@;read-64 idx clean-blob)]
(wrap (n.= value-64 output-64))))))
@@ -94,7 +94,7 @@
(let [loop-recur recur]
(if (n.< slice-size idx)
(and (succeed
- (do R;Monad<Result>
+ (do E;Monad<Error>
[reference (@;read-8 (n.+ from idx) random-blob)
sample (@;read-8 idx random-slice)]
(wrap (n.= reference sample))))
@@ -103,5 +103,5 @@
(test "Slicing the whole blob does not change anything."
(:: @;Eq<Blob> =
random-blob
- (R;assume (@;slice +0 (n.dec blob-size) random-blob))))
+ (E;assume (@;slice +0 (n.dec blob-size) random-blob))))
))
diff --git a/stdlib/test/test/lux/world/file.lux b/stdlib/test/test/lux/world/file.lux
index 3e653d0b1..32fa33d7d 100644
--- a/stdlib/test/test/lux/world/file.lux
+++ b/stdlib/test/test/lux/world/file.lux
@@ -4,7 +4,7 @@
(control [monad #+ do])
(concurrency ["P" promise]
["T" task])
- (data ["R" result]
+ (data ["E" error]
[text]
text/format
[number])
@@ -41,7 +41,7 @@
(wrap (and (not pre) post
deleted? (not remains?))))]
(test "Can create/delete files."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +1 code)))]
result (do T;Monad<Task>
@@ -50,7 +50,7 @@
_ (@;delete file)]
(wrap (:: blob;Eq<Blob> = dataL output)))]
(test "Can write/read files."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +2 code)))]
result (do T;Monad<Task>
@@ -59,7 +59,7 @@
_ (@;delete file)]
(wrap (n.= file-size read-size)))]
(test "Can read file size."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +3 code)))]
result (do T;Monad<Task>
@@ -69,10 +69,10 @@
read-size (@;size file)
_ (@;delete file)]
(wrap (and (n.= (n.* +2 file-size) read-size)
- (:: blob;Eq<Blob> = dataL (R;assume (blob;slice +0 (n.dec file-size) output)))
- (:: blob;Eq<Blob> = dataR (R;assume (blob;slice file-size (n.dec read-size) output))))))]
+ (:: blob;Eq<Blob> = dataL (E;assume (blob;slice +0 (n.dec file-size) output)))
+ (:: blob;Eq<Blob> = dataR (E;assume (blob;slice file-size (n.dec read-size) output))))))]
(test "Can append to files."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [dir (format "temp_dir_" (%n (n.+ +4 code)))]
result (do T;Monad<Task>
@@ -84,7 +84,7 @@
(wrap (and (not pre) post
deleted? (not remains?))))]
(test "Can create/delete directories."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +5 code)))
dir (format "temp_dir_" (%n (n.+ +5 code)))]
@@ -100,7 +100,7 @@
(wrap (and file-is-file (not file-is-directory)
(not directory-is-file) directory-is-directory)))]
(test "Can differentiate files from directories."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +6 code)))
dir (format "temp_dir_" (%n (n.+ +6 code)))]
@@ -115,7 +115,7 @@
deleted-file
deleted-dir)))]
(test "Can create files inside of directories."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +7 code)))
dir (format "temp_dir_" (%n (n.+ +7 code)))]
@@ -133,7 +133,7 @@
_
false)))]
(test "Can list files inside a directory."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file (format "temp_file_" (%n (n.+ +8 code)))]
result (do T;Monad<Task>
@@ -144,7 +144,7 @@
(wrap (and was-modified?
(:: i;Eq<Instant> = last-modified time-read))))]
(test "Can change the time of last modification."
- (R;default false result)))
+ (E;default false result)))
(do P;Monad<Promise>
[#let [file0 (format "temp_file_" (%n (n.+ +9 code)) "0")
file1 (format "temp_file_" (%n (n.+ +9 code)) "1")]
@@ -158,5 +158,5 @@
(wrap (and pre moved? (not post)
confirmed? deleted?)))]
(test "Can move a file from one path to another."
- (R;default false result)))
+ (E;default false result)))
))
diff --git a/stdlib/test/test/lux/world/net/tcp.lux b/stdlib/test/test/lux/world/net/tcp.lux
index 4c975b4dd..cf390ef09 100644
--- a/stdlib/test/test/lux/world/net/tcp.lux
+++ b/stdlib/test/test/lux/world/net/tcp.lux
@@ -6,7 +6,7 @@
(concurrency ["P" promise]
["T" task]
[frp])
- (data ["R" result]
+ (data ["E" error]
[text]
text/format)
(world [blob]
@@ -66,5 +66,5 @@
(wrap (and from-worked?
to-worked?)))]
(test "Can communicate between client and server."
- (R;default false result)))
+ (E;default false result)))
))
diff --git a/stdlib/test/test/lux/world/net/udp.lux b/stdlib/test/test/lux/world/net/udp.lux
index 8af67bcd5..6bd43351e 100644
--- a/stdlib/test/test/lux/world/net/udp.lux
+++ b/stdlib/test/test/lux/world/net/udp.lux
@@ -6,7 +6,7 @@
(concurrency ["P" promise]
["T" task]
[frp])
- (data ["R" result]
+ (data ["E" error]
[text]
text/format)
(world [blob]
@@ -66,5 +66,5 @@
(wrap (and from-worked?
to-worked?)))]
(test "Can communicate between client and server."
- (R;default false result)))
+ (E;default false result)))
))
diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux
index e5cf4df6f..085275e62 100644
--- a/stdlib/test/tests.lux
+++ b/stdlib/test/tests.lux
@@ -28,7 +28,7 @@
["_;" parser])
(data ["_;" bit]
["_;" bool]
- ["_;" result]
+ ["_;" error]
["_;" ident]
["_;" identity]
["_;" maybe]