aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/control
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux/control/concurrency/actor.lux6
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux14
-rw-r--r--stdlib/source/test/lux/control/concurrency/promise.lux2
-rw-r--r--stdlib/source/test/lux/control/concurrency/semaphore.lux12
-rw-r--r--stdlib/source/test/lux/control/concurrency/stm.lux14
-rw-r--r--stdlib/source/test/lux/control/concurrency/thread.lux2
-rw-r--r--stdlib/source/test/lux/control/exception.lux2
-rw-r--r--stdlib/source/test/lux/control/function.lux6
-rw-r--r--stdlib/source/test/lux/control/function/memo.lux4
-rw-r--r--stdlib/source/test/lux/control/function/mixin.lux2
-rw-r--r--stdlib/source/test/lux/control/parser.lux64
-rw-r--r--stdlib/source/test/lux/control/parser/analysis.lux4
-rw-r--r--stdlib/source/test/lux/control/parser/binary.lux66
-rw-r--r--stdlib/source/test/lux/control/parser/cli.lux2
-rw-r--r--stdlib/source/test/lux/control/parser/code.lux24
-rw-r--r--stdlib/source/test/lux/control/parser/environment.lux4
-rw-r--r--stdlib/source/test/lux/control/parser/json.lux42
-rw-r--r--stdlib/source/test/lux/control/parser/synthesis.lux50
-rw-r--r--stdlib/source/test/lux/control/parser/text.lux82
-rw-r--r--stdlib/source/test/lux/control/parser/type.lux4
-rw-r--r--stdlib/source/test/lux/control/region.lux2
-rw-r--r--stdlib/source/test/lux/control/security/policy.lux20
-rw-r--r--stdlib/source/test/lux/control/state.lux2
-rw-r--r--stdlib/source/test/lux/control/thread.lux6
-rw-r--r--stdlib/source/test/lux/control/try.lux2
-rw-r--r--stdlib/source/test/lux/control/writer.lux2
26 files changed, 220 insertions, 220 deletions
diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux
index 0932fba3d..0f98a0b77 100644
--- a/stdlib/source/test/lux/control/concurrency/actor.lux
+++ b/stdlib/source/test/lux/control/concurrency/actor.lux
@@ -195,9 +195,9 @@
(_.cover' [/.actor]
verdict)))
(do !
- [num-events (:: ! map (|>> (n.% 10) inc) random.nat)
+ [num-events (\ ! map (|>> (n.% 10) inc) random.nat)
events (random.list num-events random.nat)
- num-observations (:: ! map (n.% num-events) random.nat)
+ num-observations (\ ! map (n.% num-events) random.nat)
#let [expected (list.take num-observations events)
sink (: (Atom (Row Nat))
(atom.atom row.empty))
@@ -235,6 +235,6 @@
#.None
false)]]
(_.cover' [/.observe]
- (and (:: (list.equivalence n.equivalence) = expected (row.to-list actual))
+ (and (\ (list.equivalence n.equivalence) = expected (row.to-list actual))
(not died?))))))
))))
diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux
index fd5e7be02..6b10df1d8 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -71,8 +71,8 @@
(case (io.run
(do (try.with io.monad)
[#let [[channel sink] (/.channel [])]
- _ (:: sink feed sample)
- _ (:: sink close)]
+ _ (\ sink feed sample)
+ _ (\ sink close)]
(wrap channel)))
(#try.Success channel)
(io.run
@@ -91,8 +91,8 @@
(case (io.run
(do (try.with io.monad)
[#let [[channel sink] (/.channel [])]
- _ (:: sink close)]
- (:: sink feed sample)))
+ _ (\ sink close)]
+ (\ sink feed sample)))
(#try.Success _)
false
@@ -139,7 +139,7 @@
listened (|> sink
atom.read
promise.future
- (:: ! map row.to-list))]
+ (\ ! map row.to-list))]
(_.cover' [/.Subscriber /.subscribe]
(and (list\= inputs
output)
@@ -183,7 +183,7 @@
(wrap (do promise.monad
[#let [[channel sink] (/.poll polling-delay (: (IO Nat) (io.io sample)))]
_ (promise.schedule total-delay (io.io []))
- _ (promise.future (:: sink close))
+ _ (promise.future (\ sink close))
actual (/.consume channel)]
(_.cover' [/.poll]
(and (list.every? (n.= sample) actual)
@@ -191,7 +191,7 @@
(wrap (do promise.monad
[#let [[channel sink] (/.periodic polling-delay)]
_ (promise.schedule total-delay (io.io []))
- _ (promise.future (:: sink close))
+ _ (promise.future (\ sink close))
actual (/.consume channel)]
(_.cover' [/.periodic]
(n.>= amount-of-polls (list.size actual)))))))
diff --git a/stdlib/source/test/lux/control/concurrency/promise.lux b/stdlib/source/test/lux/control/concurrency/promise.lux
index 852dca607..bd980cd55 100644
--- a/stdlib/source/test/lux/control/concurrency/promise.lux
+++ b/stdlib/source/test/lux/control/concurrency/promise.lux
@@ -48,7 +48,7 @@
Test
(<| (_.covering /._)
(do {! random.monad}
- [to-wait (|> random.nat (:: ! map (|>> (n.% 100) (n.max 10))))
+ [to-wait (|> random.nat (\ ! map (|>> (n.% 100) (n.max 10))))
#let [extra-time (n.* 2 to-wait)]
expected random.nat
dummy random.nat
diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux
index d1c6ac1e4..8c31b9796 100644
--- a/stdlib/source/test/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux
@@ -31,7 +31,7 @@
(_.with-cover [/.Semaphore]
($_ _.and
(do {! random.monad}
- [initial-open-positions (|> random.nat (:: ! map (|>> (n.% 10) (n.max 1))))
+ [initial-open-positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
#let [semaphore (/.semaphore initial-open-positions)]]
(wrap (do promise.monad
[result (promise.time-out 10 (/.wait semaphore))]
@@ -43,7 +43,7 @@
#.None
false)))))
(do {! random.monad}
- [initial-open-positions (|> random.nat (:: ! map (|>> (n.% 10) (n.max 1))))
+ [initial-open-positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
#let [semaphore (/.semaphore initial-open-positions)]]
(wrap (do {! promise.monad}
[_ (monad.map ! /.wait (list.repeat initial-open-positions semaphore))
@@ -56,7 +56,7 @@
#.None
true)))))
(do {! random.monad}
- [initial-open-positions (|> random.nat (:: ! map (|>> (n.% 10) (n.max 1))))
+ [initial-open-positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
#let [semaphore (/.semaphore initial-open-positions)]]
(wrap (do {! promise.monad}
[_ (monad.map ! /.wait (list.repeat initial-open-positions semaphore))
@@ -72,7 +72,7 @@
_
false)))))
(do {! random.monad}
- [initial-open-positions (|> random.nat (:: ! map (|>> (n.% 10) (n.max 1))))
+ [initial-open-positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
#let [semaphore (/.semaphore initial-open-positions)]]
(wrap (do promise.monad
[outcome (/.signal semaphore)]
@@ -90,7 +90,7 @@
(_.with-cover [/.Mutex]
($_ _.and
(do {! random.monad}
- [repetitions (|> random.nat (:: ! map (|>> (n.% 100) (n.max 10))))
+ [repetitions (|> random.nat (\ ! map (|>> (n.% 100) (n.max 10))))
#let [resource (atom.atom "")
expected-As (text.join-with "" (list.repeat repetitions "A"))
expected-Bs (text.join-with "" (list.repeat repetitions "B"))
@@ -147,7 +147,7 @@
_
false)))
(do {! random.monad}
- [limit (|> random.nat (:: ! map (|>> (n.% 10) (n.max 1))))
+ [limit (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
#let [barrier (/.barrier (maybe.assume (/.limit limit)))
resource (atom.atom "")]]
(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 234c9a64e..1e7dee4e4 100644
--- a/stdlib/source/test/lux/control/concurrency/stm.lux
+++ b/stdlib/source/test/lux/control/concurrency/stm.lux
@@ -27,7 +27,7 @@
(def: injection
(Injection /.STM)
- (:: /.monad wrap))
+ (\ /.monad wrap))
(def: comparison
(Comparison /.STM)
@@ -41,7 +41,7 @@
(do {! random.monad}
[dummy random.nat
expected random.nat
- iterations-per-process (|> random.nat (:: ! map (n.% 100)))]
+ iterations-per-process (|> random.nat (\ ! map (n.% 100)))]
($_ _.and
(_.with-cover [/.functor]
($functor.spec ..injection ..comparison /.functor))
@@ -51,7 +51,7 @@
($monad.spec ..injection ..comparison /.monad))
(wrap (do promise.monad
- [actual (/.commit (:: /.monad wrap expected))]
+ [actual (/.commit (\ /.monad wrap expected))]
(_.cover' [/.commit]
(n.= expected actual))))
(wrap (do promise.monad
@@ -84,13 +84,13 @@
[follower sink] (io.run (/.follow box))]
_ (/.commit (/.write expected box))
_ (/.commit (/.update (n.* 2) box))
- _ (promise.future (:: sink close))
+ _ (promise.future (\ sink close))
_ (/.commit (/.update (n.* 3) box))
changes (frp.consume follower)]
(_.cover' [/.follow]
- (:: (list.equivalence n.equivalence) =
- (list expected (n.* 2 expected))
- changes))))
+ (\ (list.equivalence n.equivalence) =
+ (list expected (n.* 2 expected))
+ changes))))
(wrap (let [var (/.var 0)]
(do {! promise.monad}
[_ (|> (list.repeat iterations-per-process [])
diff --git a/stdlib/source/test/lux/control/concurrency/thread.lux b/stdlib/source/test/lux/control/concurrency/thread.lux
index 7794be1b9..210ff4b1d 100644
--- a/stdlib/source/test/lux/control/concurrency/thread.lux
+++ b/stdlib/source/test/lux/control/concurrency/thread.lux
@@ -26,7 +26,7 @@
(do {! random.monad}
[dummy random.nat
expected random.nat
- delay (|> random.nat (:: ! map (n.% 100)))]
+ delay (|> random.nat (\ ! map (n.% 100)))]
($_ _.and
(_.cover [/.parallelism]
(n.> 0 /.parallelism))
diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux
index 2075913a5..7f0578c5d 100644
--- a/stdlib/source/test/lux/control/exception.lux
+++ b/stdlib/source/test/lux/control/exception.lux
@@ -28,7 +28,7 @@
[expected random.nat
wrong (|> random.nat (random.filter (|>> (n.= expected) not)))
assertion-succeeded? random.bit
- #let [report-element (:: ! map %.nat random.nat)]
+ #let [report-element (\ ! map %.nat random.nat)]
field0 report-element
value0 report-element
field1 report-element
diff --git a/stdlib/source/test/lux/control/function.lux b/stdlib/source/test/lux/control/function.lux
index 6e9fc74ac..5775b9085 100644
--- a/stdlib/source/test/lux/control/function.lux
+++ b/stdlib/source/test/lux/control/function.lux
@@ -20,8 +20,8 @@
Test
(do {! random.monad}
[expected random.nat
- f0 (:: ! map n.+ random.nat)
- f1 (:: ! map n.* random.nat)
+ f0 (\ ! map n.+ random.nat)
+ f1 (\ ! map n.* random.nat)
dummy random.nat
extra (|> random.nat (random.filter (|>> (n.= expected) not)))]
(<| (_.covering /._)
@@ -32,7 +32,7 @@
(n.= (left extra)
(right extra)))))
generator (: (Random (-> Nat Nat))
- (:: ! map n.- random.nat))]
+ (\ ! map n.- random.nat))]
(_.with-cover [/.monoid]
($monoid.spec equivalence /.monoid generator)))
diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux
index a19b9e6f9..6350320b5 100644
--- a/stdlib/source/test/lux/control/function/memo.lux
+++ b/stdlib/source/test/lux/control/function/memo.lux
@@ -50,7 +50,7 @@
Test
(<| (_.covering /._)
(do {! random.monad}
- [input (|> random.nat (:: ! map (|>> (n.% 5) (n.+ 23))))])
+ [input (|> random.nat (\ ! map (|>> (n.% 5) (n.+ 23))))])
(_.with-cover [/.Memo])
($_ _.and
(_.cover [/.closed /.none]
@@ -85,7 +85,7 @@
(: (//.Mixin Nat (State (Dictionary Nat Nat) Nat))
(function (factorial delegate recur input)
(case input
- (^or 0 1) (:: state.monad wrap 1)
+ (^or 0 1) (\ state.monad wrap 1)
_ (do state.monad
[output' (recur (dec input))]
(wrap (n.* input output')))))))
diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux
index c4d6040cd..e9308e5bb 100644
--- a/stdlib/source/test/lux/control/function/mixin.lux
+++ b/stdlib/source/test/lux/control/function/mixin.lux
@@ -25,7 +25,7 @@
Test
(<| (_.covering /._)
(do {! random.monad}
- [input (|> random.nat (:: ! map (|>> (n.% 6) (n.+ 20))))
+ [input (|> random.nat (\ ! map (|>> (n.% 6) (n.+ 20))))
dummy random.nat
shift (|> random.nat (random.filter (|>> (n.= dummy) not)))
#let [equivalence (: (Equivalence (/.Mixin Nat Nat))
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index 569e32621..6710faaab 100644
--- a/stdlib/source/test/lux/control/parser.lux
+++ b/stdlib/source/test/lux/control/parser.lux
@@ -88,7 +88,7 @@
Test
(do {! random.monad}
[expected0 random.nat
- variadic (:: ! map (|>> (n.max 1) (n.min 20)) random.nat)
+ variadic (\ ! map (|>> (n.max 1) (n.min 20)) random.nat)
expected+ (random.list variadic random.nat)
even0 (random.filter n.even? random.nat)
odd0 (random.filter n.odd? random.nat)
@@ -107,7 +107,7 @@
(and (|> (list\map code.nat expected+)
(/.run (/.some s.nat))
(match actual
- (:: (list.equivalence n.equivalence) = expected+ actual)))
+ (\ (list.equivalence n.equivalence) = expected+ actual)))
(|> (list\map (|>> .int code.int) expected+)
(/.run (/.some s.nat))
(match #.Nil
@@ -116,7 +116,7 @@
(and (|> (list\map code.nat expected+)
(/.run (/.many s.nat))
(match actual
- (:: (list.equivalence n.equivalence) = expected+ actual)))
+ (\ (list.equivalence n.equivalence) = expected+ actual)))
(|> (list (code.nat expected0))
(/.run (/.many s.nat))
(match (list actual)
@@ -178,8 +178,8 @@
(def: combinators-1
Test
(do {! random.monad}
- [variadic (:: ! map (|>> (n.max 1) (n.min 20)) random.nat)
- times (:: ! map (n.% variadic) random.nat)
+ [variadic (\ ! map (|>> (n.max 1) (n.min 20)) random.nat)
+ times (\ ! map (n.% variadic) random.nat)
expected random.nat
wrong (|> random.nat (random.filter (|>> (n.= expected) not)))
expected+ (random.list variadic random.nat)
@@ -189,9 +189,9 @@
(and (|> (list\map code.nat expected+)
(/.run (/.exactly times s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- (list.take times expected+)
- actual)))
+ (\ (list.equivalence n.equivalence) =
+ (list.take times expected+)
+ actual)))
(|> (list\map code.nat expected+)
(/.run (/.exactly (inc variadic) s.nat))
fails?)))
@@ -199,9 +199,9 @@
(and (|> (list\map code.nat expected+)
(/.run (/.at-least times s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- expected+
- actual)))
+ (\ (list.equivalence n.equivalence) =
+ expected+
+ actual)))
(|> (list\map code.nat expected+)
(/.run (/.at-least (inc variadic) s.nat))
fails?)))
@@ -209,44 +209,44 @@
(and (|> (list\map code.nat expected+)
(/.run (/.at-most times s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- (list.take times expected+)
- actual)))
+ (\ (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 n.equivalence) =
- expected+
- actual)))))
+ (\ (list.equivalence n.equivalence) =
+ expected+
+ actual)))))
(_.cover [/.between]
(and (|> (list\map code.nat expected+)
(/.run (/.between times variadic s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- expected+
- actual)))
+ (\ (list.equivalence n.equivalence) =
+ expected+
+ actual)))
(|> (list\map code.nat (list.take times expected+))
(/.run (/.between times variadic s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- (list.take times expected+)
- actual)))))
+ (\ (list.equivalence n.equivalence) =
+ (list.take times expected+)
+ actual)))))
(_.cover [/.sep-by]
(|> (list.interpose (code.text separator) (list\map code.nat expected+))
(/.run (/.sep-by (s.this! (code.text separator)) s.nat))
(match actual
- (:: (list.equivalence n.equivalence) =
- expected+
- actual))))
+ (\ (list.equivalence n.equivalence) =
+ expected+
+ actual))))
(_.cover [/.remaining]
(|> (list\map code.nat expected+)
(/.run /.remaining)
(match actual
- (:: (list.equivalence code.equivalence) =
- (list\map code.nat expected+)
- actual))))
+ (\ (list.equivalence code.equivalence) =
+ (list\map code.nat expected+)
+ actual))))
(_.cover [/.default]
- (and (|> (/.run (/.default wrong (:: /.monad wrap expected)) (list))
+ (and (|> (/.run (/.default wrong (\ /.monad wrap expected)) (list))
(match actual (n.= expected actual)))
(|> (/.run (/.default expected (: (Parser (List Code) Nat)
(/.fail "yolo")))
@@ -331,7 +331,7 @@
(def: injection
(Injection (All [a i] (Parser i a)))
- (:: /.monad wrap))
+ (\ /.monad wrap))
(def: comparison
(Comparison (All [a i] (Parser i a)))
@@ -360,7 +360,7 @@
($monad.spec ..injection ..comparison /.monad))
(_.cover [/.run]
- (|> (/.run (:: /.monad wrap expected) (list))
+ (|> (/.run (\ /.monad wrap expected) (list))
(match actual (n.= expected actual))))
(_.cover [/.fail]
(|> (list)
diff --git a/stdlib/source/test/lux/control/parser/analysis.lux b/stdlib/source/test/lux/control/parser/analysis.lux
index f09967760..d4b4e533f 100644
--- a/stdlib/source/test/lux/control/parser/analysis.lux
+++ b/stdlib/source/test/lux/control/parser/analysis.lux
@@ -52,12 +52,12 @@
[]
(`` ($_ _.and
(do {! random.monad}
- [expected (:: ! map (|>> analysis.bit) random.bit)]
+ [expected (\ ! map (|>> analysis.bit) random.bit)]
(_.cover [/.run /.any]
(|> (list expected)
(/.run /.any)
(case> (#try.Success actual)
- (:: analysis.equivalence = expected actual)
+ (\ analysis.equivalence = expected actual)
(#try.Failure _)
false))))
diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux
index 9e4c06f18..94225be79 100644
--- a/stdlib/source/test/lux/control/parser/binary.lux
+++ b/stdlib/source/test/lux/control/parser/binary.lux
@@ -90,7 +90,7 @@
(random.rec
(function (_ recur)
(let [random-sequence (do {! random.monad}
- [size (:: ! map (n.% 2) random.nat)]
+ [size (\ ! map (n.% 2) random.nat)]
(random.list size recur))]
($_ random.and
..random-location
@@ -107,7 +107,7 @@
random-sequence
random-sequence
(do {! random.monad}
- [size (:: ! map (n.% 2) random.nat)]
+ [size (\ ! map (n.% 2) random.nat)]
(random.list size (random.and recur recur)))
)))))))
@@ -126,8 +126,8 @@
(`` ($_ _.and
(~~ (template [<size> <parser> <format>]
[(do {! random.monad}
- [expected (:: ! map (i64.and (i64.mask <size>))
- random.nat)]
+ [expected (\ ! map (i64.and (i64.mask <size>))
+ random.nat)]
(_.cover [<size> <parser> <format>]
(|> (format.run <format> expected)
(/.run <parser>)
@@ -146,12 +146,12 @@
(`` ($_ _.and
(~~ (template [<parser> <format>]
[(do {! random.monad}
- [expected (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [expected (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [<parser> <format>]
(|> (format.run <format> expected)
(/.run <parser>)
(!expect (^multi (#try.Success actual)
- (:: binary.equivalence = expected actual))))))]
+ (\ binary.equivalence = expected actual))))))]
[/.binary/8 format.binary/8]
[/.binary/16 format.binary/16]
@@ -169,7 +169,7 @@
(|> (format.run <format> expected)
(/.run <parser>)
(!expect (^multi (#try.Success actual)
- (:: text.equivalence = expected actual))))))]
+ (\ text.equivalence = expected actual))))))]
[/.utf8/8 format.utf8/8]
[/.utf8/16 format.utf8/16]
@@ -189,7 +189,7 @@
(format.run (<format> format.nat))
(/.run (<parser> /.nat))
(!expect (^multi (#try.Success actual)
- (:: (row.equivalence n.equivalence) = expected actual))))))]
+ (\ (row.equivalence n.equivalence) = expected actual))))))]
[/.row/8 format.row/8]
[/.row/16 format.row/16]
@@ -208,7 +208,7 @@
(format.run <format>)
(/.run <parser>)
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual))))))]
+ (\ <equivalence> = expected actual))))))]
[/.bit format.bit random.bit bit.equivalence]
[/.nat format.nat random.nat n.equivalence]
@@ -221,13 +221,13 @@
(format.run format.frac)
(/.run /.frac)
(!expect (^multi (#try.Success actual)
- (or (:: frac.equivalence = expected actual)
+ (or (\ frac.equivalence = expected actual)
(and (frac.not-a-number? expected)
(frac.not-a-number? actual))))))))
(do {! random.monad}
- [expected (:: ! map (|>> (i64.and (i64.mask /.size/8))
- (n.max 2))
- random.nat)]
+ [expected (\ ! map (|>> (i64.and (i64.mask /.size/8))
+ (n.max 2))
+ random.nat)]
(_.cover [/.not-a-bit]
(|> expected
(format.run format.bits/8)
@@ -247,7 +247,7 @@
(format.run <format>)
(/.run <parser>)
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual))))))]
+ (\ <equivalence> = expected actual))))))]
[/.location format.location random-location location-equivalence]
[/.code format.code random-code code.equivalence]
@@ -261,14 +261,14 @@
(format.run <format>)
(/.run <parser>)
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual))))))]
+ (\ <equivalence> = expected actual))))))]
[/.maybe (/.maybe /.nat) format.maybe (format.maybe format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)]
[/.list (/.list /.nat) format.list (format.list format.nat) (random.list ..segment-size random.nat) (list.equivalence n.equivalence)]
[/.set (/.set n.hash /.nat) format.set (format.set format.nat) (random.set n.hash ..segment-size random.nat) set.equivalence]
[/.name /.name format.name format.name ..random-name name.equivalence]))
(do {! random.monad}
- [expected (:: ! map (list.repeat ..segment-size) random.nat)]
+ [expected (\ ! map (list.repeat ..segment-size) random.nat)]
(_.cover [/.set-elements-are-not-unique]
(|> expected
(format.run (format.list format.nat))
@@ -283,13 +283,13 @@
(/.run (: (/.Parser (Either Bit Nat))
(/.or /.bit /.nat)))
(!expect (^multi (#try.Success actual)
- (:: (sum.equivalence bit.equivalence n.equivalence) =
- expected
- actual))))))
+ (\ (sum.equivalence bit.equivalence n.equivalence) =
+ expected
+ actual))))))
(do {! random.monad}
- [tag (:: ! map (|>> (i64.and (i64.mask /.size/8))
- (n.max 2))
- random.nat)
+ [tag (\ ! map (|>> (i64.and (i64.mask /.size/8))
+ (n.max 2))
+ random.nat)
value random.bit]
(_.cover [/.invalid-tag]
(|> [tag value]
@@ -311,9 +311,9 @@
(<>.and /.nat
recur))))))
(!expect (^multi (#try.Success actual)
- (:: (list.equivalence n.equivalence) =
- expected
- actual))))))
+ (\ (list.equivalence n.equivalence) =
+ expected
+ actual))))))
)))
(def: #export test
@@ -327,22 +327,22 @@
(/.run /.any)
(!expect (#try.Success _))))
(do {! random.monad}
- [data (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [data (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [/.binary-was-not-fully-read]
(|> data
(/.run /.any)
(!expect (^multi (#try.Failure error)
(exception.match? /.binary-was-not-fully-read error))))))
(do {! random.monad}
- [expected (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [expected (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [/.segment format.segment format.run]
(|> expected
(format.run (format.segment ..segment-size))
(/.run (/.segment ..segment-size))
(!expect (^multi (#try.Success actual)
- (:: binary.equivalence = expected actual))))))
+ (\ binary.equivalence = expected actual))))))
(do {! random.monad}
- [data (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [data (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [/.end?]
(|> data
(/.run (do <>.monad
@@ -353,8 +353,8 @@
post))))
(!expect (#try.Success #1)))))
(do {! random.monad}
- [to-read (:: ! map (n.% (inc ..segment-size)) random.nat)
- data (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [to-read (\ ! map (n.% (inc ..segment-size)) random.nat)
+ data (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [/.Offset /.offset]
(|> data
(/.run (do <>.monad
@@ -368,8 +368,8 @@
(n.= ..segment-size nothing-left)))))
(!expect (#try.Success #1)))))
(do {! random.monad}
- [to-read (:: ! map (n.% (inc ..segment-size)) random.nat)
- data (:: ! map encoding.to-utf8 (random.ascii ..segment-size))]
+ [to-read (\ ! map (n.% (inc ..segment-size)) random.nat)
+ data (\ ! map encoding.to-utf8 (random.ascii ..segment-size))]
(_.cover [/.remaining]
(|> data
(/.run (do <>.monad
diff --git a/stdlib/source/test/lux/control/parser/cli.lux b/stdlib/source/test/lux/control/parser/cli.lux
index 1222b9de1..6be78b640 100644
--- a/stdlib/source/test/lux/control/parser/cli.lux
+++ b/stdlib/source/test/lux/control/parser/cli.lux
@@ -30,7 +30,7 @@
(<| (_.covering /._)
(_.with-cover [/.Parser])
(do {! random.monad}
- [expected (:: ! map n\encode random.nat)
+ [expected (\ ! map n\encode random.nat)
#let [random-dummy (random.filter (|>> (text\= expected) not)
(random.unicode 5))]
dummy random-dummy
diff --git a/stdlib/source/test/lux/control/parser/code.lux b/stdlib/source/test/lux/control/parser/code.lux
index 521704dec..3955d760f 100644
--- a/stdlib/source/test/lux/control/parser/code.lux
+++ b/stdlib/source/test/lux/control/parser/code.lux
@@ -44,7 +44,7 @@
(_.with-cover [/.Parser])
(`` ($_ _.and
(do {! random.monad}
- [expected (:: ! map code.bit random.bit)]
+ [expected (\ ! map code.bit random.bit)]
(_.cover [/.run]
(and (|> (/.run /.any (list expected))
(!expect (#try.Success _)))
@@ -53,12 +53,12 @@
(~~ (template [<query> <check> <random> <code> <equivalence>]
[(do {! random.monad}
[expected <random>
- dummy (|> <random> (random.filter (|>> (:: <equivalence> = expected) not)))]
+ dummy (|> <random> (random.filter (|>> (\ <equivalence> = expected) not)))]
($_ _.and
(_.cover [<query>]
(|> (/.run <query> (list (<code> expected)))
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual)))))
+ (\ <equivalence> = expected actual)))))
(_.cover [<check>]
(and (|> (/.run (<check> expected) (list (<code> expected)))
(!expect (#try.Success [])))
@@ -66,7 +66,7 @@
(!expect (#try.Failure _)))))
))]
- [/.any /.this! (:: ! map code.bit random.bit) function.identity code.equivalence]
+ [/.any /.this! (\ ! map code.bit random.bit) function.identity code.equivalence]
[/.bit /.bit! random.bit code.bit bit.equivalence]
[/.nat /.nat! random.nat code.nat nat.equivalence]
[/.int /.int! random.int code.int int.equivalence]
@@ -87,8 +87,8 @@
(list (<code> (list (code.nat expected-left)
(code.int expected-right)))))
(!expect (^multi (#try.Success [actual-left actual-right])
- (and (:: nat.equivalence = expected-left actual-left)
- (:: int.equivalence = expected-right actual-right)))))))]
+ (and (\ nat.equivalence = expected-left actual-left)
+ (\ int.equivalence = expected-right actual-right)))))))]
[/.form code.form]
[/.tuple code.tuple]
@@ -101,8 +101,8 @@
(list (code.record (list [(code.nat expected-left)
(code.int expected-right)]))))
(!expect (^multi (#try.Success [actual-left actual-right])
- (and (:: nat.equivalence = expected-left actual-left)
- (:: int.equivalence = expected-right actual-right)))))))
+ (and (\ nat.equivalence = expected-left actual-left)
+ (\ int.equivalence = expected-right actual-right)))))))
(do {! random.monad}
[expected-local random.nat
expected-global random.int]
@@ -111,10 +111,10 @@
/.int)
(list (code.int expected-global)))
(!expect (^multi (#try.Success [actual-local actual-global])
- (and (:: nat.equivalence = expected-local actual-local)
- (:: int.equivalence = expected-global actual-global)))))))
+ (and (\ nat.equivalence = expected-local actual-local)
+ (\ int.equivalence = expected-global actual-global)))))))
(do {! random.monad}
- [dummy (:: ! map code.bit random.bit)]
+ [dummy (\ ! map code.bit random.bit)]
(_.cover [/.end?]
(|> (/.run (do <>.monad
[pre /.end?
@@ -126,7 +126,7 @@
(!expect (^multi (#try.Success verdict)
verdict)))))
(do {! random.monad}
- [dummy (:: ! map code.bit random.bit)]
+ [dummy (\ ! map code.bit random.bit)]
(_.cover [/.end!]
(and (|> (/.run /.end! (list))
(!expect (#try.Success [])))
diff --git a/stdlib/source/test/lux/control/parser/environment.lux b/stdlib/source/test/lux/control/parser/environment.lux
index 89b174b47..2c2263862 100644
--- a/stdlib/source/test/lux/control/parser/environment.lux
+++ b/stdlib/source/test/lux/control/parser/environment.lux
@@ -29,7 +29,7 @@
[expected random.nat]
(_.cover [/.run]
(|> (/.run (//\wrap expected) /.empty)
- (:: try.functor map (n.= expected))
+ (\ try.functor map (n.= expected))
(try.default false))))
(do random.monad
[property (random.ascii/alpha 1)
@@ -38,7 +38,7 @@
(|> /.empty
(dictionary.put property expected)
(/.run (/.property property))
- (:: try.functor map (text\= expected))
+ (\ try.functor map (text\= expected))
(try.default false))))
(do random.monad
[property (random.ascii/alpha 1)]
diff --git a/stdlib/source/test/lux/control/parser/json.lux b/stdlib/source/test/lux/control/parser/json.lux
index 27c508bd5..e9bd03ef6 100644
--- a/stdlib/source/test/lux/control/parser/json.lux
+++ b/stdlib/source/test/lux/control/parser/json.lux
@@ -45,23 +45,23 @@
(_.with-cover [/.Parser])
(`` ($_ _.and
(do {! random.monad}
- [expected (:: ! map (|>> #json.String) (random.unicode 1))]
+ [expected (\ ! map (|>> #json.String) (random.unicode 1))]
(_.cover [/.run /.any]
(|> (/.run /.any expected)
(!expect (^multi (#try.Success actual)
- (:: json.equivalence = expected actual))))))
+ (\ json.equivalence = expected actual))))))
(_.cover [/.null]
(|> (/.run /.null #json.Null)
(!expect (#try.Success _))))
(~~ (template [<query> <test> <check> <random> <json> <equivalence>]
[(do {! random.monad}
[expected <random>
- dummy (|> <random> (random.filter (|>> (:: <equivalence> = expected) not)))]
+ dummy (|> <random> (random.filter (|>> (\ <equivalence> = expected) not)))]
($_ _.and
(_.cover [<query>]
(|> (/.run <query> (<json> expected))
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual)))))
+ (\ <equivalence> = expected actual)))))
(_.cover [<test>]
(and (|> (/.run (<test> expected) (<json> expected))
(!expect (#try.Success #1)))
@@ -86,7 +86,7 @@
(exception.match? /.unexpected-value error))))))
(do {! random.monad}
[expected (random.unicode 1)
- dummy (|> (random.unicode 1) (random.filter (|>> (:: text.equivalence = expected) not)))]
+ dummy (|> (random.unicode 1) (random.filter (|>> (\ text.equivalence = expected) not)))]
(_.cover [/.value-mismatch]
(|> (/.run (/.string! expected) (#json.String dummy))
(!expect (^multi (#try.Failure error)
@@ -96,22 +96,22 @@
(_.cover [/.nullable]
(and (|> (/.run (/.nullable /.string) #json.Null)
(!expect (^multi (#try.Success actual)
- (:: (maybe.equivalence text.equivalence) = #.None actual))))
+ (\ (maybe.equivalence text.equivalence) = #.None actual))))
(|> (/.run (/.nullable /.string) (#json.String expected))
(!expect (^multi (#try.Success actual)
- (:: (maybe.equivalence text.equivalence) = (#.Some expected) actual)))))))
+ (\ (maybe.equivalence text.equivalence) = (#.Some expected) actual)))))))
(do {! random.monad}
- [size (:: ! map (n.% 10) random.nat)
+ [size (\ ! map (n.% 10) random.nat)
expected (|> (random.unicode 1)
(random.list size)
- (:: ! map row.from-list))]
+ (\ ! map row.from-list))]
(_.cover [/.array]
(|> (/.run (/.array (<>.some /.string))
(#json.Array (row\map (|>> #json.String) expected)))
(!expect (^multi (#try.Success actual)
- (:: (row.equivalence text.equivalence) = expected (row.from-list actual)))))))
+ (\ (row.equivalence text.equivalence) = expected (row.from-list actual)))))))
(do {! random.monad}
- [expected (:: ! map (|>> #json.String) (random.unicode 1))]
+ [expected (\ ! map (|>> #json.String) (random.unicode 1))]
(_.cover [/.unconsumed-input]
(|> (/.run (/.array /.any) (#json.Array (row expected expected)))
(!expect (^multi (#try.Failure error)
@@ -125,12 +125,12 @@
expected-number ..safe-frac
expected-string (random.unicode 1)
[boolean-field number-field string-field] (|> (random.set text.hash 3 (random.unicode 3))
- (:: ! map (|>> set.to-list
- (case> (^ (list boolean-field number-field string-field))
- [boolean-field number-field string-field]
+ (\ ! map (|>> set.to-list
+ (case> (^ (list boolean-field number-field string-field))
+ [boolean-field number-field string-field]
- _
- (undefined)))))]
+ _
+ (undefined)))))]
(_.cover [/.object /.field]
(|> (/.run (/.object ($_ <>.and
(/.field boolean-field /.boolean)
@@ -142,11 +142,11 @@
[number-field (#json.Number expected-number)]
[string-field (#json.String expected-string)]))))
(!expect (^multi (#try.Success [actual-boolean actual-number actual-string])
- (and (:: bit.equivalence = expected-boolean actual-boolean)
- (:: frac.equivalence = expected-number actual-number)
- (:: text.equivalence = expected-string actual-string)))))))
+ (and (\ bit.equivalence = expected-boolean actual-boolean)
+ (\ frac.equivalence = expected-number actual-number)
+ (\ text.equivalence = expected-string actual-string)))))))
(do {! random.monad}
- [size (:: ! map (n.% 10) random.nat)
+ [size (\ ! map (n.% 10) random.nat)
keys (random.list size (random.unicode 1))
values (random.list size (random.unicode 1))
#let [expected (dictionary.from-list text.hash (list.zip/2 keys values))]]
@@ -158,5 +158,5 @@
(list.zip/2 keys)
(dictionary.from-list text.hash))))
(!expect (^multi (#try.Success actual)
- (:: (dictionary.equivalence text.equivalence) = expected actual))))))
+ (\ (dictionary.equivalence text.equivalence) = expected actual))))))
))))
diff --git a/stdlib/source/test/lux/control/parser/synthesis.lux b/stdlib/source/test/lux/control/parser/synthesis.lux
index da6e3247f..d7709687f 100644
--- a/stdlib/source/test/lux/control/parser/synthesis.lux
+++ b/stdlib/source/test/lux/control/parser/synthesis.lux
@@ -52,9 +52,9 @@
(def: random-environment
(Random (Environment Synthesis))
(do {! random.monad}
- [size (:: ! map (n.% 5) random.nat)]
+ [size (\ ! map (n.% 5) random.nat)]
(|> ..random-variable
- (:: ! map (|>> synthesis.variable))
+ (\ ! map (|>> synthesis.variable))
(random.list size))))
(def: simple
@@ -63,12 +63,12 @@
(~~ (template [<query> <check> <random> <synthesis> <equivalence>]
[(do {! random.monad}
[expected <random>
- dummy (|> <random> (random.filter (|>> (:: <equivalence> = expected) not)))]
+ dummy (|> <random> (random.filter (|>> (\ <equivalence> = expected) not)))]
($_ _.and
(_.cover [<query>]
(|> (/.run <query> (list (<synthesis> expected)))
(!expect (^multi (#try.Success actual)
- (:: <equivalence> = expected actual)))))
+ (\ <equivalence> = expected actual)))))
(_.cover [<check>]
(and (|> (/.run (<check> expected) (list (<synthesis> expected)))
(!expect (#try.Success _)))
@@ -77,7 +77,7 @@
(exception.match? /.cannot-parse error))))))))]
[/.bit /.bit! random.bit synthesis.bit bit.equivalence]
- [/.i64 /.i64! (:: ! map .i64 random.nat) synthesis.i64 i64.equivalence]
+ [/.i64 /.i64! (\ ! map .i64 random.nat) synthesis.i64 i64.equivalence]
[/.f64 /.f64! random.safe-frac synthesis.f64 frac.equivalence]
[/.text /.text! (random.unicode 1) synthesis.text text.equivalence]
[/.local /.local! random.nat synthesis.variable/local n.equivalence]
@@ -91,7 +91,7 @@
($_ _.and
(do {! random.monad}
[expected-bit random.bit
- expected-i64 (:: ! map .i64 random.nat)
+ expected-i64 (\ ! map .i64 random.nat)
expected-f64 random.safe-frac
expected-text (random.unicode 1)]
(_.cover [/.tuple]
@@ -101,10 +101,10 @@
(synthesis.f64 expected-f64)
(synthesis.text expected-text)))))
(!expect (^multi (#try.Success [actual-bit actual-i64 actual-f64 actual-text])
- (and (:: bit.equivalence = expected-bit actual-bit)
- (:: i64.equivalence = expected-i64 actual-i64)
- (:: frac.equivalence = expected-f64 actual-f64)
- (:: text.equivalence = expected-text actual-text)))))
+ (and (\ bit.equivalence = expected-bit actual-bit)
+ (\ i64.equivalence = expected-i64 actual-i64)
+ (\ frac.equivalence = expected-f64 actual-f64)
+ (\ text.equivalence = expected-text actual-text)))))
(|> (/.run (/.tuple ($_ <>.and /.bit /.i64 /.f64 /.text))
(list (synthesis.text expected-text)))
(!expect (^multi (#try.Failure error)
@@ -117,10 +117,10 @@
(and (|> (/.run (/.function arity /.text)
(list (synthesis.function/abstraction [expected-environment arity (synthesis.text expected-body)])))
(!expect (^multi (#try.Success [actual-environment actual-body])
- (and (:: (list.equivalence synthesis.equivalence) =
- expected-environment
- actual-environment)
- (:: text.equivalence = expected-body actual-body)))))
+ (and (\ (list.equivalence synthesis.equivalence) =
+ expected-environment
+ actual-environment)
+ (\ text.equivalence = expected-body actual-body)))))
(|> (/.run (/.function arity /.text)
(list (synthesis.text expected-body)))
(!expect (^multi (#try.Failure error)
@@ -135,7 +135,7 @@
(!expect (^multi (#try.Failure error)
(exception.match? /.wrong-arity error))))))
(do {! random.monad}
- [arity (:: ! map (|>> (n.% 10) inc) random.nat)
+ [arity (\ ! map (|>> (n.% 10) inc) random.nat)
expected-offset random.nat
expected-inits (random.list arity random.bit)
expected-body (random.unicode 1)]
@@ -145,11 +145,11 @@
(list\map (|>> synthesis.bit) expected-inits)
(synthesis.text expected-body)])))
(!expect (^multi (#try.Success [actual-offset actual-inits actual-body])
- (and (:: n.equivalence = expected-offset actual-offset)
- (:: (list.equivalence bit.equivalence) =
- expected-inits
- actual-inits)
- (:: text.equivalence = expected-body actual-body)))))
+ (and (\ n.equivalence = expected-offset actual-offset)
+ (\ (list.equivalence bit.equivalence) =
+ expected-inits
+ actual-inits)
+ (\ text.equivalence = expected-body actual-body)))))
(|> (/.run (/.loop (<>.many /.bit) /.text)
(list (synthesis.text expected-body)))
(!expect (^multi (#try.Failure error)
@@ -162,23 +162,23 @@
(_.with-cover [/.Parser])
($_ _.and
(do {! random.monad}
- [expected (:: ! map (|>> synthesis.i64) random.nat)]
+ [expected (\ ! map (|>> synthesis.i64) random.nat)]
(_.cover [/.run /.any]
(|> (/.run /.any (list expected))
(!expect (^multi (#try.Success actual)
- (:: synthesis.equivalence = expected actual))))))
+ (\ synthesis.equivalence = expected actual))))))
(_.cover [/.empty-input]
(|> (/.run /.any (list))
(!expect (^multi (#try.Failure error)
(exception.match? /.empty-input error)))))
(do {! random.monad}
- [expected (:: ! map (|>> synthesis.i64) random.nat)]
+ [expected (\ ! map (|>> synthesis.i64) random.nat)]
(_.cover [/.unconsumed-input]
(|> (/.run /.any (list expected expected))
(!expect (^multi (#try.Failure error)
(exception.match? /.unconsumed-input error))))))
(do {! random.monad}
- [dummy (:: ! map (|>> synthesis.i64) random.nat)]
+ [dummy (\ ! map (|>> synthesis.i64) random.nat)]
(_.cover [/.end! /.expected-empty-input]
(and (|> (/.run /.end! (list))
(!expect (#try.Success _)))
@@ -186,7 +186,7 @@
(!expect (^multi (#try.Failure error)
(exception.match? /.expected-empty-input error)))))))
(do {! random.monad}
- [dummy (:: ! map (|>> synthesis.i64) random.nat)]
+ [dummy (\ ! map (|>> synthesis.i64) random.nat)]
(_.cover [/.end?]
(and (|> (/.run /.end? (list))
(!expect (#try.Success #1)))
diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux
index 2575509de..74fc6a8fd 100644
--- a/stdlib/source/test/lux/control/parser/text.lux
+++ b/stdlib/source/test/lux/control/parser/text.lux
@@ -58,7 +58,7 @@
(-> Text (/.Parser Text) Bit)
(|> expected
(/.run parser)
- (:: try.functor map (text\= expected))
+ (\ try.functor map (text\= expected))
(try.default false)))
(def: (should-pass! expected parser)
@@ -69,13 +69,13 @@
Test
($_ _.and
(do {! random.monad}
- [offset (:: ! map (n.% 50) random.nat)
- range (:: ! map (|>> (n.% 50) (n.+ 10)) random.nat)
+ [offset (\ ! map (n.% 50) random.nat)
+ range (\ ! map (|>> (n.% 50) (n.+ 10)) random.nat)
#let [limit (n.+ offset range)]
- expected (:: ! map (|>> (n.% range) (n.+ offset) text.from-code) random.nat)
+ expected (\ ! map (|>> (n.% range) (n.+ offset) text.from-code) random.nat)
out-of-range (case offset
- 0 (:: ! map (|>> (n.% 10) inc (n.+ limit) text.from-code) random.nat)
- _ (:: ! map (|>> (n.% offset) text.from-code) random.nat))]
+ 0 (\ ! map (|>> (n.% 10) inc (n.+ limit) text.from-code) random.nat)
+ _ (\ ! map (|>> (n.% offset) text.from-code) random.nat))]
(_.cover [/.range]
(and (..should-pass expected (/.range offset limit))
(..should-fail out-of-range (/.range offset limit)))))
@@ -94,22 +94,22 @@
(and (..should-pass (text.from-code expected) /.lower)
(..should-fail (text.from-code invalid) /.lower))))
(do {! random.monad}
- [expected (:: ! map (n.% 10) random.nat)
+ [expected (\ ! map (n.% 10) random.nat)
invalid (random.char (unicode.set [unicode.number-forms (list)]))]
(_.cover [/.decimal]
- (and (..should-pass (:: n.decimal encode expected) /.decimal)
+ (and (..should-pass (\ n.decimal encode expected) /.decimal)
(..should-fail (text.from-code invalid) /.decimal))))
(do {! random.monad}
- [expected (:: ! map (n.% 8) random.nat)
+ [expected (\ ! map (n.% 8) random.nat)
invalid (random.char (unicode.set [unicode.number-forms (list)]))]
(_.cover [/.octal]
- (and (..should-pass (:: n.octal encode expected) /.octal)
+ (and (..should-pass (\ n.octal encode expected) /.octal)
(..should-fail (text.from-code invalid) /.octal))))
(do {! random.monad}
- [expected (:: ! map (n.% 16) random.nat)
+ [expected (\ ! map (n.% 16) random.nat)
invalid (random.char (unicode.set [unicode.number-forms (list)]))]
(_.cover [/.hexadecimal]
- (and (..should-pass (:: n.hex encode expected) /.hexadecimal)
+ (and (..should-pass (\ n.hex encode expected) /.hexadecimal)
(..should-fail (text.from-code invalid) /.hexadecimal))))
(do {! random.monad}
[expected (random.char unicode.ascii/alpha)
@@ -152,14 +152,14 @@
[#let [num-options 3]
options (|> (random.char unicode.full)
(random.set n.hash num-options)
- (:: ! map (|>> set.to-list
- (list\map text.from-code)
- (text.join-with ""))))
- expected (:: ! map (function (_ value)
- (|> options
- (text.nth (n.% num-options value))
- maybe.assume))
- random.nat)
+ (\ ! map (|>> set.to-list
+ (list\map text.from-code)
+ (text.join-with ""))))
+ expected (\ ! map (function (_ value)
+ (|> options
+ (text.nth (n.% num-options value))
+ maybe.assume))
+ random.nat)
invalid (random.filter (|>> text.from-code
(text.contains? options)
not)
@@ -178,14 +178,14 @@
[#let [num-options 3]
options (|> (random.char unicode.full)
(random.set n.hash num-options)
- (:: ! map (|>> set.to-list
- (list\map text.from-code)
- (text.join-with ""))))
- invalid (:: ! map (function (_ value)
- (|> options
- (text.nth (n.% num-options value))
- maybe.assume))
- random.nat)
+ (\ ! map (|>> set.to-list
+ (list\map text.from-code)
+ (text.join-with ""))))
+ invalid (\ ! map (function (_ value)
+ (|> options
+ (text.nth (n.% num-options value))
+ maybe.assume))
+ random.nat)
expected (random.filter (|>> text.from-code
(text.contains? options)
not)
@@ -207,26 +207,26 @@
(let [octal! (/.one-of! "01234567")]
($_ _.and
(do {! random.monad}
- [left (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)
- right (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)
+ [left (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
+ right (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
#let [expected (format left right)]
invalid (|> random.nat
- (:: ! map (n.% 16))
+ (\ ! map (n.% 16))
(random.filter (n.>= 8))
- (:: ! map (:: n.hex encode)))]
+ (\ ! map (\ n.hex encode)))]
(_.cover [/.many /.many!]
(and (..should-pass expected (/.many /.octal))
(..should-fail invalid (/.many /.octal))
(..should-pass! expected (/.many! octal!)))))
(do {! random.monad}
- [left (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)
- right (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)
+ [left (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
+ right (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
#let [expected (format left right)]
invalid (|> random.nat
- (:: ! map (n.% 16))
+ (\ ! map (n.% 16))
(random.filter (n.>= 8))
- (:: ! map (:: n.hex encode)))]
+ (\ ! map (\ n.hex encode)))]
(_.cover [/.some /.some!]
(and (..should-pass expected (/.some /.octal))
(..should-pass "" (/.some /.octal))
@@ -235,7 +235,7 @@
(..should-pass! expected (/.some! octal!))
(..should-pass! "" (/.some! octal!)))))
(do {! random.monad}
- [#let [octal (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)]
+ [#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
@@ -248,7 +248,7 @@
(..should-fail (format first second third) (/.exactly! 2 octal!))
(..should-fail (format first) (/.exactly! 2 octal!)))))
(do {! random.monad}
- [#let [octal (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)]
+ [#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
@@ -261,7 +261,7 @@
(..should-pass! (format first) (/.at-most! 2 octal!))
(..should-fail (format first second third) (/.at-most! 2 octal!)))))
(do {! random.monad}
- [#let [octal (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)]
+ [#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
@@ -274,7 +274,7 @@
(..should-pass! (format first second third) (/.at-least! 2 octal!))
(..should-fail (format first) (/.at-least! 2 octal!)))))
(do {! random.monad}
- [#let [octal (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)]
+ [#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
@@ -386,7 +386,7 @@
(/.this out)))
(!expect (#try.Success _)))))
(do {! random.monad}
- [expected (:: ! map (|>> (n.% 8) (:: n.octal encode)) random.nat)]
+ [expected (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
(_.cover [/.embed]
(|> (list (code.text expected))
(<c>.run (/.embed /.octal <c>.text))
diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux
index 729551843..705c9ef24 100644
--- a/stdlib/source/test/lux/control/parser/type.lux
+++ b/stdlib/source/test/lux/control/parser/type.lux
@@ -28,8 +28,8 @@
(def: primitive
(Random Type)
(|> (random.ascii/alpha-num 1)
- (:: random.monad map (function (_ name)
- (#.Primitive name (list))))))
+ (\ random.monad map (function (_ name)
+ (#.Primitive name (list))))))
(def: matches
Test
diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux
index d9f28e5db..088f3dc7c 100644
--- a/stdlib/source/test/lux/control/region.lux
+++ b/stdlib/source/test/lux/control/region.lux
@@ -79,7 +79,7 @@
(<| (_.covering /._)
(_.with-cover [/.Region])
(do {! random.monad}
- [expected-clean-ups (|> random.nat (:: ! map (|>> (n.% 100) (n.max 1))))]
+ [expected-clean-ups (|> random.nat (\ ! map (|>> (n.% 100) (n.max 1))))]
($_ _.and
(_.with-cover [/.functor]
($functor.spec ..injection ..comparison (: (All [! r]
diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux
index 6206206e3..bb5144fd1 100644
--- a/stdlib/source/test/lux/control/security/policy.lux
+++ b/stdlib/source/test/lux/control/security/policy.lux
@@ -60,7 +60,7 @@
(!.use %\can-downgrade sample)))))
(def: hash
(|>> (!.use %\can-downgrade)
- (:: text.hash hash)))))
+ (\ text.hash hash)))))
(def: password
(!.use %\can-upgrade))
@@ -76,24 +76,24 @@
(do random.monad
[#let [policy-0 (policy [])]
raw-password (random.ascii 10)
- #let [password (:: policy-0 password raw-password)]]
+ #let [password (\ policy-0 password raw-password)]]
($_ _.and
(_.with-cover [/.Privacy /.Private /.Can-Conceal /.Can-Reveal
/.Safety /.Safe /.Can-Trust /.Can-Distrust]
($_ _.and
(_.with-cover [/.functor]
- ($functor.spec (..injection (:: policy-0 can-upgrade)) (..comparison (:: policy-0 can-downgrade)) /.functor))
+ ($functor.spec (..injection (\ policy-0 can-upgrade)) (..comparison (\ policy-0 can-downgrade)) /.functor))
(_.with-cover [/.apply]
- ($apply.spec (..injection (:: policy-0 can-upgrade)) (..comparison (:: policy-0 can-downgrade)) /.apply))
+ ($apply.spec (..injection (\ policy-0 can-upgrade)) (..comparison (\ policy-0 can-downgrade)) /.apply))
(_.with-cover [/.monad]
- ($monad.spec (..injection (:: policy-0 can-upgrade)) (..comparison (:: policy-0 can-downgrade)) /.monad))))
+ ($monad.spec (..injection (\ policy-0 can-upgrade)) (..comparison (\ policy-0 can-downgrade)) /.monad))))
(_.cover [/.Privilege /.Context /.with-policy]
- (and (:: policy-0 = password password)
- (n.= (:: text.hash hash raw-password)
- (:: policy-0 hash password))))
+ (and (\ policy-0 = password 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))]
+ delegate (/.delegation (\ policy-0 can-downgrade) (\ policy-1 can-upgrade))]
(_.cover [/.Delegation /.delegation]
- (:: policy-1 = (delegate password) (delegate password))))
+ (\ policy-1 = (delegate password) (delegate password))))
))))
diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux
index 3e30afab0..60f06dbef 100644
--- a/stdlib/source/test/lux/control/state.lux
+++ b/stdlib/source/test/lux/control/state.lux
@@ -84,7 +84,7 @@
(def: loops
Test
(do {! random.monad}
- [limit (|> random.nat (:: ! map (n.% 10)))
+ [limit (|> random.nat (\ ! map (n.% 10)))
#let [condition (do /.monad
[state /.get]
(wrap (n.< limit state)))]]
diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux
index aac2059f8..dfc5e7306 100644
--- a/stdlib/source/test/lux/control/thread.lux
+++ b/stdlib/source/test/lux/control/thread.lux
@@ -20,7 +20,7 @@
(def: (injection value)
(Injection (All [a !] (Thread ! a)))
- (:: /.monad wrap value))
+ (\ /.monad wrap value))
(def: comparison
(Comparison (All [a !] (Thread ! a)))
@@ -39,12 +39,12 @@
(_.cover [/.run]
(n.= sample
(|> sample
- (:: /.monad wrap)
+ (\ /.monad wrap)
/.run)))
(_.cover [/.io]
(n.= sample
(|> sample
- (:: /.monad wrap)
+ (\ /.monad wrap)
/.io
io.run)))
diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux
index f4eaec656..cc01b7337 100644
--- a/stdlib/source/test/lux/control/try.lux
+++ b/stdlib/source/test/lux/control/try.lux
@@ -28,7 +28,7 @@
(def: comparison
(Comparison Try)
(function (_ ==)
- (:: (/.equivalence ==) =)))
+ (\ (/.equivalence ==) =)))
(def: #export (try element)
(All [a] (-> (Random a) (Random (Try a))))
diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux
index 070d51888..9bb471bf5 100644
--- a/stdlib/source/test/lux/control/writer.lux
+++ b/stdlib/source/test/lux/control/writer.lux
@@ -25,7 +25,7 @@
(def: (injection monoid value)
(All [w] (-> (Monoid w) (Injection (Writer w))))
- [(:: monoid identity) value])
+ [(\ monoid identity) value])
(def: comparison
(All [w] (Comparison (Writer w)))