aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
authorEduardo Julian2021-09-15 20:45:48 -0400
committerEduardo Julian2021-09-15 20:45:48 -0400
commitc234d5d25331d6ed3b9455ce8c93ec4d34402f91 (patch)
tree29148102b8881e037dfa74c3386fdde496025a07 /stdlib/source/test
parent4f4656b278c6f9dfbdd15d5d9bc86d63c5b44333 (diff)
"Row" => "Sequence"
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/lux/control/concurrency/actor.lux10
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux12
-rw-r--r--stdlib/source/test/lux/control/parser/binary.lux18
-rw-r--r--stdlib/source/test/lux/control/parser/json.lux12
-rw-r--r--stdlib/source/test/lux/data/collection.lux4
-rw-r--r--stdlib/source/test/lux/data/collection/sequence.lux (renamed from stdlib/source/test/lux/data/collection/row.lux)10
-rw-r--r--stdlib/source/test/lux/data/format/json.lux18
-rw-r--r--stdlib/source/test/lux/data/format/tar.lux102
-rw-r--r--stdlib/source/test/lux/extension.lux6
-rw-r--r--stdlib/source/test/lux/target/jvm.lux18
-rw-r--r--stdlib/source/test/lux/type/poly/json.lux2
11 files changed, 106 insertions, 106 deletions
diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux
index 829dcfbcb..964ea694d 100644
--- a/stdlib/source/test/lux/control/concurrency/actor.lux
+++ b/stdlib/source/test/lux/control/concurrency/actor.lux
@@ -13,7 +13,7 @@
["%" format {"+" format}]]
[collection
["[0]" list]
- ["[0]" row {"+" Row}]]]
+ ["[0]" sequence {"+" Sequence}]]]
[math
["[0]" random]
[number
@@ -202,8 +202,8 @@
events (random.list 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))]]
+ sink (: (Atom (Sequence Nat))
+ (atom.atom sequence.empty))]]
(in (do async.monad
[agent (async.future
(do [! io.monad]
@@ -213,7 +213,7 @@
(async.future
(if (n.< num_observations events_seen)
(do !
- [_ (atom.update! (row.suffix event) sink)]
+ [_ (atom.update! (sequence.suffix event) sink)]
(in {try.#Success (++ events_seen)}))
(do !
[_ stop]
@@ -224,5 +224,5 @@
_ (/.obituary agent)
actual (async.future (atom.read! sink))]
(_.cover' [/.Stop /.observe! /.obituary]
- (# (list.equivalence n.equivalence) = expected (row.list actual))))))
+ (# (list.equivalence n.equivalence) = expected (sequence.list actual))))))
))))
diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux
index aa77d2835..1c07464c1 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -15,7 +15,7 @@
[data
[collection
["[0]" list ("[1]#[0]" mix monoid)]
- ["[0]" row {"+" Row}]]]
+ ["[0]" sequence {"+" Sequence}]]]
[math
["[0]" random]
[number
@@ -140,14 +140,14 @@
(in (do [! async.monad]
[.let [[?signal !signal] (: [(async.Async Any) (async.Resolver Any)]
(async.async []))
- sink (: (Atom (Row Nat))
- (atom.atom row.empty))]
+ sink (: (Atom (Sequence Nat))
+ (atom.atom sequence.empty))]
_ (async.future (/.subscribe! (function (_ value)
(do [! io.monad]
[current (atom.read! sink)
- _ (atom.update! (row.suffix value) sink)]
+ _ (atom.update! (sequence.suffix value) sink)]
(if (n.< (list.size inputs)
- (++ (row.size current)))
+ (++ (sequence.size current)))
(in {.#Some []})
(do !
[_ (!signal [])]
@@ -157,7 +157,7 @@
listened (|> sink
atom.read!
async.future
- (# ! each row.list))]
+ (# ! each sequence.list))]
(_.cover' [/.Subscriber /.subscribe!]
(list#= inputs listened))))
(in (do async.monad
diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux
index e878f916f..2ecb4aaa2 100644
--- a/stdlib/source/test/lux/control/parser/binary.lux
+++ b/stdlib/source/test/lux/control/parser/binary.lux
@@ -25,7 +25,7 @@
["[1]" binary]]
[collection
["[0]" list]
- ["[0]" row]
+ ["[0]" sequence]
["[0]" set]]]
[macro
["[0]" code]]
@@ -178,23 +178,23 @@
[/.text format.text]
)))))
-(def: row
+(def: sequence
Test
(`` ($_ _.and
(~~ (template [<parser> <format>]
[(do [! random.monad]
- [expected (random.row ..segment_size random.nat)]
+ [expected (random.sequence ..segment_size random.nat)]
(_.cover [<parser> <format>]
(|> expected
(format.result (<format> format.nat))
(/.result (<parser> /.nat))
(!expect (^multi {try.#Success actual}
- (# (row.equivalence n.equivalence) = expected actual))))))]
+ (# (sequence.equivalence n.equivalence) = expected actual))))))]
- [/.row/8 format.row/8]
- [/.row/16 format.row/16]
- [/.row/32 format.row/32]
- [/.row/64 format.row/64]
+ [/.sequence/8 format.sequence/8]
+ [/.sequence/16 format.sequence/16]
+ [/.sequence/32 format.sequence/32]
+ [/.sequence/64 format.sequence/64]
)))))
(def: simple
@@ -384,7 +384,7 @@
..size
..binary
..utf8
- ..row
+ ..sequence
..simple
..complex
))))
diff --git a/stdlib/source/test/lux/control/parser/json.lux b/stdlib/source/test/lux/control/parser/json.lux
index 04d52c647..23d319bec 100644
--- a/stdlib/source/test/lux/control/parser/json.lux
+++ b/stdlib/source/test/lux/control/parser/json.lux
@@ -17,7 +17,7 @@
["[0]" list ("[1]#[0]" functor)]
["[0]" set]
["[0]" dictionary]
- ["[0]" row {"+" row} ("[1]#[0]" functor)]]
+ ["[0]" sequence {"+" sequence} ("[1]#[0]" functor)]]
[format
["[0]" json]]]
[math
@@ -105,20 +105,20 @@
[size (# ! each (n.% 10) random.nat)
expected (|> (random.unicode 1)
(random.list size)
- (# ! each row.of_list))]
+ (# ! each sequence.of_list))]
(_.cover [/.array]
(|> (/.result (/.array (<>.some /.string))
- {json.#Array (row#each (|>> {json.#String}) expected)})
+ {json.#Array (sequence#each (|>> {json.#String}) expected)})
(!expect (^multi {try.#Success actual}
- (# (row.equivalence text.equivalence) = expected (row.of_list actual)))))))
+ (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual)))))))
(do [! random.monad]
[expected (# ! each (|>> {json.#String}) (random.unicode 1))]
(_.cover [/.unconsumed_input]
- (|> (/.result (/.array /.any) {json.#Array (row expected expected)})
+ (|> (/.result (/.array /.any) {json.#Array (sequence expected expected)})
(!expect (^multi {try.#Failure error}
(exception.match? /.unconsumed_input error))))))
(_.cover [/.empty_input]
- (|> (/.result (/.array /.any) {json.#Array (row)})
+ (|> (/.result (/.array /.any) {json.#Array (sequence)})
(!expect (^multi {try.#Failure error}
(exception.match? /.empty_input error)))))
(do [! random.monad]
diff --git a/stdlib/source/test/lux/data/collection.lux b/stdlib/source/test/lux/data/collection.lux
index e4caad8c8..94f884ba9 100644
--- a/stdlib/source/test/lux/data/collection.lux
+++ b/stdlib/source/test/lux/data/collection.lux
@@ -6,7 +6,7 @@
["[1][0]" array]
["[1][0]" bits]
["[1][0]" list]
- ["[1][0]" row]
+ ["[1][0]" sequence]
["[1][0]" stream]
["[1][0]" stack]
["[1][0]" dictionary
@@ -58,7 +58,7 @@
/array.test
/bits.test
/list.test
- /row.test
+ /sequence.test
/stream.test
/stack.test
..dictionary
diff --git a/stdlib/source/test/lux/data/collection/row.lux b/stdlib/source/test/lux/data/collection/sequence.lux
index 8728a6df9..6ecbab8ee 100644
--- a/stdlib/source/test/lux/data/collection/row.lux
+++ b/stdlib/source/test/lux/data/collection/sequence.lux
@@ -32,9 +32,9 @@
[size (# ! each (n.% 100) random.nat)]
($_ _.and
(_.for [/.equivalence]
- ($equivalence.spec (/.equivalence n.equivalence) (random.row size random.nat)))
+ ($equivalence.spec (/.equivalence n.equivalence) (random.sequence size random.nat)))
(_.for [/.monoid]
- ($monoid.spec (/.equivalence n.equivalence) /.monoid (random.row size random.nat)))
+ ($monoid.spec (/.equivalence n.equivalence) /.monoid (random.sequence size random.nat)))
(_.for [/.mix]
($mix.spec /#in /.equivalence /.mix))
(_.for [/.functor]
@@ -132,7 +132,7 @@
(def: .public test
Test
(<| (_.covering /._)
- (_.for [/.Row])
+ (_.for [/.Sequence])
(do [! random.monad]
[size (# ! each (|>> (n.% 100) ++) random.nat)]
($_ _.and
@@ -151,9 +151,9 @@
[value/0 random.nat
value/1 random.nat
value/2 random.nat]
- (_.cover [/.row]
+ (_.cover [/.sequence]
(/#= (/.of_list (list value/0 value/1 value/2))
- (/.row value/0 value/1 value/2))))
+ (/.sequence value/0 value/1 value/2))))
(_.cover [/.member?]
(and (list.every? (/.member? n.equivalence sample)
(/.list sample))
diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux
index 440ab1f07..9eb86e1c5 100644
--- a/stdlib/source/test/lux/data/format/json.lux
+++ b/stdlib/source/test/lux/data/format/json.lux
@@ -16,7 +16,7 @@
["[0]" text
["%" format {"+" format}]]
[collection
- ["[0]" row]
+ ["[0]" sequence]
["[0]" dictionary]
["[0]" set]
["[0]" list ("[1]#[0]" functor)]]]
@@ -42,7 +42,7 @@
random.bit
random.safe_frac
(random.unicode size)
- (random.row size again)
+ (random.sequence size again)
(random.dictionary text.hash size (random.unicode size) again)
)))))
@@ -147,16 +147,16 @@
[/.Boolean /.boolean_field /.#Boolean random.bit bit.equivalence]
[/.Number /.number_field /.#Number random.safe_frac frac.equivalence]
[/.String /.string_field /.#String (random.ascii/alpha 1) text.equivalence]
- [/.Array /.array_field /.#Array (random.row 3 ..random) (row.equivalence /.equivalence)]
+ [/.Array /.array_field /.#Array (random.sequence 3 ..random) (sequence.equivalence /.equivalence)]
[/.Object /.object_field /.#Object (random.dictionary text.hash 3 (random.ascii/alpha 1) ..random) (dictionary.equivalence /.equivalence)]
))
(with_expansions [<boolean> (boolean)
<number> (number)
<string> (string)
- <array_row> (row.row {/.#Null}
- {/.#Boolean <boolean>}
- {/.#Number <number>}
- {/.#String <string>})
+ <array_sequence> (sequence.sequence {/.#Null}
+ {/.#Boolean <boolean>}
+ {/.#Number <number>}
+ {/.#String <string>})
<key0> (string)
<key1> (string)
<key2> (string)
@@ -173,7 +173,7 @@
[/.#Number <number>]
[/.#String <string>]
))
- (#= {/.#Array <array_row>} (/.json [() <boolean> <number> <string>]))
+ (#= {/.#Array <array_sequence>} (/.json [() <boolean> <number> <string>]))
(let [object (/.json {<key0> ()
<key1> <boolean>
<key2> <number>
@@ -193,7 +193,7 @@
(#= {/.#Boolean <boolean>} value1)
(#= {/.#Number <number>} value2)
(#= {/.#String <string>} value3)
- (#= {/.#Array <array_row>} value4)
+ (#= {/.#Array <array_sequence>} value4)
(#= {/.#Number <number>} value6))))))
)))
))))
diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux
index e01670420..37be384ef 100644
--- a/stdlib/source/test/lux/data/format/tar.lux
+++ b/stdlib/source/test/lux/data/format/tar.lux
@@ -21,7 +21,7 @@
["[1]" set]
["[1]/[0]" block]]]
[collection
- ["[0]" row]
+ ["[0]" sequence]
["[0]" list ("[1]#[0]" mix)]]
["[0]" format "_"
["[1]" binary]]]
@@ -171,10 +171,10 @@
[(_.cover [<type>]
(|> (do try.monad
[expected_path (/.path expected_path)
- tar (|> (row.row {<tag> expected_path})
+ tar (|> (sequence.sequence {<tag> expected_path})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {<tag> actual_path}))
(text#= (/.from_path expected_path)
(/.from_path actual_path))
@@ -193,17 +193,17 @@
(|> (do try.monad
[expected_path (/.path expected_path)
expected_content (/.content content)
- tar (|> (row.row {<tag> [expected_path
- expected_moment
- /.none
- [/.#user [/.#name /.anonymous
- /.#id /.no_id]
- /.#group [/.#name /.anonymous
- /.#id /.no_id]]
- expected_content]})
+ tar (|> (sequence.sequence {<tag> [expected_path
+ expected_moment
+ /.none
+ [/.#user [/.#name /.anonymous
+ /.#id /.no_id]
+ /.#group [/.#name /.anonymous
+ /.#id /.no_id]]
+ expected_content]})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]}))
(let [seconds (: (-> Instant Int)
(|>> instant.relative (duration.ticks duration.second)))]
@@ -251,17 +251,17 @@
(|> (do try.monad
[path (/.path path)
content (/.content (binary.empty 0))
- tar (|> (row.row {/.#Normal [path
- (instant.of_millis +0)
- expected_mode
- [/.#user [/.#name /.anonymous
- /.#id /.no_id]
- /.#group [/.#name /.anonymous
- /.#id /.no_id]]
- content]})
+ tar (|> (sequence.sequence {/.#Normal [path
+ (instant.of_millis +0)
+ expected_mode
+ [/.#user [/.#name /.anonymous
+ /.#id /.no_id]
+ /.#group [/.#name /.anonymous
+ /.#id /.no_id]]
+ content]})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {/.#Normal [_ _ actual_mode _ _]}))
(n.= (/.mode expected_mode)
(/.mode actual_mode))
@@ -274,17 +274,17 @@
(|> (do try.monad
[path (/.path path)
content (/.content (binary.empty 0))
- tar (|> (row.row {/.#Normal [path
- (instant.of_millis +0)
- <expected_mode>
- [/.#user [/.#name /.anonymous
- /.#id /.no_id]
- /.#group [/.#name /.anonymous
- /.#id /.no_id]]
- content]})
+ tar (|> (sequence.sequence {/.#Normal [path
+ (instant.of_millis +0)
+ <expected_mode>
+ [/.#user [/.#name /.anonymous
+ /.#id /.no_id]
+ /.#group [/.#name /.anonymous
+ /.#id /.no_id]]
+ content]})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {/.#Normal [_ _ actual_mode _ _]}))
(n.= (/.mode <expected_mode>)
(/.mode actual_mode))
@@ -341,17 +341,17 @@
[path (/.path path)
content (/.content (binary.empty 0))
expected (/.name expected)
- tar (|> (row.row {/.#Normal [path
- (instant.of_millis +0)
- /.none
- [/.#user [/.#name expected
- /.#id /.no_id]
- /.#group [/.#name /.anonymous
- /.#id /.no_id]]
- content]})
+ tar (|> (sequence.sequence {/.#Normal [path
+ (instant.of_millis +0)
+ /.none
+ [/.#user [/.#name expected
+ /.#id /.no_id]
+ /.#group [/.#name /.anonymous
+ /.#id /.no_id]]
+ content]})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {/.#Normal [_ _ _ actual_ownership _]}))
(and (text#= (/.from_name expected)
(/.from_name (value@ [/.#user /.#name] actual_ownership)))
@@ -365,17 +365,17 @@
(|> (do try.monad
[path (/.path path)
content (/.content (binary.empty 0))
- tar (|> (row.row {/.#Normal [path
- (instant.of_millis +0)
- /.none
- [/.#user [/.#name /.anonymous
- /.#id /.no_id]
- /.#group [/.#name /.anonymous
- /.#id /.no_id]]
- content]})
+ tar (|> (sequence.sequence {/.#Normal [path
+ (instant.of_millis +0)
+ /.none
+ [/.#user [/.#name /.anonymous
+ /.#id /.no_id]
+ /.#group [/.#name /.anonymous
+ /.#id /.no_id]]
+ content]})
(format.result /.writer)
(<b>.result /.parser))]
- (in (case (row.list tar)
+ (in (case (sequence.list tar)
(^ (list {/.#Normal [_ _ _ actual_ownership _]}))
(and (text#= (/.from_name /.anonymous)
(/.from_name (value@ [/.#user /.#name] actual_ownership)))
@@ -399,13 +399,13 @@
[_ (in [])]
($_ _.and
(_.cover [/.writer /.parser]
- (|> row.empty
+ (|> sequence.empty
(format.result /.writer)
(<b>.result /.parser)
- (# try.monad each row.empty?)
+ (# try.monad each sequence.empty?)
(try.else false)))
(_.cover [/.invalid_end_of_archive]
- (let [dump (format.result /.writer row.empty)]
+ (let [dump (format.result /.writer sequence.empty)]
(case (<b>.result /.parser (binary#composite dump dump))
{try.#Success _}
false
diff --git a/stdlib/source/test/lux/extension.lux b/stdlib/source/test/lux/extension.lux
index bf955b152..91a3f9c84 100644
--- a/stdlib/source/test/lux/extension.lux
+++ b/stdlib/source/test/lux/extension.lux
@@ -23,7 +23,7 @@
["[0]" text ("[1]#[0]" equivalence)
["%" format {"+" format}]]
[collection
- ["[0]" row]
+ ["[0]" sequence]
["[0]" list ("[1]#[0]" functor)]]]
[math
["[0]" random]
@@ -84,7 +84,7 @@
(generation: (..my_generation self phase archive [pass_through <synthesis>.any])
(for [@.jvm
- (# phase.monad each (|>> {jvm.#Embedded} row.row)
+ (# phase.monad each (|>> {jvm.#Embedded} sequence.sequence)
(phase archive pass_through))]
(phase archive pass_through)))
@@ -97,7 +97,7 @@
(generation: (..dummy_generation self phase archive [])
(# phase.monad in
(for [@.jvm
- (row.row {jvm.#Constant {jvm.#LDC {jvm.#String self}}})
+ (sequence.sequence {jvm.#Constant {jvm.#LDC {jvm.#String self}}})
@.js (js.string self)
@.python (python.unicode self)
diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux
index bdfc318a7..21da14fb5 100644
--- a/stdlib/source/test/lux/target/jvm.lux
+++ b/stdlib/source/test/lux/target/jvm.lux
@@ -21,7 +21,7 @@
[collection
["[0]" array]
["[0]" dictionary]
- ["[0]" row]
+ ["[0]" sequence]
["[0]" set]
["[0]" list ("[1]#[0]" functor)]]]
[math
@@ -120,7 +120,7 @@
{.#Some (do /.monad
[_ bytecode]
/.areturn)}))
- (row.row))
+ (sequence.sequence))
.let [bytecode (format.result /class.writer class)
loader (/loader.memory (/loader.new_library []))]
_ (/loader.define class_name bytecode loader)
@@ -855,8 +855,8 @@
(/name.internal class_name)
(/name.internal "java.lang.Object")
(list)
- (list (/field.field /field.static class_field /type.long (row.row))
- (/field.field /field.public object_field /type.long (row.row)))
+ (list (/field.field /field.static class_field /type.long (sequence.sequence))
+ (/field.field /field.public object_field /type.long (sequence.sequence)))
(list (/method.method /method.private
constructor
constructor::type
@@ -886,7 +886,7 @@
_ /.ladd
_ ..$Long::wrap]
/.areturn)}))
- (row.row))
+ (sequence.sequence))
try.trusted
(format.result /class.writer))
loader (/loader.memory (/loader.new_library []))]]
@@ -1354,7 +1354,7 @@
(substitute expected))
_ (value@ #wrap primitive)]
/.areturn)}))
- (row.row))
+ (sequence.sequence))
.let [bytecode (format.result /class.writer class)
loader (/loader.memory (/loader.new_library []))]
_ (/loader.define class_name bytecode loader)
@@ -1634,7 +1634,7 @@
(list)
(list (/method.method ($_ /modifier#composite /method.public /method.abstract)
interface_method method::type (list) {.#None}))
- (row.row))
+ (sequence.sequence))
try.trusted
(format.result /class.writer))
abstract_bytecode (|> (/class.class /version.v6_0 ($_ /modifier#composite /class.public /class.abstract)
@@ -1654,7 +1654,7 @@
(method overriden_method fake_part2)
(/method.method ($_ /modifier#composite /method.public /method.abstract)
abstract_method method::type (list) {.#None}))
- (row.row))
+ (sequence.sequence))
try.trusted
(format.result /class.writer))
invoke (: (-> (Type Class) Text (Bytecode Any))
@@ -1701,7 +1701,7 @@
_ /.ladd
_ ..$Long::wrap]
/.areturn)}))
- (row.row))
+ (sequence.sequence))
try.trusted
(format.result /class.writer))
loader (/loader.memory (/loader.new_library []))]]
diff --git a/stdlib/source/test/lux/type/poly/json.lux b/stdlib/source/test/lux/type/poly/json.lux
index 4b028a9cc..cb9fcc14d 100644
--- a/stdlib/source/test/lux/type/poly/json.lux
+++ b/stdlib/source/test/lux/type/poly/json.lux
@@ -26,7 +26,7 @@
[\\poly
["[0]" /]]]]
[collection
- [row {"+" row}]
+ [sequence {"+" sequence}]
["d" dictionary]
["[0]" list]]]
[type