aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2018-07-21 00:20:16 -0400
committerEduardo Julian2018-07-21 00:20:16 -0400
commit47890ee876d2a33d9d7d1c559912123359ab9f87 (patch)
tree25b7baaec924ad864a2ca2e75bd2c0b7af08e39f /stdlib/test
parentf7772ee6c7c99912b3ea2b0c98eefff0d1489841 (diff)
Re-named "lux/world/blob" to "lux/world/binary".
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/world/binary.lux (renamed from stdlib/test/test/lux/world/blob.lux)40
-rw-r--r--stdlib/test/test/lux/world/file.lux14
-rw-r--r--stdlib/test/test/lux/world/net/tcp.lux16
-rw-r--r--stdlib/test/test/lux/world/net/udp.lux14
-rw-r--r--stdlib/test/tests.lux2
5 files changed, 43 insertions, 43 deletions
diff --git a/stdlib/test/test/lux/world/blob.lux b/stdlib/test/test/lux/world/binary.lux
index e24017587..25c59c88d 100644
--- a/stdlib/test/test/lux/world/blob.lux
+++ b/stdlib/test/test/lux/world/binary.lux
@@ -9,7 +9,7 @@
[collection
["." list]]]
[world
- ["/" blob]]
+ ["/" binary]]
[math
["r" random]]]
lux/test
@@ -27,8 +27,8 @@
(#e.Success output)
output))
-(def: #export (blob size)
- (-> Nat (r.Random /.Blob))
+(def: #export (binary size)
+ (-> Nat (r.Random /.Binary))
(let [output (/.create size)]
(loop [idx +0]
(if (n/< size idx)
@@ -39,31 +39,31 @@
(:: r.Monad<Random> wrap output)))))
(def: (bits-io bytes read write value)
- (-> Nat (-> Nat /.Blob (e.Error Nat)) (-> Nat Nat /.Blob (e.Error Any)) Nat Bit)
- (let [blob (/.create +8)
+ (-> Nat (-> Nat /.Binary (e.Error Nat)) (-> Nat Nat /.Binary (e.Error Any)) Nat Bit)
+ (let [binary (/.create +8)
bits (n/* +8 bytes)
capped-value (|> +1 (i64.left-shift bits) dec (i64.and value))]
(succeed
(do e.Monad<Error>
- [_ (write +0 value blob)
- output (read +0 blob)]
+ [_ (write +0 value binary)
+ output (read +0 binary)]
(wrap (n/= capped-value output))))))
-(context: "Blob."
+(context: "Binary."
(<| (times +100)
(do @
[#let [gen-size (|> r.nat (:: @ map (|>> (n/% +100) (n/max +8))))]
- blob-size gen-size
- random-blob (blob blob-size)
+ binary-size gen-size
+ random-binary (binary binary-size)
value r.nat
- #let [gen-idx (|> r.nat (:: @ map (n/% blob-size)))]
+ #let [gen-idx (|> r.nat (:: @ map (n/% binary-size)))]
[from to] (r.seq gen-idx gen-idx)
#let [[from to] [(n/min from to) (n/max from to)]]]
($_ seq
## TODO: De-comment...
- ## (_eq.spec /.Equivalence<Blob> (:: @ map blob gen-size))
- (test "Can get size of blob."
- (|> random-blob /.size (n/= blob-size)))
+ ## (_eq.spec /.Equivalence<Binary> (:: @ map binary gen-size))
+ (test "Can get size of binary."
+ (|> random-binary /.size (n/= binary-size)))
(test "Can read/write 8-bit values."
(bits-io +1 /.read/8 /.write/8 value))
(test "Can read/write 16-bit values."
@@ -72,16 +72,16 @@
(bits-io +4 /.read/32 /.write/32 value))
(test "Can read/write 64-bit values."
(bits-io +8 /.read/64 /.write/64 value))
- (test "Can slice blobs."
+ (test "Can slice binaries."
(let [slice-size (|> to (n/- from) inc)
- random-slice (e.assume (/.slice from to random-blob))
+ random-slice (e.assume (/.slice from to random-binary))
idxs (list.n/range +0 (dec slice-size))
- reader (function (_ blob idx) (/.read/8 idx blob))]
+ reader (function (_ binary idx) (/.read/8 idx binary))]
(and (n/= slice-size (/.size random-slice))
(case [(monad.map e.Monad<Error> (reader random-slice) idxs)
- (monad.map e.Monad<Error> (|>> (n/+ from) (reader random-blob)) idxs)]
- [(#e.Success slice-vals) (#e.Success blob-vals)]
- (:: (list.Equivalence<List> number.Equivalence<Nat>) = slice-vals blob-vals)
+ (monad.map e.Monad<Error> (|>> (n/+ from) (reader random-binary)) idxs)]
+ [(#e.Success slice-vals) (#e.Success binary-vals)]
+ (:: (list.Equivalence<List> number.Equivalence<Nat>) = slice-vals binary-vals)
_
#0))))
diff --git a/stdlib/test/test/lux/world/file.lux b/stdlib/test/test/lux/world/file.lux
index 43b62ac3f..54a5e0e2a 100644
--- a/stdlib/test/test/lux/world/file.lux
+++ b/stdlib/test/test/lux/world/file.lux
@@ -15,12 +15,12 @@
[duration]]
[world
["@" file]
- [blob]]
+ [binary]]
[math
["r" random]]]
lux/test
[//
- ["_." blob]])
+ ["_." binary]])
(def: truncate-millis
(|>> (i// 1_000) (i/* 1_000)))
@@ -28,8 +28,8 @@
(context: "File system."
(do @
[file-size (|> r.nat (:: @ map (|>> (n/% +100) (n/max +10))))
- dataL (_blob.blob file-size)
- dataR (_blob.blob file-size)
+ dataL (_binary.binary file-size)
+ dataR (_binary.binary file-size)
code r.nat
last-modified (|> r.int (:: @ map (|>> (:: number.Number<Int> abs)
truncate-millis
@@ -56,7 +56,7 @@
[_ (:: @.JVM@System write dataL file)
output (:: @.JVM@System read file)
_ (:: @.JVM@System delete file)]
- (wrap (:: blob.Equivalence<Blob> = dataL output))))]
+ (wrap (:: binary.Equivalence<Binary> = dataL output))))]
(assert "Can write/read files."
(error.default #0 result))))
(wrap (do promise.Monad<Promise>
@@ -79,8 +79,8 @@
read-size (:: @.JVM@System size file)
_ (:: @.JVM@System delete file)]
(wrap (and (n/= (n/* +2 file-size) read-size)
- (:: blob.Equivalence<Blob> = dataL (error.assume (blob.slice +0 (dec file-size) output)))
- (:: blob.Equivalence<Blob> = dataR (error.assume (blob.slice file-size (dec read-size) output)))))))]
+ (:: binary.Equivalence<Binary> = dataL (error.assume (binary.slice +0 (dec file-size) output)))
+ (:: binary.Equivalence<Binary> = dataR (error.assume (binary.slice file-size (dec read-size) output)))))))]
(assert "Can append to files."
(error.default #0 result))))
(wrap (do promise.Monad<Promise>
diff --git a/stdlib/test/test/lux/world/net/tcp.lux b/stdlib/test/test/lux/world/net/tcp.lux
index cda068a78..1991e33cd 100644
--- a/stdlib/test/test/lux/world/net/tcp.lux
+++ b/stdlib/test/test/lux/world/net/tcp.lux
@@ -13,14 +13,14 @@
["." text
format]]
[world
- ["." blob]
+ ["." binary]
["." net
["@" tcp]]]
[math
["r" random]]]
lux/test
[///
- ["_." blob]])
+ ["_." binary]])
(def: localhost net.Address "127.0.0.1")
(def: port
@@ -34,10 +34,10 @@
(do @
[port ..port
size (|> r.nat (:: @ map (|>> (n/% +100) (n/max +10))))
- from (_blob.blob size)
- to (_blob.blob size)
- #let [temp-from (blob.create size)
- temp-to (blob.create size)]]
+ from (_binary.binary size)
+ to (_binary.binary size)
+ #let [temp-from (binary.create size)
+ temp-to (binary.create size)]]
($_ seq
(wrap (do P.Monad<Promise>
[result (do T.Monad<Task>
@@ -48,7 +48,7 @@
(do @
[bytes-from (@.read temp-from +0 size socket)
#let [_ (io.run (P.resolve (#E.Success (and (n/= size bytes-from)
- (:: blob.Equivalence<Blob> = from temp-from)))
+ (:: binary.Equivalence<Binary> = from temp-from)))
from-worked?))]]
(@.write to +0 size socket)))
server)]
@@ -59,7 +59,7 @@
####################
bytes-to (@.read temp-to +0 size client)
#let [to-worked? (and (n/= size bytes-to)
- (:: blob.Equivalence<Blob> = to temp-to))]
+ (:: binary.Equivalence<Binary> = to temp-to))]
####################
_ (@.close client)
_ (T.from-promise (P.future (P.resolve [] server-close)))]
diff --git a/stdlib/test/test/lux/world/net/udp.lux b/stdlib/test/test/lux/world/net/udp.lux
index 444f8ac11..b3911aea3 100644
--- a/stdlib/test/test/lux/world/net/udp.lux
+++ b/stdlib/test/test/lux/world/net/udp.lux
@@ -10,14 +10,14 @@
["." text
format]]
[world
- ["." blob]
+ ["." binary]
["." net
["@" udp]]]
[math
["r" random]]]
lux/test
[///
- ["_." blob]])
+ ["_." binary]])
(def: localhost net.Address "127.0.0.1")
(def: port
@@ -31,9 +31,9 @@
(do @
[port ..port
size (|> r.nat (:: @ map (|>> (n/% +100) (n/max +10))))
- from (_blob.blob size)
- to (_blob.blob size)
- #let [temp (blob.create size)]]
+ from (_binary.binary size)
+ to (_binary.binary size)
+ #let [temp (binary.create size)]]
($_ seq
(wrap (do P.Monad<Promise>
[result (do T.Monad<Task>
@@ -43,12 +43,12 @@
_ (@.write localhost port from +0 size client)
[bytes-from from-address from-port] (@.read temp +0 size server)
#let [from-worked? (and (n/= size bytes-from)
- (:: blob.Equivalence<Blob> = from temp))]
+ (:: binary.Equivalence<Binary> = from temp))]
####################
_ (@.write from-address from-port to +0 size server)
[bytes-to to-address to-port] (@.read temp +0 size client)
#let [to-worked? (and (n/= size bytes-to)
- (:: blob.Equivalence<Blob> = to temp)
+ (:: binary.Equivalence<Binary> = to temp)
(n/= port to-port))]
####################
_ (@.close client)
diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux
index c79b17073..a795556eb 100644
--- a/stdlib/test/tests.lux
+++ b/stdlib/test/tests.lux
@@ -168,7 +168,7 @@
["_.S" case]
["_.S" function]]]]
[world
- ["_." blob]
+ ["_." binary]
## ["_." file] ## TODO: Specially troublesome...
[net
["_." tcp]