aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/world
diff options
context:
space:
mode:
authorEduardo Julian2020-12-25 09:22:38 -0400
committerEduardo Julian2020-12-25 09:22:38 -0400
commit4ca397765805eda5ddee393901ed3a02001a960a (patch)
tree2ab184a1a4e244f3a69e86c8a7bb3ad49c22b4a3 /stdlib/source/test/lux/world
parentd29e091e98dabb8dfcf816899ada480ecbf7e357 (diff)
Replaced kebab-case with snake_case for naming convention.
Diffstat (limited to 'stdlib/source/test/lux/world')
-rw-r--r--stdlib/source/test/lux/world/console.lux8
-rw-r--r--stdlib/source/test/lux/world/file.lux134
-rw-r--r--stdlib/source/test/lux/world/file/watch.lux42
-rw-r--r--stdlib/source/test/lux/world/shell.lux36
4 files changed, 110 insertions, 110 deletions
diff --git a/stdlib/source/test/lux/world/console.lux b/stdlib/source/test/lux/world/console.lux
index 56291563d..b7c7d3a50 100644
--- a/stdlib/source/test/lux/world/console.lux
+++ b/stdlib/source/test/lux/world/console.lux
@@ -17,22 +17,22 @@
(def: simulation
(/.Simulation Bit)
(structure
- (def: (on-read dead?)
+ (def: (on_read dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success [dead? (char "a")])))
- (def: (on-read-line dead?)
+ (def: (on_read_line dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success [dead? "YOLO"])))
- (def: (on-write message dead?)
+ (def: (on_write message dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success dead?)))
- (def: (on-close dead?)
+ (def: (on_close dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success true)))))
diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux
index 35706fa8a..173bd7586 100644
--- a/stdlib/source/test/lux/world/file.lux
+++ b/stdlib/source/test/lux/world/file.lux
@@ -30,37 +30,37 @@
[data
["_." binary]]])
-(def: truncate-millis
+(def: truncate_millis
(let [millis +1,000]
(|>> (i./ millis) (i.* millis))))
-(def: (creation-and-deletion number)
+(def: (creation_and_deletion number)
(-> Nat Test)
(r\wrap (do promise.monad
[#let [path (format "temp_file_" (%.nat number))]
result (promise.future
(do (try.with io.monad)
- [#let [check-existence! (: (IO (Try Bit))
+ [#let [check_existence! (: (IO (Try Bit))
(try.lift io.monad (/.exists? io.monad /.default path)))]
- pre! check-existence!
- file (!.use (\ /.default create-file) path)
- post! check-existence!
+ pre! check_existence!
+ file (!.use (\ /.default create_file) path)
+ post! check_existence!
_ (!.use (\ file delete) [])
- remains? check-existence!]
+ remains? check_existence!]
(wrap (and (not pre!)
post!
(not remains?)))))]
(_.assert "Can create/delete files."
(try.default #0 result)))))
-(def: (read-and-write number data)
+(def: (read_and_write number data)
(-> Nat Binary Test)
(r\wrap (do promise.monad
[#let [path (format "temp_file_" (%.nat number))]
result (promise.future
(do (try.with io.monad)
- [file (!.use (\ /.default create-file) path)
- _ (!.use (\ file over-write) data)
+ [file (!.use (\ /.default create_file) path)
+ _ (!.use (\ file over_write) data)
content (!.use (\ file content) [])
_ (!.use (\ file delete) [])]
(wrap (\ binary.equivalence = data content))))]
@@ -69,114 +69,114 @@
(def: #export test
Test
- (<| (_.context (%.name (name-of /._)))
+ (<| (_.context (%.name (name_of /._)))
(do {! r.monad}
- [file-size (|> r.nat (\ ! map (|>> (n.% 100) (n.max 10))))
- dataL (_binary.random file-size)
- dataR (_binary.random file-size)
- new-modified (|> r.int (\ ! map (|>> i.abs
+ [file_size (|> r.nat (\ ! map (|>> (n.% 100) (n.max 10))))
+ dataL (_binary.random file_size)
+ dataR (_binary.random file_size)
+ new_modified (|> r.int (\ ! map (|>> i.abs
(i.% +10,000,000,000,000)
- truncate-millis
- duration.from-millis
+ truncate_millis
+ duration.from_millis
instant.absolute)))]
($_ _.and
- ## (..creation-and-deletion 0)
- ## (..read-and-write 1 dataL)
+ ## (..creation_and_deletion 0)
+ ## (..read_and_write 1 dataL)
## (wrap (do promise.monad
## [#let [path "temp_file_2"]
## result (promise.future
## (do (try.with io.monad)
- ## [file (!.use (\ /.default create-file) path)
- ## _ (!.use (\ file over-write) dataL)
- ## read-size (!.use (\ file size) [])
+ ## [file (!.use (\ /.default create_file) path)
+ ## _ (!.use (\ file over_write) dataL)
+ ## read_size (!.use (\ file size) [])
## _ (!.use (\ file delete) [])]
- ## (wrap (n.= file-size read-size))))]
+ ## (wrap (n.= file_size read_size))))]
## (_.assert "Can read file size."
## (try.default #0 result))))
## (wrap (do promise.monad
## [#let [path "temp_file_3"]
## result (promise.future
## (do (try.with io.monad)
- ## [file (!.use (\ /.default create-file) path)
- ## _ (!.use (\ file over-write) dataL)
+ ## [file (!.use (\ /.default create_file) path)
+ ## _ (!.use (\ file over_write) dataL)
## _ (!.use (\ file append) dataR)
## content (!.use (\ file content) [])
- ## read-size (!.use (\ file size) [])
+ ## read_size (!.use (\ file size) [])
## _ (!.use (\ file delete) [])]
- ## (wrap (and (n.= (n.* 2 file-size) read-size)
+ ## (wrap (and (n.= (n.* 2 file_size) read_size)
## (\ binary.equivalence =
## dataL
- ## (try.assume (binary.slice 0 (dec file-size) content)))
+ ## (try.assume (binary.slice 0 (dec file_size) content)))
## (\ binary.equivalence =
## dataR
- ## (try.assume (binary.slice file-size (dec read-size) content)))))))]
+ ## (try.assume (binary.slice file_size (dec read_size) content)))))))]
## (_.assert "Can append to files."
## (try.default #0 result))))
## (wrap (do promise.monad
## [#let [path "temp_dir_4"]
## result (promise.future
## (do (try.with io.monad)
- ## [#let [check-existence! (: (IO (Try Bit))
+ ## [#let [check_existence! (: (IO (Try Bit))
## (try.lift io.monad (/.exists? io.monad /.default path)))]
- ## pre! check-existence!
- ## dir (!.use (\ /.default create-directory) path)
- ## post! check-existence!
+ ## pre! check_existence!
+ ## dir (!.use (\ /.default create_directory) path)
+ ## post! check_existence!
## _ (!.use (\ dir discard) [])
- ## remains? check-existence!]
+ ## remains? check_existence!]
## (wrap (and (not pre!)
## post!
## (not remains?)))))]
## (_.assert "Can create/delete directories."
## (try.default #0 result))))
## (wrap (do promise.monad
- ## [#let [file-path "temp_file_5"
- ## dir-path "temp_dir_5"]
+ ## [#let [file_path "temp_file_5"
+ ## dir_path "temp_dir_5"]
## result (promise.future
## (do (try.with io.monad)
- ## [dir (!.use (\ /.default create-directory) dir-path)
- ## file (!.use (\ /.default create-file) (format dir-path "/" file-path))
- ## _ (!.use (\ file over-write) dataL)
- ## read-size (!.use (\ file size) [])
+ ## [dir (!.use (\ /.default create_directory) dir_path)
+ ## file (!.use (\ /.default create_file) (format dir_path "/" file_path))
+ ## _ (!.use (\ file over_write) dataL)
+ ## read_size (!.use (\ file size) [])
## _ (!.use (\ file delete) [])
## _ (!.use (\ dir discard) [])]
- ## (wrap (n.= file-size read-size))))]
+ ## (wrap (n.= file_size read_size))))]
## (_.assert "Can create files inside of directories."
## (try.default #0 result))))
## (wrap (do promise.monad
- ## [#let [file-path "temp_file_6"
- ## dir-path "temp_dir_6"
- ## inner-dir-path "inner_temp_dir_6"]
+ ## [#let [file_path "temp_file_6"
+ ## dir_path "temp_dir_6"
+ ## inner_dir_path "inner_temp_dir_6"]
## result (promise.future
## (do (try.with io.monad)
- ## [dir (!.use (\ /.default create-directory) dir-path)
- ## pre-files (!.use (\ dir files) [])
- ## pre-directories (!.use (\ dir directories) [])
+ ## [dir (!.use (\ /.default create_directory) dir_path)
+ ## pre_files (!.use (\ dir files) [])
+ ## pre_directories (!.use (\ dir directories) [])
- ## file (!.use (\ /.default create-file) (format dir-path "/" file-path))
- ## inner-dir (!.use (\ /.default create-directory) (format dir-path "/" inner-dir-path))
- ## post-files (!.use (\ dir files) [])
- ## post-directories (!.use (\ dir directories) [])
+ ## file (!.use (\ /.default create_file) (format dir_path "/" file_path))
+ ## inner_dir (!.use (\ /.default create_directory) (format dir_path "/" inner_dir_path))
+ ## post_files (!.use (\ dir files) [])
+ ## post_directories (!.use (\ dir directories) [])
## _ (!.use (\ file delete) [])
- ## _ (!.use (\ inner-dir discard) [])
+ ## _ (!.use (\ inner_dir discard) [])
## _ (!.use (\ dir discard) [])]
- ## (wrap (and (and (n.= 0 (list.size pre-files))
- ## (n.= 0 (list.size pre-directories)))
- ## (and (n.= 1 (list.size post-files))
- ## (n.= 1 (list.size post-directories)))))))]
+ ## (wrap (and (and (n.= 0 (list.size pre_files))
+ ## (n.= 0 (list.size pre_directories)))
+ ## (and (n.= 1 (list.size post_files))
+ ## (n.= 1 (list.size post_directories)))))))]
## (_.assert "Can list files/directories inside a directory."
## (try.default #0 result))))
## (wrap (do promise.monad
## [#let [path "temp_file_7"]
## result (promise.future
## (do (try.with io.monad)
- ## [file (!.use (\ /.default create-file) path)
- ## _ (!.use (\ file over-write) dataL)
- ## _ (!.use (\ file modify) new-modified)
- ## current-modified (!.use (\ file last-modified) [])
+ ## [file (!.use (\ /.default create_file) path)
+ ## _ (!.use (\ file over_write) dataL)
+ ## _ (!.use (\ file modify) new_modified)
+ ## current_modified (!.use (\ file last_modified) [])
## _ (!.use (\ file delete) [])]
- ## (wrap (\ instant.equivalence = new-modified current-modified))))]
+ ## (wrap (\ instant.equivalence = new_modified current_modified))))]
## (_.assert "Can change the time of last modification."
## (try.default #0 result))))
## (wrap (do promise.monad
@@ -184,16 +184,16 @@
## path1 (format "temp_file_8+1")]
## result (promise.future
## (do (try.with io.monad)
- ## [#let [check-existence! (: (-> Path (IO (Try Bit)))
+ ## [#let [check_existence! (: (_> Path (IO (Try Bit)))
## (|>> (/.exists? io.monad /.default)
## (try.lift io.monad)))]
- ## file0 (!.use (\ /.default create-file) path0)
- ## _ (!.use (\ file0 over-write) dataL)
- ## pre! (check-existence! path0)
+ ## file0 (!.use (\ /.default create_file) path0)
+ ## _ (!.use (\ file0 over_write) dataL)
+ ## pre! (check_existence! path0)
## file1 (: (IO (Try (File IO))) ## TODO: Remove :
## (!.use (\ file0 move) path1))
- ## post! (check-existence! path0)
- ## confirmed? (check-existence! path1)
+ ## post! (check_existence! path0)
+ ## confirmed? (check_existence! path1)
## _ (!.use (\ file1 delete) [])]
## (wrap (and pre!
## (not post!)
diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux
index aa3a51e59..c0873b41a 100644
--- a/stdlib/source/test/lux/world/file/watch.lux
+++ b/stdlib/source/test/lux/world/file/watch.lux
@@ -74,16 +74,16 @@
(wrap (do promise.monad
[?concern (\ watcher concern directory)
?stop (\ watcher stop directory)]
- (_.cover' [/.not-being-watched]
+ (_.cover' [/.not_being_watched]
(and (case ?concern
(#try.Failure error)
- (exception.match? /.not-being-watched error)
+ (exception.match? /.not_being_watched error)
(#try.Success _)
false)
(case ?stop
(#try.Failure error)
- (exception.match? /.not-being-watched error)
+ (exception.match? /.not_being_watched error)
(#try.Success _)
false)))))
@@ -101,23 +101,23 @@
[directory (random.ascii/alpha 5)
#let [/ "/"
[fs watcher] (/.mock /)]
- expected-path (\ ! map (|>> (format directory /))
+ expected_path (\ ! map (|>> (format directory /))
(random.ascii/alpha 5))
data (_binary.random 10)]
(wrap (do {! promise.monad}
[verdict (do (try.with !)
- [_ (!.use (\ fs create-directory) [directory])
+ [_ (!.use (\ fs create_directory) [directory])
_ (\ watcher start /.all directory)
poll/0 (\ watcher poll [])
- #let [no-events-prior-to-creation!
+ #let [no_events_prior_to_creation!
(list.empty? poll/0)]
- file (!.use (\ fs create-file) [expected-path])
+ file (!.use (\ fs create_file) [expected_path])
poll/1 (\ watcher poll [])
poll/1' (\ watcher poll [])
- #let [after-creation!
+ #let [after_creation!
(and (case poll/1
- (^ (list [actual-path concern]))
- (and (text\= expected-path actual-path)
+ (^ (list [actual_path concern]))
+ (and (text\= expected_path actual_path)
(and (/.creation? concern)
(not (/.modification? concern))
(not (/.deletion? concern))))
@@ -125,14 +125,14 @@
_
false)
(list.empty? poll/1'))]
- _ (promise.delay 1 (#try.Success "Delay to make sure the over-write time-stamp always changes."))
- _ (!.use (\ file over-write) data)
+ _ (promise.delay 1 (#try.Success "Delay to make sure the over_write time-stamp always changes."))
+ _ (!.use (\ file over_write) data)
poll/2 (\ watcher poll [])
poll/2' (\ watcher poll [])
- #let [after-modification!
+ #let [after_modification!
(and (case poll/2
- (^ (list [actual-path concern]))
- (and (text\= expected-path actual-path)
+ (^ (list [actual_path concern]))
+ (and (text\= expected_path actual_path)
(and (not (/.creation? concern))
(/.modification? concern)
(not (/.deletion? concern))))
@@ -143,9 +143,9 @@
_ (!.use (\ file delete) [])
poll/3 (\ watcher poll [])
poll/3' (\ watcher poll [])
- #let [after-deletion!
+ #let [after_deletion!
(and (case poll/3
- (^ (list [actual-path concern]))
+ (^ (list [actual_path concern]))
(and (not (/.creation? concern))
(not (/.modification? concern))
(/.deletion? concern))
@@ -153,10 +153,10 @@
_
false)
(list.empty? poll/3'))]]
- (wrap (and no-events-prior-to-creation!
- after-creation!
- after-modification!
- after-deletion!)))]
+ (wrap (and no_events_prior_to_creation!
+ after_creation!
+ after_modification!
+ after_deletion!)))]
(_.cover' [/.mock /.polling]
(try.default false verdict)))))
)))
diff --git a/stdlib/source/test/lux/world/shell.lux b/stdlib/source/test/lux/world/shell.lux
index d3c7e24f8..1dbe5dcd5 100644
--- a/stdlib/source/test/lux/world/shell.lux
+++ b/stdlib/source/test/lux/world/shell.lux
@@ -32,65 +32,65 @@
(exception: dead)
-(def: (simulation [environment working-directory command arguments])
+(def: (simulation [environment working_directory command arguments])
(-> [Environment Path /.Command (List /.Argument)]
(/.Simulation Bit))
(structure
- (def: (on-read dead?)
+ (def: (on_read dead?)
(if dead?
(exception.throw ..dead [])
(do try.monad
- [to-echo (try.from-maybe (list.head arguments))]
- (wrap [dead? to-echo]))))
+ [to_echo (try.from_maybe (list.head arguments))]
+ (wrap [dead? to_echo]))))
- (def: (on-error dead?)
+ (def: (on_error dead?)
(if dead?
(exception.throw ..dead [])
(exception.return [dead? ""])))
- (def: (on-write message dead?)
+ (def: (on_write message dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success dead?)))
- (def: (on-destroy dead?)
+ (def: (on_destroy dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success true)))
- (def: (on-await dead?)
+ (def: (on_await dead?)
(if dead?
(exception.throw ..dead [])
(#try.Success [true /.normal])))))
-(def: (io-shell command oops input destruction exit)
+(def: (io_shell command oops input destruction exit)
(-> /.Command Text Text Text /.Exit (/.Shell IO))
(structure
(def: execute
- ((debug.private /.can-execute)
- (function (_ [environment working-directory command arguments])
+ ((debug.private /.can_execute)
+ (function (_ [environment working_directory command arguments])
(io.io
(#try.Success
(: (/.Process IO)
(structure
(def: read
- ((debug.private /.can-read)
+ ((debug.private /.can_read)
(function (_ _)
(io.io (#try.Success command)))))
(def: error
- ((debug.private /.can-read)
+ ((debug.private /.can_read)
(function (_ _)
(io.io (#try.Success oops)))))
(def: write
- ((debug.private /.can-write)
+ ((debug.private /.can_write)
(function (_ message)
(io.io (#try.Failure message)))))
(def: destroy
- ((debug.private /.can-destroy)
+ ((debug.private /.can_destroy)
(function (_ _)
(io.io (#try.Failure destruction)))))
(def: await
- ((debug.private /.can-wait)
+ ((debug.private /.can_wait)
(function (_ _)
(io.io (#try.Success exit))))))))))))))
@@ -109,7 +109,7 @@
input (random.ascii/alpha 5)
destruction (random.ascii/alpha 5)
exit random.int
- #let [shell (/.async (..io-shell command oops input destruction exit))]]
+ #let [shell (/.async (..io_shell command oops input destruction exit))]]
(wrap (do {! promise.monad}
[verdict (do (try.with !)
[process (!.use (\ shell execute) [environment.empty "~" command (list)])
@@ -137,6 +137,6 @@
wrote!
destroyed!
(i.= exit await))))]
- (_.cover' [/.async /.Can-Write]
+ (_.cover' [/.async /.Can_Write]
(try.default false verdict)))))
)))