aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/control
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux/control')
-rw-r--r--stdlib/source/test/lux/control/concurrency/actor.lux6
-rw-r--r--stdlib/source/test/lux/control/concurrency/async.lux2
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux20
-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.lux4
-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/inline.lux2
-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/function/mutual.lux4
-rw-r--r--stdlib/source/test/lux/control/lazy.lux4
-rw-r--r--stdlib/source/test/lux/control/maybe.lux8
-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.lux68
-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.lux44
-rw-r--r--stdlib/source/test/lux/control/parser/synthesis.lux46
-rw-r--r--stdlib/source/test/lux/control/parser/text.lux82
-rw-r--r--stdlib/source/test/lux/control/parser/type.lux12
-rw-r--r--stdlib/source/test/lux/control/parser/xml.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
31 files changed, 239 insertions, 239 deletions
diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux
index 5713f1599..3149e3873 100644
--- a/stdlib/source/test/lux/control/concurrency/actor.lux
+++ b/stdlib/source/test/lux/control/concurrency/actor.lux
@@ -198,9 +198,9 @@
verdict)))
(do !
- [num_events (# ! each (|>> (n.% 10) ++) random.nat)
+ [num_events (at ! each (|>> (n.% 10) ++) random.nat)
events (random.list num_events random.nat)
- num_observations (# ! each (n.% num_events) random.nat)
+ num_observations (at ! each (n.% num_events) random.nat)
.let [expected (list.first num_observations events)
sink (is (Atom (Sequence Nat))
(atom.atom sequence.empty))]]
@@ -224,5 +224,5 @@
_ (/.obituary agent)
actual (async.future (atom.read! sink))]
(_.coverage' [/.Stop /.observe! /.obituary]
- (# (list.equivalence n.equivalence) = expected (sequence.list actual))))))
+ (at (list.equivalence n.equivalence) = expected (sequence.list actual))))))
))))
diff --git a/stdlib/source/test/lux/control/concurrency/async.lux b/stdlib/source/test/lux/control/concurrency/async.lux
index 95647d607..1e343c32d 100644
--- a/stdlib/source/test/lux/control/concurrency/async.lux
+++ b/stdlib/source/test/lux/control/concurrency/async.lux
@@ -52,7 +52,7 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [waiting_time (|> random.nat (# ! each (|>> (n.% ..delay) (n.+ ..delay))))
+ [waiting_time (|> random.nat (at ! each (|>> (n.% ..delay) (n.+ ..delay))))
expected random.nat
dummy random.nat
.let [not_dummy (|> random.nat (random.only (|>> (n.= dummy) not)))]
diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux
index 79d2fe727..004659886 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -52,7 +52,7 @@
(All (_ a) (-> Nat [(/.Channel a) (/.Sink a)] (Async (List a))))
(case amount_of_polls
0 (do async.monad
- [_ (async.future (# sink close))]
+ [_ (async.future (at sink close))]
(in {.#End}))
_ (do [! async.monad]
[event channel]
@@ -61,8 +61,8 @@
(in {.#End})
{.#Some [head tail]}
- (# ! each (|>> {.#Item (variance.read head)})
- (take_amount (-- amount_of_polls) [channel sink]))))))
+ (at ! each (|>> {.#Item (variance.read head)})
+ (take_amount (-- amount_of_polls) [channel sink]))))))
(def: .public test
Test
@@ -90,8 +90,8 @@
(do (try.with io.monad)
[.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)]
(/.channel []))]
- _ (# sink feed sample)
- _ (# sink close)]
+ _ (at sink feed sample)
+ _ (at sink close)]
(in channel)))
{try.#Success channel}
(io.run!
@@ -111,8 +111,8 @@
(do (try.with io.monad)
[.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)]
(/.channel []))]
- _ (# sink close)]
- (# sink feed sample)))
+ _ (at sink close)]
+ (at sink feed sample)))
{try.#Success _}
false
@@ -161,7 +161,7 @@
listened (|> sink
atom.read!
async.future
- (# ! each sequence.list))]
+ (at ! each sequence.list))]
(_.coverage' [/.Subscriber /.subscribe!]
(list#= inputs listened))))
(in (do async.monad
@@ -193,8 +193,8 @@
(list#= (list distinct/0 distinct/1 distinct/2)
actual))))
(do !
- [polling_delay (# ! each (|>> (n.% 10) ++) random.nat)
- amount_of_polls (# ! each (|>> (n.% 10) ++) random.nat)]
+ [polling_delay (at ! each (|>> (n.% 10) ++) random.nat)
+ amount_of_polls (at ! each (|>> (n.% 10) ++) random.nat)]
(all _.and
(in (do [! async.monad]
[actual (..take_amount amount_of_polls (/.poll polling_delay (is (IO Nat) (io.io sample))))
diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux
index 1df21f823..64a5cd067 100644
--- a/stdlib/source/test/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux
@@ -38,7 +38,7 @@
(_.for [/.Semaphore]
(all _.and
(do [! random.monad]
- [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (at ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do async.monad
[result (async.within ..delay (/.wait! semaphore))]
@@ -50,7 +50,7 @@
{.#None}
false)))))
(do [! random.monad]
- [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (at ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do [! async.monad]
[_ (monad.each ! /.wait! (list.repeated initial_open_positions semaphore))
@@ -63,7 +63,7 @@
{.#None}
true)))))
(do [! random.monad]
- [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (at ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do [! async.monad]
[_ (monad.each ! /.wait! (list.repeated initial_open_positions semaphore))
@@ -79,7 +79,7 @@
_
false)))))
(do [! random.monad]
- [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (at ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do async.monad
[outcome (/.signal! semaphore)]
@@ -97,7 +97,7 @@
(_.for [/.Mutex]
(all _.and
(do [! random.monad]
- [repetitions (|> random.nat (# ! each (|>> (n.% 100) (n.max 10))))
+ [repetitions (|> random.nat (at ! each (|>> (n.% 100) (n.max 10))))
.let [resource (atom.atom "")
expected_As (text.together (list.repeated repetitions "A"))
expected_Bs (text.together (list.repeated repetitions "B"))
@@ -154,7 +154,7 @@
_
false)))
(do [! random.monad]
- [limit (# ! each (|>> (n.% 9) ++) random.nat)
+ [limit (at ! each (|>> (n.% 9) ++) random.nat)
.let [barrier (/.barrier (maybe.trusted (/.limit limit)))
resource (atom.atom "")]]
(in (do [! async.monad]
diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux
index 05d6f33da..a06248ba1 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 in))
+ (at /.monad in))
(def: comparison
(Comparison /.STM)
@@ -41,7 +41,7 @@
(do [! random.monad]
[dummy random.nat
expected random.nat
- iterations_per_process (|> random.nat (# ! each (n.% 100)))]
+ iterations_per_process (|> random.nat (at ! each (n.% 100)))]
(all _.and
(_.for [/.functor]
($functor.spec ..injection ..comparison /.functor))
@@ -51,7 +51,7 @@
($monad.spec ..injection ..comparison /.monad))
(in (do async.monad
- [actual (/.commit! (# /.monad in expected))]
+ [actual (/.commit! (at /.monad in expected))]
(_.coverage' [/.commit!]
(n.= expected actual))))
(in (do async.monad
@@ -84,13 +84,13 @@
[follower sink] (io.run! (/.changes box))]
_ (/.commit! (/.write expected box))
_ (/.commit! (/.update (n.* 2) box))
- _ (async.future (# sink close))
+ _ (async.future (at sink close))
_ (/.commit! (/.update (n.* 3) box))
changes (frp.list follower)]
(_.coverage' [/.changes]
- (# (list.equivalence n.equivalence) =
- (list expected (n.* 2 expected))
- changes))))
+ (at (list.equivalence n.equivalence) =
+ (list expected (n.* 2 expected))
+ changes))))
(in (let [var (/.var 0)]
(do [! async.monad]
[_ (|> (list.repeated iterations_per_process [])
diff --git a/stdlib/source/test/lux/control/concurrency/thread.lux b/stdlib/source/test/lux/control/concurrency/thread.lux
index 9f9611c42..7ed7aff8c 100644
--- a/stdlib/source/test/lux/control/concurrency/thread.lux
+++ b/stdlib/source/test/lux/control/concurrency/thread.lux
@@ -26,8 +26,8 @@
(do [! random.monad]
[dummy random.nat
expected random.nat
- delay (# ! each (|>> (n.% 5) (n.+ 5))
- random.nat)]
+ delay (at ! each (|>> (n.% 5) (n.+ 5))
+ random.nat)]
(all _.and
(_.coverage [/.parallelism]
(n.> 0 /.parallelism))
diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux
index 459e7101a..34756195a 100644
--- a/stdlib/source/test/lux/control/exception.lux
+++ b/stdlib/source/test/lux/control/exception.lux
@@ -29,7 +29,7 @@
[expected random.nat
wrong (|> random.nat (random.only (|>> (n.= expected) not)))
assertion_succeeded? random.bit
- .let [report_element (# ! each %.nat random.nat)]
+ .let [report_element (at ! each %.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 d122bbd39..4a95a0065 100644
--- a/stdlib/source/test/lux/control/function.lux
+++ b/stdlib/source/test/lux/control/function.lux
@@ -24,8 +24,8 @@
Test
(do [! random.monad]
[expected random.nat
- f0 (# ! each n.+ random.nat)
- f1 (# ! each n.* random.nat)
+ f0 (at ! each n.+ random.nat)
+ f1 (at ! each n.* random.nat)
dummy random.nat
extra (|> random.nat (random.only (|>> (n.= expected) not)))]
(<| (_.covering /._)
@@ -36,7 +36,7 @@
(n.= (left extra)
(right extra)))))
generator (is (Random (-> Nat Nat))
- (# ! each n.- random.nat))]
+ (at ! each n.- random.nat))]
(_.for [/.monoid]
($monoid.spec equivalence /.monoid generator)))
diff --git a/stdlib/source/test/lux/control/function/inline.lux b/stdlib/source/test/lux/control/function/inline.lux
index 67245f8cc..54cbeabc7 100644
--- a/stdlib/source/test/lux/control/function/inline.lux
+++ b/stdlib/source/test/lux/control/function/inline.lux
@@ -22,7 +22,7 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [.let [measurement (# ! each (i.% +1000) random.int)]
+ [.let [measurement (at ! each (i.% +1000) random.int)]
m0 measurement
m1 measurement])
(all _.and
diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux
index b16902c88..3a74921cf 100644
--- a/stdlib/source/test/lux/control/function/memo.lux
+++ b/stdlib/source/test/lux/control/function/memo.lux
@@ -60,7 +60,7 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [input (|> random.nat (# ! each (|>> (n.% 5) (n.+ 21))))])
+ [input (|> random.nat (at ! each (|>> (n.% 5) (n.+ 21))))])
(_.for [/.Memo])
(all _.and
(_.coverage [/.closed /.none]
@@ -108,7 +108,7 @@
(is (//.Mixin Nat (State (Dictionary Nat Nat) Nat))
(function (factorial delegate again input)
(case input
- (^.or 0 1) (# state.monad in 1)
+ (^.or 0 1) (at state.monad in 1)
_ (do state.monad
[output' (again (-- input))]
(in (n.* input output')))))))
diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux
index c19295365..02ea34ad3 100644
--- a/stdlib/source/test/lux/control/function/mixin.lux
+++ b/stdlib/source/test/lux/control/function/mixin.lux
@@ -27,7 +27,7 @@
Test
(<| (_.covering /._)
(do [! random.monad]
- [input (|> random.nat (# ! each (|>> (n.% 6) (n.+ 20))))
+ [input (|> random.nat (at ! each (|>> (n.% 6) (n.+ 20))))
dummy random.nat
shift (|> random.nat (random.only (|>> (n.= dummy) not)))
.let [equivalence (is (Equivalence (/.Mixin Nat Nat))
diff --git a/stdlib/source/test/lux/control/function/mutual.lux b/stdlib/source/test/lux/control/function/mutual.lux
index 698685d0c..3d936c6dd 100644
--- a/stdlib/source/test/lux/control/function/mutual.lux
+++ b/stdlib/source/test/lux/control/function/mutual.lux
@@ -18,7 +18,7 @@
(def: test_let
Test
(do [! random.monad]
- [sample (# ! each (n.% 10) random.nat)
+ [sample (at ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
(<| (_.coverage [/.let])
(/.let [(even? number)
@@ -51,7 +51,7 @@
(def: test_def
Test
(do [! random.monad]
- [sample (# ! each (n.% 10) random.nat)
+ [sample (at ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
(<| (_.coverage [/.def:])
(and (bit#= expected (..even? sample))
diff --git a/stdlib/source/test/lux/control/lazy.lux b/stdlib/source/test/lux/control/lazy.lux
index d205eebb2..26e1baba6 100644
--- a/stdlib/source/test/lux/control/lazy.lux
+++ b/stdlib/source/test/lux/control/lazy.lux
@@ -25,11 +25,11 @@
(def: comparison
(Comparison Lazy)
(function (_ ==)
- (# (/.equivalence ==) =)))
+ (at (/.equivalence ==) =)))
(def: .public lazy
(All (_ a) (-> (Random a) (Random (Lazy a))))
- (# random.functor each (|>> /.lazy)))
+ (at random.functor each (|>> /.lazy)))
(def: .public test
Test
diff --git a/stdlib/source/test/lux/control/maybe.lux b/stdlib/source/test/lux/control/maybe.lux
index b986c2fbc..7b5c61659 100644
--- a/stdlib/source/test/lux/control/maybe.lux
+++ b/stdlib/source/test/lux/control/maybe.lux
@@ -34,7 +34,7 @@
($equivalence.spec (/.equivalence n.equivalence) (random.maybe random.nat)))
(_.for [/.hash]
(|> random.nat
- (# random.monad each (|>> {.#Some}))
+ (at random.monad each (|>> {.#Some}))
($hash.spec (/.hash n.hash))))
(_.for [/.monoid]
($monoid.spec (/.equivalence n.equivalence) /.monoid (random.maybe random.nat)))
@@ -78,9 +78,9 @@
(do random.monad
[value random.nat]
(_.coverage [/.list]
- (# (list.equivalence n.equivalence) =
- (list value)
- (/.list {.#Some value}))))
+ (at (list.equivalence n.equivalence) =
+ (list value)
+ (/.list {.#Some value}))))
(do random.monad
[expected random.nat
.let [(open "/#[0]") (/.equivalence n.equivalence)]]
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index c5fdb888a..c0f1d05f6 100644
--- a/stdlib/source/test/lux/control/parser.lux
+++ b/stdlib/source/test/lux/control/parser.lux
@@ -90,7 +90,7 @@
Test
(do [! random.monad]
[expected0 random.nat
- variadic (# ! each (|>> (n.max 1) (n.min 20)) random.nat)
+ variadic (at ! each (|>> (n.max 1) (n.min 20)) random.nat)
expected+ (random.list variadic random.nat)
even0 (random.only n.even? random.nat)
odd0 (random.only n.odd? random.nat)
@@ -109,7 +109,7 @@
(and (|> (list#each code.nat expected+)
(/.result (/.some <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) = expected+ actual)))
+ (at (list.equivalence n.equivalence) = expected+ actual)))
(|> (list#each (|>> .int code.int) expected+)
(/.result (/.some <code>.nat))
(match {.#End}
@@ -118,7 +118,7 @@
(and (|> (list#each code.nat expected+)
(/.result (/.many <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) = expected+ actual)))
+ (at (list.equivalence n.equivalence) = expected+ actual)))
(|> (list (code.nat expected0))
(/.result (/.many <code>.nat))
(match (list actual)
@@ -180,8 +180,8 @@
(def: combinators_1
Test
(do [! random.monad]
- [variadic (# ! each (|>> (n.max 1) (n.min 20)) random.nat)
- times (# ! each (n.% variadic) random.nat)
+ [variadic (at ! each (|>> (n.max 1) (n.min 20)) random.nat)
+ times (at ! each (n.% variadic) random.nat)
expected random.nat
wrong (|> random.nat (random.only (|>> (n.= expected) not)))
expected+ (random.list variadic random.nat)
@@ -191,9 +191,9 @@
(and (|> (list#each code.nat expected+)
(/.result (/.exactly times <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- (list.first times expected+)
- actual)))
+ (at (list.equivalence n.equivalence) =
+ (list.first times expected+)
+ actual)))
(|> (list#each code.nat expected+)
(/.result (/.exactly (++ variadic) <code>.nat))
fails?)))
@@ -201,9 +201,9 @@
(and (|> (list#each code.nat expected+)
(/.result (/.at_least times <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- expected+
- actual)))
+ (at (list.equivalence n.equivalence) =
+ expected+
+ actual)))
(|> (list#each code.nat expected+)
(/.result (/.at_least (++ variadic) <code>.nat))
fails?)))
@@ -211,44 +211,44 @@
(and (|> (list#each code.nat expected+)
(/.result (/.at_most times <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- (list.first times expected+)
- actual)))
+ (at (list.equivalence n.equivalence) =
+ (list.first times expected+)
+ actual)))
(|> (list#each code.nat expected+)
(/.result (/.at_most (++ variadic) <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- expected+
- actual)))))
+ (at (list.equivalence n.equivalence) =
+ expected+
+ actual)))))
(_.coverage [/.between]
(and (|> (list#each code.nat expected+)
(/.result (/.between times (n.- times variadic) <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- expected+
- actual)))
+ (at (list.equivalence n.equivalence) =
+ expected+
+ actual)))
(|> (list#each code.nat (list.first times expected+))
(/.result (/.between times (n.- times variadic) <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- (list.first times expected+)
- actual)))))
+ (at (list.equivalence n.equivalence) =
+ (list.first times expected+)
+ actual)))))
(_.coverage [/.separated_by]
(|> (list.interposed (code.text separator) (list#each code.nat expected+))
(/.result (/.separated_by (<code>.this (code.text separator)) <code>.nat))
(match actual
- (# (list.equivalence n.equivalence) =
- expected+
- actual))))
+ (at (list.equivalence n.equivalence) =
+ expected+
+ actual))))
(_.coverage [/.remaining]
(|> (list#each code.nat expected+)
(/.result /.remaining)
(match actual
- (# (list.equivalence code.equivalence) =
- (list#each code.nat expected+)
- actual))))
+ (at (list.equivalence code.equivalence) =
+ (list#each code.nat expected+)
+ actual))))
(_.coverage [/.else]
- (and (|> (/.result (/.else wrong (# /.monad in expected)) (list))
+ (and (|> (/.result (/.else wrong (at /.monad in expected)) (list))
(match actual (n.= expected actual)))
(|> (/.result (/.else expected (/.failure "yolo"))
(list))
@@ -332,7 +332,7 @@
(def: injection
(Injection (All (_ a i) (Parser i a)))
- (# /.monad in))
+ (at /.monad in))
(def: comparison
(Comparison (All (_ a i) (Parser i a)))
@@ -361,7 +361,7 @@
($monad.spec ..injection ..comparison /.monad))
(_.coverage [/.result]
- (|> (/.result (# /.monad in expected) (list))
+ (|> (/.result (at /.monad in expected) (list))
(match actual (n.= expected actual))))
(_.coverage [/.failure]
(|> (list)
diff --git a/stdlib/source/test/lux/control/parser/analysis.lux b/stdlib/source/test/lux/control/parser/analysis.lux
index 1e1a288b2..6f79c1dcb 100644
--- a/stdlib/source/test/lux/control/parser/analysis.lux
+++ b/stdlib/source/test/lux/control/parser/analysis.lux
@@ -54,13 +54,13 @@
[]
(`` (all _.and
(do [! random.monad]
- [expected (# ! each (|>> analysis.bit) random.bit)]
+ [expected (at ! each (|>> analysis.bit) random.bit)]
(_.coverage [/.result /.any]
(|> (list expected)
(/.result /.any)
(pipe.case
{try.#Success actual}
- (# analysis.equivalence = expected actual)
+ (at 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 41d2cec10..f2198c2d5 100644
--- a/stdlib/source/test/lux/control/parser/binary.lux
+++ b/stdlib/source/test/lux/control/parser/binary.lux
@@ -56,8 +56,8 @@
(def: (utf8_conversion_does_not_alter? value)
(Predicate Text)
(|> value
- (# utf8.codec encoded)
- (# utf8.codec decoded)
+ (at utf8.codec encoded)
+ (at utf8.codec decoded)
(pipe.case
{try.#Success converted}
(text#= value converted)
@@ -95,7 +95,7 @@
(random.rec
(function (_ again)
(let [random_sequence (do [! random.monad]
- [size (# ! each (n.% 2) random.nat)]
+ [size (at ! each (n.% 2) random.nat)]
(random.list size again))]
(all random.and
..random_location
@@ -128,8 +128,8 @@
(`` (all _.and
(~~ (template [<size> <parser> <format>]
[(do [! random.monad]
- [expected (# ! each (i64.and (i64.mask <size>))
- random.nat)]
+ [expected (at ! each (i64.and (i64.mask <size>))
+ random.nat)]
(_.coverage [<size> <parser> <format>]
(|> (format.result <format> expected)
(/.result <parser>)
@@ -148,12 +148,12 @@
(`` (all _.and
(~~ (template [<parser> <format>]
[(do [! random.monad]
- [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [<parser> <format>]
(|> (format.result <format> expected)
(/.result <parser>)
(!expect (^.multi {try.#Success actual}
- (# binary.equivalence = expected actual))))))]
+ (at binary.equivalence = expected actual))))))]
[/.binary_8 format.binary_8]
[/.binary_16 format.binary_16]
@@ -171,7 +171,7 @@
(|> (format.result <format> expected)
(/.result <parser>)
(!expect (^.multi {try.#Success actual}
- (# text.equivalence = expected actual))))))]
+ (at text.equivalence = expected actual))))))]
[/.utf8_8 format.utf8_8]
[/.utf8_16 format.utf8_16]
@@ -191,7 +191,7 @@
(format.result (<format> format.nat))
(/.result (<parser> /.nat))
(!expect (^.multi {try.#Success actual}
- (# (sequence.equivalence n.equivalence) = expected actual))))))]
+ (at (sequence.equivalence n.equivalence) = expected actual))))))]
[/.sequence_8 format.sequence_8]
[/.sequence_16 format.sequence_16]
@@ -210,7 +210,7 @@
(format.result <format>)
(/.result <parser>)
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual))))))]
+ (at <equivalence> = expected actual))))))]
[/.bit format.bit random.bit bit.equivalence]
[/.nat format.nat random.nat n.equivalence]
@@ -223,13 +223,13 @@
(format.result format.frac)
(/.result /.frac)
(!expect (^.multi {try.#Success actual}
- (or (# frac.equivalence = expected actual)
+ (or (at frac.equivalence = expected actual)
(and (frac.not_a_number? expected)
(frac.not_a_number? actual))))))))
(do [! random.monad]
- [expected (# ! each (|>> (i64.and (i64.mask /.size_8))
- (n.max 2))
- random.nat)]
+ [expected (at ! each (|>> (i64.and (i64.mask /.size_8))
+ (n.max 2))
+ random.nat)]
(_.coverage [/.not_a_bit]
(|> expected
(format.result format.bits_8)
@@ -249,7 +249,7 @@
(format.result <format>)
(/.result <parser>)
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual))))))]
+ (at <equivalence> = expected actual))))))]
[/.location format.location random_location location_equivalence]
[/.code format.code random_code code.equivalence]
@@ -263,14 +263,14 @@
(format.result <format>)
(/.result <parser>)
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual))))))]
+ (at <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]
[/.symbol /.symbol format.symbol format.symbol ..random_symbol symbol.equivalence]))
(do [! random.monad]
- [expected (# ! each (list.repeated ..segment_size) random.nat)]
+ [expected (at ! each (list.repeated ..segment_size) random.nat)]
(_.coverage [/.set_elements_are_not_unique]
(|> expected
(format.result (format.list format.nat))
@@ -285,13 +285,13 @@
(/.result (is (/.Parser (Either Bit Nat))
(/.or /.bit /.nat)))
(!expect (^.multi {try.#Success actual}
- (# (sum.equivalence bit.equivalence n.equivalence) =
- expected
- actual))))))
+ (at (sum.equivalence bit.equivalence n.equivalence) =
+ expected
+ actual))))))
(do [! random.monad]
- [tag (# ! each (|>> (i64.and (i64.mask /.size_8))
- (n.max 2))
- random.nat)
+ [tag (at ! each (|>> (i64.and (i64.mask /.size_8))
+ (n.max 2))
+ random.nat)
value random.bit]
(_.coverage [/.invalid_tag]
(|> [tag value]
@@ -313,9 +313,9 @@
(<>.and /.nat
again))))))
(!expect (^.multi {try.#Success actual}
- (# (list.equivalence n.equivalence) =
- expected
- actual))))))
+ (at (list.equivalence n.equivalence) =
+ expected
+ actual))))))
)))
(def: .public test
@@ -329,22 +329,22 @@
(/.result /.any)
(!expect {try.#Success _})))
(do [! random.monad]
- [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [/.binary_was_not_fully_read]
(|> data
(/.result /.any)
(!expect (^.multi {try.#Failure error}
(exception.match? /.binary_was_not_fully_read error))))))
(do [! random.monad]
- [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [/.segment format.segment format.result]
(|> expected
(format.result (format.segment ..segment_size))
(/.result (/.segment ..segment_size))
(!expect (^.multi {try.#Success actual}
- (# binary.equivalence = expected actual))))))
+ (at binary.equivalence = expected actual))))))
(do [! random.monad]
- [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [/.end?]
(|> data
(/.result (do <>.monad
@@ -355,8 +355,8 @@
post))))
(!expect {try.#Success #1}))))
(do [! random.monad]
- [to_read (# ! each (n.% (++ ..segment_size)) random.nat)
- data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (at ! each (n.% (++ ..segment_size)) random.nat)
+ data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [/.Offset /.offset]
(|> data
(/.result (do <>.monad
@@ -370,8 +370,8 @@
(n.= ..segment_size nothing_left)))))
(!expect {try.#Success #1}))))
(do [! random.monad]
- [to_read (# ! each (n.% (++ ..segment_size)) random.nat)
- data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (at ! each (n.% (++ ..segment_size)) random.nat)
+ data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [/.remaining]
(|> data
(/.result (do <>.monad
diff --git a/stdlib/source/test/lux/control/parser/cli.lux b/stdlib/source/test/lux/control/parser/cli.lux
index 28e5fb4a2..9e12a51aa 100644
--- a/stdlib/source/test/lux/control/parser/cli.lux
+++ b/stdlib/source/test/lux/control/parser/cli.lux
@@ -33,7 +33,7 @@
(<| (_.covering /._)
(_.for [/.Parser])
(do [! random.monad]
- [expected (# ! each n#encoded random.nat)
+ [expected (at ! each n#encoded random.nat)
.let [random_dummy (random.only (|>> (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 ad59d2ba3..01837874f 100644
--- a/stdlib/source/test/lux/control/parser/code.lux
+++ b/stdlib/source/test/lux/control/parser/code.lux
@@ -61,7 +61,7 @@
(_.for [/.Parser])
(`` (all _.and
(do [! random.monad]
- [expected (# ! each code.bit random.bit)]
+ [expected (at ! each code.bit random.bit)]
(_.coverage [/.result]
(and (|> (/.result /.any (list expected))
(!expect {try.#Success _}))
@@ -70,12 +70,12 @@
(~~ (template [<query> <check> <random> <code> <equivalence>]
[(do [! random.monad]
[expected <random>
- dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))]
+ dummy (|> <random> (random.only (|>> (at <equivalence> = expected) not)))]
(all _.and
(_.coverage [<query>]
(|> (/.result <query> (list (<code> expected)))
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual)))))
+ (at <equivalence> = expected actual)))))
(_.coverage [<check>]
(and (|> (/.result (<check> expected) (list (<code> expected)))
(!expect {try.#Success []}))
@@ -83,7 +83,7 @@
(!expect {try.#Failure _}))))
))]
- [/.any /.this (# ! each code.bit random.bit) function.identity code.equivalence]
+ [/.any /.this (at ! each code.bit random.bit) function.identity code.equivalence]
[/.bit /.this_bit random.bit code.bit bit.equivalence]
[/.nat /.this_nat random.nat code.nat nat.equivalence]
[/.int /.this_int random.int code.int int.equivalence]
@@ -103,8 +103,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 (at nat.equivalence = expected_left actual_left)
+ (at int.equivalence = expected_right actual_right)))))))]
[/.form code.form]
[/.variant code.variant]
@@ -118,10 +118,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 (at nat.equivalence = expected_local actual_local)
+ (at int.equivalence = expected_global actual_global)))))))
(do [! random.monad]
- [dummy (# ! each code.bit random.bit)]
+ [dummy (at ! each code.bit random.bit)]
(_.coverage [/.end?]
(|> (/.result (do <>.monad
[pre /.end?
@@ -133,14 +133,14 @@
(!expect (^.multi {try.#Success verdict}
verdict)))))
(do [! random.monad]
- [dummy (# ! each code.bit random.bit)]
+ [dummy (at ! each code.bit random.bit)]
(_.coverage [/.end]
(and (|> (/.result /.end (list))
(!expect {try.#Success []}))
(|> (/.result /.end (list dummy))
(!expect {try.#Failure _})))))
(do [! random.monad]
- [expected (# ! each code.bit random.bit)]
+ [expected (at ! each code.bit random.bit)]
(_.coverage [/.next]
(|> (/.result (do <>.monad
[pre /.next
@@ -150,7 +150,7 @@
(list expected))
(!expect {try.#Success _}))))
(do [! random.monad]
- [expected (# ! each code.bit random.bit)]
+ [expected (at ! each code.bit random.bit)]
(_.coverage [/.not]
(and (|> (/.result (/.not /.nat) (list expected))
(!expect (^.multi {try.#Success actual}
diff --git a/stdlib/source/test/lux/control/parser/environment.lux b/stdlib/source/test/lux/control/parser/environment.lux
index 9b098cf1a..d009918c4 100644
--- a/stdlib/source/test/lux/control/parser/environment.lux
+++ b/stdlib/source/test/lux/control/parser/environment.lux
@@ -30,7 +30,7 @@
[expected random.nat]
(_.coverage [/.result]
(|> (/.result (//#in expected) /.empty)
- (# try.functor each (n.= expected))
+ (at try.functor each (n.= expected))
(try.else false))))
(do random.monad
[property (random.alphabetic 1)
@@ -39,7 +39,7 @@
(|> /.empty
(dictionary.has property expected)
(/.result (/.property property))
- (# try.functor each (text#= expected))
+ (at try.functor each (text#= expected))
(try.else false))))
(do random.monad
[property (random.alphabetic 1)]
diff --git a/stdlib/source/test/lux/control/parser/json.lux b/stdlib/source/test/lux/control/parser/json.lux
index 75a817481..6c2a0753a 100644
--- a/stdlib/source/test/lux/control/parser/json.lux
+++ b/stdlib/source/test/lux/control/parser/json.lux
@@ -48,23 +48,23 @@
(_.for [/.Parser])
(`` (all _.and
(do [! random.monad]
- [expected (# ! each (|>> {json.#String}) (random.unicode 1))]
+ [expected (at ! each (|>> {json.#String}) (random.unicode 1))]
(_.coverage [/.result /.any]
(|> (/.result /.any expected)
(!expect (^.multi {try.#Success actual}
- (# json.equivalence = expected actual))))))
+ (at json.equivalence = expected actual))))))
(_.coverage [/.null]
(|> (/.result /.null {json.#Null})
(!expect {try.#Success _})))
(~~ (template [<query> <test> <check> <random> <json> <equivalence>]
[(do [! random.monad]
[expected <random>
- dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))]
+ dummy (|> <random> (random.only (|>> (at <equivalence> = expected) not)))]
(all _.and
(_.coverage [<query>]
(|> (/.result <query> {<json> expected})
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual)))))
+ (at <equivalence> = expected actual)))))
(_.coverage [<test>]
(and (|> (/.result (<test> expected) {<json> expected})
(!expect {try.#Success #1}))
@@ -89,7 +89,7 @@
(exception.match? /.unexpected_value error))))))
(do [! random.monad]
[expected (random.unicode 1)
- dummy (|> (random.unicode 1) (random.only (|>> (# text.equivalence = expected) not)))]
+ dummy (|> (random.unicode 1) (random.only (|>> (at text.equivalence = expected) not)))]
(_.coverage [/.value_mismatch]
(|> (/.result (/.this_string expected) {json.#String dummy})
(!expect (^.multi {try.#Failure error}
@@ -99,22 +99,22 @@
(_.coverage [/.nullable]
(and (|> (/.result (/.nullable /.string) {json.#Null})
(!expect (^.multi {try.#Success actual}
- (# (maybe.equivalence text.equivalence) = {.#None} actual))))
+ (at (maybe.equivalence text.equivalence) = {.#None} actual))))
(|> (/.result (/.nullable /.string) {json.#String expected})
(!expect (^.multi {try.#Success actual}
- (# (maybe.equivalence text.equivalence) = {.#Some expected} actual)))))))
+ (at (maybe.equivalence text.equivalence) = {.#Some expected} actual)))))))
(do [! random.monad]
- [size (# ! each (n.% 10) random.nat)
+ [size (at ! each (n.% 10) random.nat)
expected (|> (random.unicode 1)
(random.list size)
- (# ! each sequence.of_list))]
+ (at ! each sequence.of_list))]
(_.coverage [/.array]
(|> (/.result (/.array (<>.some /.string))
{json.#Array (sequence#each (|>> {json.#String}) expected)})
(!expect (^.multi {try.#Success actual}
- (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual)))))))
+ (at (sequence.equivalence text.equivalence) = expected (sequence.of_list actual)))))))
(do [! random.monad]
- [expected (# ! each (|>> {json.#String}) (random.unicode 1))]
+ [expected (at ! each (|>> {json.#String}) (random.unicode 1))]
(_.coverage [/.unconsumed_input]
(|> (/.result (/.array /.any) {json.#Array (sequence expected expected)})
(!expect (^.multi {try.#Failure error}
@@ -128,13 +128,13 @@
expected_number ..safe_frac
expected_string (random.unicode 1)
[boolean_field number_field string_field] (|> (random.set text.hash 3 (random.unicode 3))
- (# ! each (|>> set.list
- (pipe.case
- (pattern (list boolean_field number_field string_field))
- [boolean_field number_field string_field]
+ (at ! each (|>> set.list
+ (pipe.case
+ (pattern (list boolean_field number_field string_field))
+ [boolean_field number_field string_field]
- _
- (undefined)))))]
+ _
+ (undefined)))))]
(_.coverage [/.object /.field]
(|> (/.result (/.object (all <>.and
(/.field boolean_field /.boolean)
@@ -146,11 +146,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 (at bit.equivalence = expected_boolean actual_boolean)
+ (at frac.equivalence = expected_number actual_number)
+ (at text.equivalence = expected_string actual_string)))))))
(do [! random.monad]
- [size (# ! each (n.% 10) random.nat)
+ [size (at ! each (n.% 10) random.nat)
keys (random.list size (random.unicode 1))
values (random.list size (random.unicode 1))
.let [expected (dictionary.of_list text.hash (list.zipped_2 keys values))]]
@@ -162,5 +162,5 @@
(list.zipped_2 keys)
(dictionary.of_list text.hash))})
(!expect (^.multi {try.#Success actual}
- (# (dictionary.equivalence text.equivalence) = expected actual))))))
+ (at (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 8e974ad33..7046d5d1d 100644
--- a/stdlib/source/test/lux/control/parser/synthesis.lux
+++ b/stdlib/source/test/lux/control/parser/synthesis.lux
@@ -55,9 +55,9 @@
(def: random_environment
(Random (Environment Synthesis))
(do [! random.monad]
- [size (# ! each (n.% 5) random.nat)]
+ [size (at ! each (n.% 5) random.nat)]
(|> ..random_variable
- (# ! each (|>> synthesis.variable))
+ (at ! each (|>> synthesis.variable))
(random.list size))))
(def: simple
@@ -66,12 +66,12 @@
(~~ (template [<query> <check> <random> <synthesis> <equivalence>]
[(do [! random.monad]
[expected <random>
- dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))]
+ dummy (|> <random> (random.only (|>> (at <equivalence> = expected) not)))]
(all _.and
(_.coverage [<query>]
(|> (/.result <query> (list (<synthesis> expected)))
(!expect (^.multi {try.#Success actual}
- (# <equivalence> = expected actual)))))
+ (at <equivalence> = expected actual)))))
(_.coverage [<check>]
(and (|> (/.result (<check> expected) (list (<synthesis> expected)))
(!expect {try.#Success _}))
@@ -105,10 +105,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 (at bit.equivalence = expected_bit actual_bit)
+ (at i64.equivalence = expected_i64 actual_i64)
+ (at frac.equivalence = expected_f64 actual_f64)
+ (at text.equivalence = expected_text actual_text)))))
(|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text))
(list (synthesis.text expected_text)))
(!expect (^.multi {try.#Failure error}
@@ -121,10 +121,10 @@
(and (|> (/.result (/.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 (at (list.equivalence synthesis.equivalence) =
+ expected_environment
+ actual_environment)
+ (at text.equivalence = expected_body actual_body)))))
(|> (/.result (/.function arity /.text)
(list (synthesis.text expected_body)))
(!expect (^.multi {try.#Failure error}
@@ -139,7 +139,7 @@
(!expect (^.multi {try.#Failure error}
(exception.match? /.wrong_arity error))))))
(do [! random.monad]
- [arity (# ! each (|>> (n.% 10) ++) random.nat)
+ [arity (at ! each (|>> (n.% 10) ++) random.nat)
expected_offset random.nat
expected_inits (random.list arity random.bit)
expected_body (random.unicode 1)]
@@ -149,11 +149,11 @@
(list#each (|>> 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 (at n.equivalence = expected_offset actual_offset)
+ (at (list.equivalence bit.equivalence) =
+ expected_inits
+ actual_inits)
+ (at text.equivalence = expected_body actual_body)))))
(|> (/.result (/.loop (<>.many /.bit) /.text)
(list (synthesis.text expected_body)))
(!expect (^.multi {try.#Failure error}
@@ -166,23 +166,23 @@
(_.for [/.Parser])
(all _.and
(do [! random.monad]
- [expected (# ! each (|>> synthesis.i64) random.i64)]
+ [expected (at ! each (|>> synthesis.i64) random.i64)]
(_.coverage [/.result /.any]
(|> (/.result /.any (list expected))
(!expect (^.multi {try.#Success actual}
- (# synthesis.equivalence = expected actual))))))
+ (at synthesis.equivalence = expected actual))))))
(_.coverage [/.empty_input]
(|> (/.result /.any (list))
(!expect (^.multi {try.#Failure error}
(exception.match? /.empty_input error)))))
(do [! random.monad]
- [expected (# ! each (|>> synthesis.i64) random.i64)]
+ [expected (at ! each (|>> synthesis.i64) random.i64)]
(_.coverage [/.unconsumed_input]
(|> (/.result /.any (list expected expected))
(!expect (^.multi {try.#Failure error}
(exception.match? /.unconsumed_input error))))))
(do [! random.monad]
- [dummy (# ! each (|>> synthesis.i64) random.i64)]
+ [dummy (at ! each (|>> synthesis.i64) random.i64)]
(_.coverage [/.end /.expected_empty_input]
(and (|> (/.result /.end (list))
(!expect {try.#Success _}))
@@ -190,7 +190,7 @@
(!expect (^.multi {try.#Failure error}
(exception.match? /.expected_empty_input error)))))))
(do [! random.monad]
- [dummy (# ! each (|>> synthesis.i64) random.i64)]
+ [dummy (at ! each (|>> synthesis.i64) random.i64)]
(_.coverage [/.end?]
(and (|> (/.result /.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 af56ad878..55a334421 100644
--- a/stdlib/source/test/lux/control/parser/text.lux
+++ b/stdlib/source/test/lux/control/parser/text.lux
@@ -62,7 +62,7 @@
(-> Text (/.Parser Text) Bit)
(|> expected
(/.result parser)
- (# try.functor each (text#= expected))
+ (at try.functor each (text#= expected))
(try.else false)))
(def: (should_pass! expected parser)
@@ -73,13 +73,13 @@
Test
(all _.and
(do [! random.monad]
- [offset (# ! each (n.% 50) random.nat)
- range (# ! each (|>> (n.% 50) (n.+ 10)) random.nat)
+ [offset (at ! each (n.% 50) random.nat)
+ range (at ! each (|>> (n.% 50) (n.+ 10)) random.nat)
.let [limit (n.+ offset range)]
- expected (# ! each (|>> (n.% range) (n.+ offset) text.of_char) random.nat)
+ expected (at ! each (|>> (n.% range) (n.+ offset) text.of_char) random.nat)
out_of_range (case offset
- 0 (# ! each (|>> (n.% 10) ++ (n.+ limit) text.of_char) random.nat)
- _ (# ! each (|>> (n.% offset) text.of_char) random.nat))]
+ 0 (at ! each (|>> (n.% 10) ++ (n.+ limit) text.of_char) random.nat)
+ _ (at ! each (|>> (n.% offset) text.of_char) random.nat))]
(_.coverage [/.range]
(and (..should_pass expected (/.range offset limit))
(..should_fail out_of_range (/.range offset limit)))))
@@ -98,22 +98,22 @@
(and (..should_pass (text.of_char expected) /.lower)
(..should_fail (text.of_char invalid) /.lower))))
(do [! random.monad]
- [expected (# ! each (n.% 10) random.nat)
+ [expected (at ! each (n.% 10) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [/.decimal]
- (and (..should_pass (# n.decimal encoded expected) /.decimal)
+ (and (..should_pass (at n.decimal encoded expected) /.decimal)
(..should_fail (text.of_char invalid) /.decimal))))
(do [! random.monad]
- [expected (# ! each (n.% 8) random.nat)
+ [expected (at ! each (n.% 8) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [/.octal]
- (and (..should_pass (# n.octal encoded expected) /.octal)
+ (and (..should_pass (at n.octal encoded expected) /.octal)
(..should_fail (text.of_char invalid) /.octal))))
(do [! random.monad]
- [expected (# ! each (n.% 16) random.nat)
+ [expected (at ! each (n.% 16) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [/.hexadecimal]
- (and (..should_pass (# n.hex encoded expected) /.hexadecimal)
+ (and (..should_pass (at n.hex encoded expected) /.hexadecimal)
(..should_fail (text.of_char invalid) /.hexadecimal))))
(do [! random.monad]
[expected (random.char unicode.alphabetic)
@@ -156,14 +156,14 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set n.hash num_options)
- (# ! each (|>> set.list
- (list#each text.of_char)
- text.together)))
- expected (# ! each (function (_ value)
- (|> options
- (text.char (n.% num_options value))
- maybe.trusted))
- random.nat)
+ (at ! each (|>> set.list
+ (list#each text.of_char)
+ text.together)))
+ expected (at ! each (function (_ value)
+ (|> options
+ (text.char (n.% num_options value))
+ maybe.trusted))
+ random.nat)
invalid (random.only (function (_ char)
(not (text.contains? (text.of_char char) options)))
(random.char unicode.character))]
@@ -182,14 +182,14 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set n.hash num_options)
- (# ! each (|>> set.list
- (list#each text.of_char)
- text.together)))
- invalid (# ! each (function (_ value)
- (|> options
- (text.char (n.% num_options value))
- maybe.trusted))
- random.nat)
+ (at ! each (|>> set.list
+ (list#each text.of_char)
+ text.together)))
+ invalid (at ! each (function (_ value)
+ (|> options
+ (text.char (n.% num_options value))
+ maybe.trusted))
+ random.nat)
expected (random.only (function (_ char)
(not (text.contains? (text.of_char char) options)))
(random.char unicode.character))]
@@ -211,26 +211,26 @@
(let [octal! (/.one_of! "01234567")]
(all _.and
(do [! random.monad]
- [left (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)
- right (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)
+ [left (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)
+ right (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)
.let [expected (format left right)]
invalid (|> random.nat
- (# ! each (n.% 16))
+ (at ! each (n.% 16))
(random.only (n.>= 8))
- (# ! each (# n.hex encoded)))]
+ (at ! each (at n.hex encoded)))]
(_.coverage [/.many /.many!]
(and (..should_pass expected (/.many /.octal))
(..should_fail invalid (/.many /.octal))
(..should_pass! expected (/.many! octal!)))))
(do [! random.monad]
- [left (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)
- right (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)
+ [left (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)
+ right (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)
.let [expected (format left right)]
invalid (|> random.nat
- (# ! each (n.% 16))
+ (at ! each (n.% 16))
(random.only (n.>= 8))
- (# ! each (# n.hex encoded)))]
+ (at ! each (at n.hex encoded)))]
(_.coverage [/.some /.some!]
(and (..should_pass expected (/.some /.octal))
(..should_pass "" (/.some /.octal))
@@ -239,7 +239,7 @@
(..should_pass! expected (/.some! octal!))
(..should_pass! "" (/.some! octal!)))))
(do [! random.monad]
- [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)]
+ [.let [octal (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -252,7 +252,7 @@
(..should_fail (format first second third) (/.exactly! 2 octal!))
(..should_fail (format first) (/.exactly! 2 octal!)))))
(do [! random.monad]
- [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)]
+ [.let [octal (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -265,7 +265,7 @@
(..should_pass! (format first) (/.at_most! 2 octal!))
(..should_fail (format first second third) (/.at_most! 2 octal!)))))
(do [! random.monad]
- [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)]
+ [.let [octal (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -278,7 +278,7 @@
(..should_pass! (format first second third) (/.at_least! 2 octal!))
(..should_fail (format first) (/.at_least! 2 octal!)))))
(do [! random.monad]
- [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)]
+ [.let [octal (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -390,7 +390,7 @@
(/.this output)))
(!expect {try.#Success _}))))
(do [! random.monad]
- [expected (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)]
+ [expected (at ! each (|>> (n.% 8) (at n.octal encoded)) random.nat)]
(_.coverage [/.then]
(|> (list (code.text expected))
(<c>.result (/.then /.octal <c>.text))
diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux
index 779c63cd2..2d871bdef 100644
--- a/stdlib/source/test/lux/control/parser/type.lux
+++ b/stdlib/source/test/lux/control/parser/type.lux
@@ -36,8 +36,8 @@
(def: primitive
(Random Type)
(|> (random.alpha_numeric 1)
- (# random.monad each (function (_ name)
- {.#Primitive name (list)}))))
+ (at random.monad each (function (_ name)
+ {.#Primitive name (list)}))))
(def: test|matches
Test
@@ -144,14 +144,14 @@
(/.with_extension argument)
/.any)
not_parameter)
- (!expect (^.multi {try.#Success [quantification##binding argument##binding actual]}
+ (!expect (^.multi {try.#Success [quantification::binding argument::binding actual]}
(same? not_parameter actual)))))
(_.coverage [/.parameter]
(|> (/.result (<| (/.with_extension quantification)
(/.with_extension argument)
/.parameter)
{.#Parameter 0})
- (!expect {try.#Success [quantification##binding argument##binding _]})))
+ (!expect {try.#Success [quantification::binding argument::binding _]})))
(_.coverage [/.argument]
(let [argument? (is (-> Nat Nat Bit)
(function (_ @ expected)
@@ -181,14 +181,14 @@
(/.with_extension argument)
(/.this_parameter 0))
{.#Parameter 0})
- (!expect {try.#Success [quantification##binding argument##binding _]})))
+ (!expect {try.#Success [quantification::binding argument::binding _]})))
)))
(def: test|polymorphic
Test
(do [! random.monad]
[not_polymorphic ..primitive
- expected_inputs (# ! each (|>> (n.% 10) ++) random.nat)]
+ expected_inputs (at ! each (|>> (n.% 10) ++) random.nat)]
(all _.and
(_.coverage [/.not_polymorphic]
(and (|> (/.result (/.polymorphic /.any)
diff --git a/stdlib/source/test/lux/control/parser/xml.lux b/stdlib/source/test/lux/control/parser/xml.lux
index 95e6c3713..57833948e 100644
--- a/stdlib/source/test/lux/control/parser/xml.lux
+++ b/stdlib/source/test/lux/control/parser/xml.lux
@@ -71,7 +71,7 @@
[[(//#in expected)
{xml.#Text expected}]])
(do [! random.monad]
- [expected (# ! each (|>> {xml.#Text}) (random.alphabetic 1))]
+ [expected (at ! each (|>> {xml.#Text}) (random.alphabetic 1))]
(_.coverage [/.any]
(|> (/.result /.any (list expected))
(try#each (xml#= expected))
@@ -161,7 +161,7 @@
(//#in []))
_ (//.some /.any)]
(in [])))]
- repetitions (# ! each (n.% 10) random.nat)]
+ repetitions (at ! each (n.% 10) random.nat)]
(all _.and
(_.coverage [/.somewhere]
(|> (/.result parser
diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux
index 458c74381..258436915 100644
--- a/stdlib/source/test/lux/control/region.lux
+++ b/stdlib/source/test/lux/control/region.lux
@@ -81,7 +81,7 @@
(<| (_.covering /._)
(_.for [/.Region])
(do [! random.monad]
- [expected_clean_ups (|> random.nat (# ! each (|>> (n.% 100) (n.max 1))))]
+ [expected_clean_ups (|> random.nat (at ! each (|>> (n.% 100) (n.max 1))))]
(all _.and
(_.for [/.functor]
($functor.spec ..injection ..comparison (is (All (_ ! r)
diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux
index efd4a029c..8e188702b 100644
--- a/stdlib/source/test/lux/control/security/policy.lux
+++ b/stdlib/source/test/lux/control/security/policy.lux
@@ -61,7 +61,7 @@
(%#can_downgrade sample)))))
(def: hash
(|>> %#can_downgrade
- (# text.hash hash)))))
+ (at text.hash hash)))))
(def: password
%#can_upgrade)
@@ -77,24 +77,24 @@
(do random.monad
[.let [policy_0 (policy [])]
raw_password (random.ascii 10)
- .let [password (# policy_0 password raw_password)]]
+ .let [password (at policy_0 password raw_password)]]
(all _.and
(_.for [/.Privacy /.Private /.Can_Conceal /.Can_Reveal
/.Safety /.Safe /.Can_Trust /.Can_Distrust]
(all _.and
(_.for [/.functor]
- ($functor.spec (..injection (# policy_0 #can_upgrade)) (..comparison (# policy_0 #can_downgrade)) /.functor))
+ ($functor.spec (..injection (at policy_0 #can_upgrade)) (..comparison (at policy_0 #can_downgrade)) /.functor))
(_.for [/.apply]
- ($apply.spec (..injection (# policy_0 #can_upgrade)) (..comparison (# policy_0 #can_downgrade)) /.apply))
+ ($apply.spec (..injection (at policy_0 #can_upgrade)) (..comparison (at policy_0 #can_downgrade)) /.apply))
(_.for [/.monad]
- ($monad.spec (..injection (# policy_0 #can_upgrade)) (..comparison (# policy_0 #can_downgrade)) /.monad))))
+ ($monad.spec (..injection (at policy_0 #can_upgrade)) (..comparison (at policy_0 #can_downgrade)) /.monad))))
(_.coverage [/.Privilege /.Context /.with_policy]
- (and (# policy_0 = password password)
- (n.= (# text.hash hash raw_password)
- (# policy_0 hash password))))
+ (and (at policy_0 = password password)
+ (n.= (at text.hash hash raw_password)
+ (at policy_0 hash password))))
(let [policy_1 (policy [])
- delegate (/.delegation (# policy_0 #can_downgrade) (# policy_1 #can_upgrade))]
+ delegate (/.delegation (at policy_0 #can_downgrade) (at policy_1 #can_upgrade))]
(_.coverage [/.Delegation /.delegation]
- (# policy_1 = (delegate password) (delegate password))))
+ (at 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 8fa9abe69..81c10a970 100644
--- a/stdlib/source/test/lux/control/state.lux
+++ b/stdlib/source/test/lux/control/state.lux
@@ -81,7 +81,7 @@
(def: loops
Test
(do [! random.monad]
- [limit (|> random.nat (# ! each (n.% 10)))
+ [limit (|> random.nat (at ! each (n.% 10)))
.let [condition (do /.monad
[state /.get]
(in (n.< limit state)))]]
diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux
index a4c2622dc..7d7e9ae43 100644
--- a/stdlib/source/test/lux/control/thread.lux
+++ b/stdlib/source/test/lux/control/thread.lux
@@ -19,7 +19,7 @@
(def: (injection value)
(Injection (All (_ a !) (Thread ! a)))
- (# /.monad in value))
+ (at /.monad in value))
(def: comparison
(Comparison (All (_ a !) (Thread ! a)))
@@ -38,12 +38,12 @@
(_.coverage [/.result]
(n.= sample
(|> sample
- (# /.monad in)
+ (at /.monad in)
/.result)))
(_.coverage [/.io]
(n.= sample
(|> sample
- (# /.monad in)
+ (at /.monad in)
/.io
io.run!)))
diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux
index 043890c39..d448bedc2 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 ==) =)))
+ (at (/.equivalence ==) =)))
(def: .public (attempt 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 78d475ce1..986ffa366 100644
--- a/stdlib/source/test/lux/control/writer.lux
+++ b/stdlib/source/test/lux/control/writer.lux
@@ -24,7 +24,7 @@
(def: (injection monoid value)
(All (_ w) (-> (Monoid w) (Injection (Writer w))))
- [(# monoid identity) value])
+ [(at monoid identity) value])
(def: comparison
(All (_ w) (Comparison (Writer w)))