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.lux4
-rw-r--r--stdlib/source/test/lux/control/concurrency/async.lux2
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux10
-rw-r--r--stdlib/source/test/lux/control/concurrency/semaphore.lux24
-rw-r--r--stdlib/source/test/lux/control/concurrency/stm.lux4
-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.lux4
-rw-r--r--stdlib/source/test/lux/control/function/mutual.lux4
-rw-r--r--stdlib/source/test/lux/control/lazy.lux2
-rw-r--r--stdlib/source/test/lux/control/maybe.lux2
-rw-r--r--stdlib/source/test/lux/control/parser.lux36
-rw-r--r--stdlib/source/test/lux/control/parser/analysis.lux2
-rw-r--r--stdlib/source/test/lux/control/parser/binary.lux32
-rw-r--r--stdlib/source/test/lux/control/parser/cli.lux2
-rw-r--r--stdlib/source/test/lux/control/parser/code.lux8
-rw-r--r--stdlib/source/test/lux/control/parser/environment.lux4
-rw-r--r--stdlib/source/test/lux/control/parser/json.lux24
-rw-r--r--stdlib/source/test/lux/control/parser/synthesis.lux20
-rw-r--r--stdlib/source/test/lux/control/parser/text.lux72
-rw-r--r--stdlib/source/test/lux/control/parser/type.lux6
-rw-r--r--stdlib/source/test/lux/control/parser/xml.lux6
-rw-r--r--stdlib/source/test/lux/control/region.lux18
-rw-r--r--stdlib/source/test/lux/control/remember.lux4
-rw-r--r--stdlib/source/test/lux/control/state.lux2
27 files changed, 153 insertions, 153 deletions
diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux
index 93c68faff..c5c66d2fc 100644
--- a/stdlib/source/test/lux/control/concurrency/actor.lux
+++ b/stdlib/source/test/lux/control/concurrency/actor.lux
@@ -200,9 +200,9 @@
verdict)))
(do !
- [num_events (\ ! map (|>> (n.% 10) ++) random.nat)
+ [num_events (\ ! each (|>> (n.% 10) ++) random.nat)
events (random.list num_events random.nat)
- num_observations (\ ! map (n.% num_events) random.nat)
+ num_observations (\ ! each (n.% num_events) random.nat)
.let [expected (list.first num_observations events)
sink (: (Atom (Row Nat))
(atom.atom row.empty))]]
diff --git a/stdlib/source/test/lux/control/concurrency/async.lux b/stdlib/source/test/lux/control/concurrency/async.lux
index f9b917ee5..c6a858a5d 100644
--- a/stdlib/source/test/lux/control/concurrency/async.lux
+++ b/stdlib/source/test/lux/control/concurrency/async.lux
@@ -54,7 +54,7 @@
Test
(<| (_.covering /._)
(do {! random.monad}
- [waiting_time (|> random.nat (\ ! map (|>> (n.% ..delay) (n.+ ..delay))))
+ [waiting_time (|> random.nat (\ ! 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 174c8adc7..ad508df7b 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -59,7 +59,7 @@
(in #.End)
(#.Some [head tail])
- (\ ! map (|>> (#.Item head))
+ (\ ! each (|>> (#.Item head))
(take_amount (-- amount_of_polls) [channel sink]))))))
(def: .public test
@@ -152,12 +152,12 @@
(do !
[_ (!signal [])]
(in #.None)))))
- (/.sequential 0 (list\compose inputs inputs))))
+ (/.sequential 0 (list\composite inputs inputs))))
_ ?signal
listened (|> sink
atom.read!
async.future
- (\ ! map row.list))]
+ (\ ! each row.list))]
(_.cover' [/.Subscriber /.subscribe!]
(list\= inputs listened))))
(in (do async.monad
@@ -189,8 +189,8 @@
(list\= (list distint/0 distint/1 distint/2)
actual))))
(do !
- [polling_delay (\ ! map (|>> (n.% 10) ++) random.nat)
- amount_of_polls (\ ! map (|>> (n.% 10) ++) random.nat)]
+ [polling_delay (\ ! each (|>> (n.% 10) ++) random.nat)
+ amount_of_polls (\ ! each (|>> (n.% 10) ++) random.nat)]
($_ _.and
(in (do {! async.monad}
[actual (..take_amount amount_of_polls (/.poll polling_delay (: (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 b4b07bbb0..796a1604e 100644
--- a/stdlib/source/test/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux
@@ -39,7 +39,7 @@
(_.for [/.Semaphore]
($_ _.and
(do {! random.monad}
- [initial_open_positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (\ ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do async.monad
[result (async.within ..delay (/.wait! semaphore))]
@@ -51,10 +51,10 @@
#.None
false)))))
(do {! random.monad}
- [initial_open_positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (\ ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do {! async.monad}
- [_ (monad.map ! /.wait! (list.repeated initial_open_positions semaphore))
+ [_ (monad.each ! /.wait! (list.repeated initial_open_positions semaphore))
result (async.within ..delay (/.wait! semaphore))]
(_.cover' [/.wait!]
(case result
@@ -64,10 +64,10 @@
#.None
true)))))
(do {! random.monad}
- [initial_open_positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (\ ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do {! async.monad}
- [_ (monad.map ! /.wait! (list.repeated initial_open_positions semaphore))
+ [_ (monad.each ! /.wait! (list.repeated initial_open_positions semaphore))
.let [block (/.wait! semaphore)]
result/0 (async.within ..delay block)
open_positions (/.signal! semaphore)
@@ -80,7 +80,7 @@
_
false)))))
(do {! random.monad}
- [initial_open_positions (|> random.nat (\ ! map (|>> (n.% 10) (n.max 1))))
+ [initial_open_positions (|> random.nat (\ ! each (|>> (n.% 10) (n.max 1))))
.let [semaphore (/.semaphore initial_open_positions)]]
(in (do async.monad
[outcome (/.signal! semaphore)]
@@ -98,7 +98,7 @@
(_.for [/.Mutex]
($_ _.and
(do {! random.monad}
- [repetitions (|> random.nat (\ ! map (|>> (n.% 100) (n.max 10))))
+ [repetitions (|> random.nat (\ ! 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"))
@@ -155,7 +155,7 @@
_
false)))
(do {! random.monad}
- [limit (\ ! map (|>> (n.% 9) ++) random.nat)
+ [limit (\ ! each (|>> (n.% 9) ++) random.nat)
.let [barrier (/.barrier (maybe.trusted (/.limit limit)))
resource (atom.atom "")]]
(in (do {! async.monad}
@@ -165,10 +165,10 @@
text.together)
expected_ids (enum.range n.enum 0 (-- limit))]
_ (|> expected_ids
- (list\map (function (_ id)
- (exec
- (io.run! (atom.update! (|>> (format suffix)) resource))
- (waiter resource barrier id))))
+ (list\each (function (_ id)
+ (exec
+ (io.run! (atom.update! (|>> (format suffix)) resource))
+ (waiter resource barrier id))))
(monad.all !))
.let [outcome (io.run! (atom.read! resource))]]
(_.cover' [/.barrier /.block!]
diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux
index f3a5c618c..8d56cbed2 100644
--- a/stdlib/source/test/lux/control/concurrency/stm.lux
+++ b/stdlib/source/test/lux/control/concurrency/stm.lux
@@ -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 (\ ! each (n.% 100)))]
($_ _.and
(_.for [/.functor]
($functor.spec ..injection ..comparison /.functor))
@@ -94,7 +94,7 @@
(in (let [var (/.var 0)]
(do {! async.monad}
[_ (|> (list.repeated iterations_per_process [])
- (list\map (function (_ _) (/.commit! (/.update ++ var))))
+ (list\each (function (_ _) (/.commit! (/.update ++ var))))
(monad.all !))
cummulative (/.commit! (/.read var))]
(_.cover' [/.STM]
diff --git a/stdlib/source/test/lux/control/concurrency/thread.lux b/stdlib/source/test/lux/control/concurrency/thread.lux
index bee49206d..42c4c2d9f 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 (\ ! map (|>> (n.% 5) (n.+ 5))
+ delay (\ ! each (|>> (n.% 5) (n.+ 5))
random.nat)]
($_ _.and
(_.cover [/.parallelism]
diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux
index 74e73f45b..aacd0ab5a 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 (\ ! map %.nat random.nat)]
+ .let [report_element (\ ! 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 4450991ec..714d33949 100644
--- a/stdlib/source/test/lux/control/function.lux
+++ b/stdlib/source/test/lux/control/function.lux
@@ -25,8 +25,8 @@
Test
(do {! random.monad}
[expected random.nat
- f0 (\ ! map n.+ random.nat)
- f1 (\ ! map n.* random.nat)
+ f0 (\ ! each n.+ random.nat)
+ f1 (\ ! each n.* random.nat)
dummy random.nat
extra (|> random.nat (random.only (|>> (n.= expected) not)))]
(<| (_.covering /._)
@@ -37,7 +37,7 @@
(n.= (left extra)
(right extra)))))
generator (: (Random (-> Nat Nat))
- (\ ! map n.- random.nat))]
+ (\ ! each n.- random.nat))]
(_.for [/.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 3941998fc..ca4d06e2d 100644
--- a/stdlib/source/test/lux/control/function/memo.lux
+++ b/stdlib/source/test/lux/control/function/memo.lux
@@ -58,7 +58,7 @@
Test
(<| (_.covering /._)
(do {! random.monad}
- [input (|> random.nat (\ ! map (|>> (n.% 5) (n.+ 21))))])
+ [input (|> random.nat (\ ! each (|>> (n.% 5) (n.+ 21))))])
(_.for [/.Memo])
($_ _.and
(_.cover [/.closed /.none]
@@ -111,7 +111,7 @@
[output' (recur (-- input))]
(in (n.* input output')))))))
expected (|> (list.indices input)
- (list\map ++)
+ (list\each ++)
(list\mix n.* 1))
actual (|> (memo input)
(state.result (dictionary.empty n.hash))
diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux
index 001626888..533f88072 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 (\ ! each (|>> (n.% 6) (n.+ 20))))
dummy random.nat
shift (|> random.nat (random.only (|>> (n.= dummy) not)))
.let [equivalence (: (Equivalence (/.Mixin Nat Nat))
@@ -39,7 +39,7 @@
(in (function (_ delegate recur input)
output))))
expected (|> (list.indices input)
- (list\map ++)
+ (list\each ++)
(list\mix n.* 1))]])
($_ _.and
(_.for [/.Mixin]
diff --git a/stdlib/source/test/lux/control/function/mutual.lux b/stdlib/source/test/lux/control/function/mutual.lux
index 4fe2e4219..2e24285ef 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 (\ ! map (n.% 10) random.nat)
+ [sample (\ ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
(<| (_.cover [/.let])
(/.let [(even? number)
@@ -51,7 +51,7 @@
(def: test_def
Test
(do {! random.monad}
- [sample (\ ! map (n.% 10) random.nat)
+ [sample (\ ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
(<| (_.cover [/.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 ea1b1f787..bc1ed13d0 100644
--- a/stdlib/source/test/lux/control/lazy.lux
+++ b/stdlib/source/test/lux/control/lazy.lux
@@ -29,7 +29,7 @@
(def: .public lazy
(All [a] (-> (Random a) (Random (Lazy a))))
- (\ random.functor map (|>> /.lazy)))
+ (\ 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 6f4213268..291d61adf 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 map (|>> #.Some))
+ (\ random.monad each (|>> #.Some))
($hash.spec (/.hash n.hash))))
(_.for [/.monoid]
($monoid.spec (/.equivalence n.equivalence) /.monoid (random.maybe random.nat)))
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index e37a2f355..fd29bd07b 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 (\ ! map (|>> (n.max 1) (n.min 20)) random.nat)
+ variadic (\ ! 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)
@@ -106,16 +106,16 @@
(match #.None
#1))))
(_.cover [/.some]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.some <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) = expected+ actual)))
- (|> (list\map (|>> .int code.int) expected+)
+ (|> (list\each (|>> .int code.int) expected+)
(/.result (/.some <code>.nat))
(match #.End
#1))))
(_.cover [/.many]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.many <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) = expected+ actual)))
@@ -123,7 +123,7 @@
(/.result (/.many <code>.nat))
(match (list actual)
(n.= expected0 actual)))
- (|> (list\map (|>> .int code.int) expected+)
+ (|> (list\each (|>> .int code.int) expected+)
(/.result (/.many <code>.nat))
fails?)))
(_.cover [/.only]
@@ -180,72 +180,72 @@
(def: combinators_1
Test
(do {! random.monad}
- [variadic (\ ! map (|>> (n.max 1) (n.min 20)) random.nat)
- times (\ ! map (n.% variadic) random.nat)
+ [variadic (\ ! each (|>> (n.max 1) (n.min 20)) random.nat)
+ times (\ ! each (n.% variadic) random.nat)
expected random.nat
wrong (|> random.nat (random.only (|>> (n.= expected) not)))
expected+ (random.list variadic random.nat)
separator (random.ascii 1)]
($_ _.and
(_.cover [/.exactly]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.exactly times <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) =
(list.first times expected+)
actual)))
- (|> (list\map code.nat expected+)
+ (|> (list\each code.nat expected+)
(/.result (/.exactly (++ variadic) <code>.nat))
fails?)))
(_.cover [/.at_least]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.at_least times <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) =
expected+
actual)))
- (|> (list\map code.nat expected+)
+ (|> (list\each code.nat expected+)
(/.result (/.at_least (++ variadic) <code>.nat))
fails?)))
(_.cover [/.at_most]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.at_most times <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) =
(list.first times expected+)
actual)))
- (|> (list\map code.nat expected+)
+ (|> (list\each code.nat expected+)
(/.result (/.at_most (++ variadic) <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) =
expected+
actual)))))
(_.cover [/.between]
- (and (|> (list\map code.nat expected+)
+ (and (|> (list\each code.nat expected+)
(/.result (/.between times (n.- times variadic) <code>.nat))
(match actual
(\ (list.equivalence n.equivalence) =
expected+
actual)))
- (|> (list\map code.nat (list.first times expected+))
+ (|> (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)))))
(_.cover [/.separated_by]
- (|> (list.interposed (code.text separator) (list\map code.nat expected+))
+ (|> (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))))
(_.cover [/.remaining]
- (|> (list\map code.nat expected+)
+ (|> (list\each code.nat expected+)
(/.result /.remaining)
(match actual
(\ (list.equivalence code.equivalence) =
- (list\map code.nat expected+)
+ (list\each code.nat expected+)
actual))))
(_.cover [/.else]
(and (|> (/.result (/.else wrong (\ /.monad in expected)) (list))
diff --git a/stdlib/source/test/lux/control/parser/analysis.lux b/stdlib/source/test/lux/control/parser/analysis.lux
index 85ab04863..7cce374d0 100644
--- a/stdlib/source/test/lux/control/parser/analysis.lux
+++ b/stdlib/source/test/lux/control/parser/analysis.lux
@@ -53,7 +53,7 @@
[]
(`` ($_ _.and
(do {! random.monad}
- [expected (\ ! map (|>> analysis.bit) random.bit)]
+ [expected (\ ! each (|>> analysis.bit) random.bit)]
(_.cover [/.result /.any]
(|> (list expected)
(/.result /.any)
diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux
index a3c20dbde..cdb9a1572 100644
--- a/stdlib/source/test/lux/control/parser/binary.lux
+++ b/stdlib/source/test/lux/control/parser/binary.lux
@@ -92,7 +92,7 @@
(random.rec
(function (_ recur)
(let [random_sequence (do {! random.monad}
- [size (\ ! map (n.% 2) random.nat)]
+ [size (\ ! each (n.% 2) random.nat)]
(random.list size recur))]
($_ random.and
..random_location
@@ -109,7 +109,7 @@
random_sequence
random_sequence
(do {! random.monad}
- [size (\ ! map (n.% 2) random.nat)]
+ [size (\ ! each (n.% 2) random.nat)]
(random.list size (random.and recur recur)))
)))))))
@@ -128,7 +128,7 @@
(`` ($_ _.and
(~~ (template [<size> <parser> <format>]
[(do {! random.monad}
- [expected (\ ! map (i64.and (i64.mask <size>))
+ [expected (\ ! each (i64.and (i64.mask <size>))
random.nat)]
(_.cover [<size> <parser> <format>]
(|> (format.result <format> expected)
@@ -148,7 +148,7 @@
(`` ($_ _.and
(~~ (template [<parser> <format>]
[(do {! random.monad}
- [expected (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [<parser> <format>]
(|> (format.result <format> expected)
(/.result <parser>)
@@ -227,8 +227,8 @@
(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))
+ [expected (\ ! each (|>> (i64.and (i64.mask /.size/8))
+ (n.max 2))
random.nat)]
(_.cover [/.not_a_bit]
(|> expected
@@ -270,7 +270,7 @@
[/.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.repeated ..segment_size) random.nat)]
+ [expected (\ ! each (list.repeated ..segment_size) random.nat)]
(_.cover [/.set_elements_are_not_unique]
(|> expected
(format.result (format.list format.nat))
@@ -289,8 +289,8 @@
expected
actual))))))
(do {! random.monad}
- [tag (\ ! map (|>> (i64.and (i64.mask /.size/8))
- (n.max 2))
+ [tag (\ ! each (|>> (i64.and (i64.mask /.size/8))
+ (n.max 2))
random.nat)
value random.bit]
(_.cover [/.invalid_tag]
@@ -329,14 +329,14 @@
(/.result /.any)
(!expect (#try.Success _))))
(do {! random.monad}
- [data (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [/.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 (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [/.segment format.segment format.result]
(|> expected
(format.result (format.segment ..segment_size))
@@ -344,7 +344,7 @@
(!expect (^multi (#try.Success actual)
(\ binary.equivalence = expected actual))))))
(do {! random.monad}
- [data (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [/.end?]
(|> data
(/.result (do <>.monad
@@ -355,8 +355,8 @@
post))))
(!expect (#try.Success #1)))))
(do {! random.monad}
- [to_read (\ ! map (n.% (++ ..segment_size)) random.nat)
- data (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (\ ! each (n.% (++ ..segment_size)) random.nat)
+ data (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [/.Offset /.offset]
(|> data
(/.result (do <>.monad
@@ -370,8 +370,8 @@
(n.= ..segment_size nothing_left)))))
(!expect (#try.Success #1)))))
(do {! random.monad}
- [to_read (\ ! map (n.% (++ ..segment_size)) random.nat)
- data (\ ! map (\ utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (\ ! each (n.% (++ ..segment_size)) random.nat)
+ data (\ ! each (\ utf8.codec encoded) (random.ascii ..segment_size))]
(_.cover [/.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 9c1247775..a70abb3b4 100644
--- a/stdlib/source/test/lux/control/parser/cli.lux
+++ b/stdlib/source/test/lux/control/parser/cli.lux
@@ -31,7 +31,7 @@
(<| (_.covering /._)
(_.for [/.Parser])
(do {! random.monad}
- [expected (\ ! map n\encoded random.nat)
+ [expected (\ ! 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 b6a3768d4..99ea38f16 100644
--- a/stdlib/source/test/lux/control/parser/code.lux
+++ b/stdlib/source/test/lux/control/parser/code.lux
@@ -45,7 +45,7 @@
(_.for [/.Parser])
(`` ($_ _.and
(do {! random.monad}
- [expected (\ ! map code.bit random.bit)]
+ [expected (\ ! each code.bit random.bit)]
(_.cover [/.result]
(and (|> (/.result /.any (list expected))
(!expect (#try.Success _)))
@@ -67,7 +67,7 @@
(!expect (#try.Failure _)))))
))]
- [/.any /.this! (\ ! map code.bit random.bit) function.identity code.equivalence]
+ [/.any /.this! (\ ! each 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]
@@ -115,7 +115,7 @@
(and (\ nat.equivalence = expected_local actual_local)
(\ int.equivalence = expected_global actual_global)))))))
(do {! random.monad}
- [dummy (\ ! map code.bit random.bit)]
+ [dummy (\ ! each code.bit random.bit)]
(_.cover [/.end?]
(|> (/.result (do <>.monad
[pre /.end?
@@ -127,7 +127,7 @@
(!expect (^multi (#try.Success verdict)
verdict)))))
(do {! random.monad}
- [dummy (\ ! map code.bit random.bit)]
+ [dummy (\ ! each code.bit random.bit)]
(_.cover [/.end!]
(and (|> (/.result /.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 ba846b8b2..a1652a95f 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]
(_.cover [/.result]
(|> (/.result (//\in expected) /.empty)
- (\ try.functor map (n.= expected))
+ (\ try.functor each (n.= expected))
(try.else false))))
(do random.monad
[property (random.ascii/alpha 1)
@@ -39,7 +39,7 @@
(|> /.empty
(dictionary.has property expected)
(/.result (/.property property))
- (\ try.functor map (text\= expected))
+ (\ try.functor each (text\= expected))
(try.else 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 a87396228..043f00979 100644
--- a/stdlib/source/test/lux/control/parser/json.lux
+++ b/stdlib/source/test/lux/control/parser/json.lux
@@ -46,7 +46,7 @@
(_.for [/.Parser])
(`` ($_ _.and
(do {! random.monad}
- [expected (\ ! map (|>> #json.String) (random.unicode 1))]
+ [expected (\ ! each (|>> #json.String) (random.unicode 1))]
(_.cover [/.result /.any]
(|> (/.result /.any expected)
(!expect (^multi (#try.Success actual)
@@ -102,17 +102,17 @@
(!expect (^multi (#try.Success actual)
(\ (maybe.equivalence text.equivalence) = (#.Some expected) actual)))))))
(do {! random.monad}
- [size (\ ! map (n.% 10) random.nat)
+ [size (\ ! each (n.% 10) random.nat)
expected (|> (random.unicode 1)
(random.list size)
- (\ ! map row.of_list))]
+ (\ ! each row.of_list))]
(_.cover [/.array]
(|> (/.result (/.array (<>.some /.string))
- (#json.Array (row\map (|>> #json.String) expected)))
+ (#json.Array (row\each (|>> #json.String) expected)))
(!expect (^multi (#try.Success actual)
(\ (row.equivalence text.equivalence) = expected (row.of_list actual)))))))
(do {! random.monad}
- [expected (\ ! map (|>> #json.String) (random.unicode 1))]
+ [expected (\ ! each (|>> #json.String) (random.unicode 1))]
(_.cover [/.unconsumed_input]
(|> (/.result (/.array /.any) (#json.Array (row expected expected)))
(!expect (^multi (#try.Failure error)
@@ -126,12 +126,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.list
- (case> (^ (list boolean_field number_field string_field))
- [boolean_field number_field string_field]
+ (\ ! each (|>> set.list
+ (case> (^ (list boolean_field number_field string_field))
+ [boolean_field number_field string_field]
- _
- (undefined)))))]
+ _
+ (undefined)))))]
(_.cover [/.object /.field]
(|> (/.result (/.object ($_ <>.and
(/.field boolean_field /.boolean)
@@ -147,7 +147,7 @@
(\ frac.equivalence = expected_number actual_number)
(\ text.equivalence = expected_string actual_string)))))))
(do {! random.monad}
- [size (\ ! map (n.% 10) random.nat)
+ [size (\ ! 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))]]
@@ -155,7 +155,7 @@
(|> (/.result (/.dictionary /.string)
(#json.Object
(|> values
- (list\map (|>> #json.String))
+ (list\each (|>> #json.String))
(list.zipped/2 keys)
(dictionary.of_list text.hash))))
(!expect (^multi (#try.Success actual)
diff --git a/stdlib/source/test/lux/control/parser/synthesis.lux b/stdlib/source/test/lux/control/parser/synthesis.lux
index e412ff262..82b851696 100644
--- a/stdlib/source/test/lux/control/parser/synthesis.lux
+++ b/stdlib/source/test/lux/control/parser/synthesis.lux
@@ -53,9 +53,9 @@
(def: random_environment
(Random (Environment Synthesis))
(do {! random.monad}
- [size (\ ! map (n.% 5) random.nat)]
+ [size (\ ! each (n.% 5) random.nat)]
(|> ..random_variable
- (\ ! map (|>> synthesis.variable))
+ (\ ! each (|>> synthesis.variable))
(random.list size))))
(def: simple
@@ -79,7 +79,7 @@
))]
[/.bit /.bit! random.bit synthesis.bit bit.equivalence]
- [/.i64 /.i64! (\ ! map .i64 random.nat) synthesis.i64 i64.equivalence]
+ [/.i64 /.i64! (\ ! each .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]
@@ -93,7 +93,7 @@
($_ _.and
(do {! random.monad}
[expected_bit random.bit
- expected_i64 (\ ! map .i64 random.nat)
+ expected_i64 (\ ! each .i64 random.nat)
expected_f64 random.safe_frac
expected_text (random.unicode 1)]
(_.cover [/.tuple]
@@ -137,14 +137,14 @@
(!expect (^multi (#try.Failure error)
(exception.match? /.wrong_arity error))))))
(do {! random.monad}
- [arity (\ ! map (|>> (n.% 10) ++) random.nat)
+ [arity (\ ! each (|>> (n.% 10) ++) random.nat)
expected_offset random.nat
expected_inits (random.list arity random.bit)
expected_body (random.unicode 1)]
(_.cover [/.loop]
(and (|> (/.result (/.loop (<>.many /.bit) /.text)
(list (synthesis.loop/scope [expected_offset
- (list\map (|>> synthesis.bit) expected_inits)
+ (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)
@@ -164,7 +164,7 @@
(_.for [/.Parser])
($_ _.and
(do {! random.monad}
- [expected (\ ! map (|>> synthesis.i64) random.nat)]
+ [expected (\ ! each (|>> synthesis.i64) random.nat)]
(_.cover [/.result /.any]
(|> (/.result /.any (list expected))
(!expect (^multi (#try.Success actual)
@@ -174,13 +174,13 @@
(!expect (^multi (#try.Failure error)
(exception.match? /.empty_input error)))))
(do {! random.monad}
- [expected (\ ! map (|>> synthesis.i64) random.nat)]
+ [expected (\ ! each (|>> synthesis.i64) random.nat)]
(_.cover [/.unconsumed_input]
(|> (/.result /.any (list expected expected))
(!expect (^multi (#try.Failure error)
(exception.match? /.unconsumed_input error))))))
(do {! random.monad}
- [dummy (\ ! map (|>> synthesis.i64) random.nat)]
+ [dummy (\ ! each (|>> synthesis.i64) random.nat)]
(_.cover [/.end! /.expected_empty_input]
(and (|> (/.result /.end! (list))
(!expect (#try.Success _)))
@@ -188,7 +188,7 @@
(!expect (^multi (#try.Failure error)
(exception.match? /.expected_empty_input error)))))))
(do {! random.monad}
- [dummy (\ ! map (|>> synthesis.i64) random.nat)]
+ [dummy (\ ! each (|>> synthesis.i64) random.nat)]
(_.cover [/.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 b3767ab01..3b28d2390 100644
--- a/stdlib/source/test/lux/control/parser/text.lux
+++ b/stdlib/source/test/lux/control/parser/text.lux
@@ -61,7 +61,7 @@
(-> Text (/.Parser Text) Bit)
(|> expected
(/.result parser)
- (\ try.functor map (text\= expected))
+ (\ try.functor each (text\= expected))
(try.else false)))
(def: (should_pass! expected parser)
@@ -72,13 +72,13 @@
Test
($_ _.and
(do {! random.monad}
- [offset (\ ! map (n.% 50) random.nat)
- range (\ ! map (|>> (n.% 50) (n.+ 10)) random.nat)
+ [offset (\ ! each (n.% 50) random.nat)
+ range (\ ! each (|>> (n.% 50) (n.+ 10)) random.nat)
.let [limit (n.+ offset range)]
- expected (\ ! map (|>> (n.% range) (n.+ offset) text.of_char) random.nat)
+ expected (\ ! each (|>> (n.% range) (n.+ offset) text.of_char) random.nat)
out_of_range (case offset
- 0 (\ ! map (|>> (n.% 10) ++ (n.+ limit) text.of_char) random.nat)
- _ (\ ! map (|>> (n.% offset) text.of_char) random.nat))]
+ 0 (\ ! each (|>> (n.% 10) ++ (n.+ limit) text.of_char) random.nat)
+ _ (\ ! each (|>> (n.% offset) text.of_char) random.nat))]
(_.cover [/.range]
(and (..should_pass expected (/.range offset limit))
(..should_fail out_of_range (/.range offset limit)))))
@@ -97,19 +97,19 @@
(and (..should_pass (text.of_char expected) /.lower)
(..should_fail (text.of_char invalid) /.lower))))
(do {! random.monad}
- [expected (\ ! map (n.% 10) random.nat)
+ [expected (\ ! each (n.% 10) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.decimal]
(and (..should_pass (\ n.decimal encoded expected) /.decimal)
(..should_fail (text.of_char invalid) /.decimal))))
(do {! random.monad}
- [expected (\ ! map (n.% 8) random.nat)
+ [expected (\ ! each (n.% 8) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.octal]
(and (..should_pass (\ n.octal encoded expected) /.octal)
(..should_fail (text.of_char invalid) /.octal))))
(do {! random.monad}
- [expected (\ ! map (n.% 16) random.nat)
+ [expected (\ ! each (n.% 16) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.hexadecimal]
(and (..should_pass (\ n.hex encoded expected) /.hexadecimal)
@@ -155,13 +155,13 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set n.hash num_options)
- (\ ! map (|>> set.list
- (list\map text.of_char)
- text.together)))
- expected (\ ! map (function (_ value)
- (|> options
- (text.char (n.% num_options value))
- maybe.trusted))
+ (\ ! 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)
invalid (random.only (function (_ char)
(not (text.contains? (text.of_char char) options)))
@@ -181,13 +181,13 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set n.hash num_options)
- (\ ! map (|>> set.list
- (list\map text.of_char)
- text.together)))
- invalid (\ ! map (function (_ value)
- (|> options
- (text.char (n.% num_options value))
- maybe.trusted))
+ (\ ! 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)
expected (random.only (function (_ char)
(not (text.contains? (text.of_char char) options)))
@@ -210,26 +210,26 @@
(let [octal! (/.one_of! "01234567")]
($_ _.and
(do {! random.monad}
- [left (\ ! map (|>> (n.% 8) (\ n.octal encoded)) random.nat)
- right (\ ! map (|>> (n.% 8) (\ n.octal encoded)) random.nat)
+ [left (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)
+ right (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)
.let [expected (format left right)]
invalid (|> random.nat
- (\ ! map (n.% 16))
+ (\ ! each (n.% 16))
(random.only (n.>= 8))
- (\ ! map (\ n.hex encoded)))]
+ (\ ! each (\ n.hex encoded)))]
(_.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 encoded)) random.nat)
- right (\ ! map (|>> (n.% 8) (\ n.octal encoded)) random.nat)
+ [left (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)
+ right (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)
.let [expected (format left right)]
invalid (|> random.nat
- (\ ! map (n.% 16))
+ (\ ! each (n.% 16))
(random.only (n.>= 8))
- (\ ! map (\ n.hex encoded)))]
+ (\ ! each (\ n.hex encoded)))]
(_.cover [/.some /.some!]
(and (..should_pass expected (/.some /.octal))
(..should_pass "" (/.some /.octal))
@@ -238,7 +238,7 @@
(..should_pass! expected (/.some! octal!))
(..should_pass! "" (/.some! octal!)))))
(do {! random.monad}
- [.let [octal (\ ! map (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
+ [.let [octal (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -251,7 +251,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 encoded)) random.nat)]
+ [.let [octal (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -264,7 +264,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 encoded)) random.nat)]
+ [.let [octal (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -277,7 +277,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 encoded)) random.nat)]
+ [.let [octal (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -389,7 +389,7 @@
(/.this output)))
(!expect (#try.Success _)))))
(do {! random.monad}
- [expected (\ ! map (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
+ [expected (\ ! each (|>> (n.% 8) (\ n.octal encoded)) random.nat)]
(_.cover [/.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 dc901e3c4..fd1706b0f 100644
--- a/stdlib/source/test/lux/control/parser/type.lux
+++ b/stdlib/source/test/lux/control/parser/type.lux
@@ -31,8 +31,8 @@
(def: primitive
(Random Type)
(|> (random.ascii/alpha_num 1)
- (\ random.monad map (function (_ name)
- (#.Primitive name (list))))))
+ (\ random.monad each (function (_ name)
+ (#.Primitive name (list))))))
(def: matches
Test
@@ -166,7 +166,7 @@
Test
(do {! random.monad}
[not_polymorphic ..primitive
- expected_inputs (\ ! map (|>> (n.% 10) ++) random.nat)]
+ expected_inputs (\ ! each (|>> (n.% 10) ++) random.nat)]
($_ _.and
(_.cover [/.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 e92216696..ffc96e172 100644
--- a/stdlib/source/test/lux/control/parser/xml.lux
+++ b/stdlib/source/test/lux/control/parser/xml.lux
@@ -69,10 +69,10 @@
[[(//\in expected)
(#xml.Text expected)]])
(do {! random.monad}
- [expected (\ ! map (|>> #xml.Text) (random.ascii/alpha 1))]
+ [expected (\ ! each (|>> #xml.Text) (random.ascii/alpha 1))]
(_.cover [/.any]
(|> (/.result /.any (list expected))
- (try\map (xml\= expected))
+ (try\each (xml\= expected))
(try.else false))))
(do {! random.monad}
[expected ..random_tag]
@@ -159,7 +159,7 @@
(//\in []))
_ (//.some /.any)]
(in [])))]
- repetitions (\ ! map (n.% 10) random.nat)]
+ repetitions (\ ! each (n.% 10) random.nat)]
($_ _.and
(_.cover [/.somewhere]
(|> (/.result parser
diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux
index 555f30b4f..5cf65f56b 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 (\ ! map (|>> (n.% 100) (n.max 1))))]
+ [expected_clean_ups (|> random.nat (\ ! each (|>> (n.% 100) (n.max 1))))]
($_ _.and
(_.for [/.functor]
($functor.spec ..injection ..comparison (: (All [! r]
@@ -107,8 +107,8 @@
(in (#try.Success []))))]
outcome (/.run! !
(do {! (/.monad !)}
- [_ (monad.map ! (/.acquire! //@ count_clean_up)
- (enum.range n.enum 1 expected_clean_ups))]
+ [_ (monad.each ! (/.acquire! //@ count_clean_up)
+ (enum.range n.enum 1 expected_clean_ups))]
(in [])))
actual_clean_ups (thread.read! clean_up_counter)]
(in (and (..success? outcome)
@@ -125,8 +125,8 @@
(in (#try.Success []))))]
outcome (/.run! !
(do {! (/.monad !)}
- [_ (monad.map ! (/.acquire! //@ count_clean_up)
- (enum.range n.enum 1 expected_clean_ups))
+ [_ (monad.each ! (/.acquire! //@ count_clean_up)
+ (enum.range n.enum 1 expected_clean_ups))
_ (/.failure //@ (exception.error ..oops []))]
(in [])))
actual_clean_ups (thread.read! clean_up_counter)]
@@ -144,8 +144,8 @@
(in (#try.Success []))))]
outcome (/.run! !
(do {! (/.monad !)}
- [_ (monad.map ! (/.acquire! //@ count_clean_up)
- (enum.range n.enum 1 expected_clean_ups))
+ [_ (monad.each ! (/.acquire! //@ count_clean_up)
+ (enum.range n.enum 1 expected_clean_ups))
_ (/.except //@ ..oops [])]
(in [])))
actual_clean_ups (thread.read! clean_up_counter)]
@@ -164,8 +164,8 @@
(exception.except ..oops [])))))]
outcome (/.run! !
(do {! (/.monad !)}
- [_ (monad.map ! (/.acquire! //@ count_clean_up)
- (enum.range n.enum 1 expected_clean_ups))]
+ [_ (monad.each ! (/.acquire! //@ count_clean_up)
+ (enum.range n.enum 1 expected_clean_ups))]
(in [])))
actual_clean_ups (thread.read! clean_up_counter)]
(in (and (or (n.= 0 expected_clean_ups)
diff --git a/stdlib/source/test/lux/control/remember.lux b/stdlib/source/test/lux/control/remember.lux
index 045e2d0df..ae5240f7e 100644
--- a/stdlib/source/test/lux/control/remember.lux
+++ b/stdlib/source/test/lux/control/remember.lux
@@ -29,8 +29,8 @@
["." /]])
(def: deadline (Random Date) random.date)
-(def: message (Random Text) (random\map %.bit random.bit))
-(def: focus (Random Code) (random\map code.bit random.bit))
+(def: message (Random Text) (random\each %.bit random.bit))
+(def: focus (Random Code) (random\each code.bit random.bit))
(def: (memory macro deadline message focus)
(-> Name Date Text (Maybe Code) Code)
diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux
index eda78cbeb..10bda7445 100644
--- a/stdlib/source/test/lux/control/state.lux
+++ b/stdlib/source/test/lux/control/state.lux
@@ -82,7 +82,7 @@
(def: loops
Test
(do {! random.monad}
- [limit (|> random.nat (\ ! map (n.% 10)))
+ [limit (|> random.nat (\ ! each (n.% 10)))
.let [condition (do /.monad
[state /.get]
(in (n.< limit state)))]]