aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/world
diff options
context:
space:
mode:
authorEduardo Julian2021-07-06 21:34:21 -0400
committerEduardo Julian2021-07-06 21:34:21 -0400
commit2b909032e7a0bd10cd7db52067d2fb701bfa95e5 (patch)
tree0e2aaef228f80f3336715327f7f34065c309de22 /stdlib/source/test/lux/world
parent5cf4efa861075f8276f43a2516f5beacaf610b44 (diff)
Simplified the API for file-system operations.
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux/world/file.lux199
-rw-r--r--stdlib/source/test/lux/world/file/watch.lux131
2 files changed, 88 insertions, 242 deletions
diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux
index 8a0c416be..4b9f8655a 100644
--- a/stdlib/source/test/lux/world/file.lux
+++ b/stdlib/source/test/lux/world/file.lux
@@ -1,206 +1,27 @@
(.module:
[lux #*
- ["%" data/text/format (#+ format)]
["_" test (#+ Test)]
- [abstract/monad (#+ do)]
+ [abstract
+ [monad (#+ do)]]
[control
- ["." io (#+ IO)]
- ["." try (#+ Try)]
- [concurrency
- ["." promise]]]
- [data
- ["." binary (#+ Binary)]
- ["." text]
- [collection
- ["." list]]]
+ ["." io]]
[math
- ["." random (#+ Random) ("#\." monad)]
- [number
- ["n" nat]
- ["i" int]]]
- [time
- ["." instant]
- ["." duration]]]
+ ["." random]]]
["." / #_
["#." watch]]
{1
- ["." / (#+ Path File)]}
- [///
- [data
- ["_." binary]]])
-
-(def: truncate_millis
- (let [millis +1,000]
- (|>> (i./ millis) (i.* millis))))
-
-## (def: (creation_and_deletion number)
-## (-> Nat Test)
-## (random\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))
-## (try.lift io.monad (/.exists? io.monad /.default path)))]
-## pre! check_existence!
-## file (!.use (\ /.default create_file) path)
-## post! check_existence!
-## _ (!.use (\ file delete) [])
-## 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)
-## (-> Nat Binary Test)
-## (random\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)
-## content (!.use (\ file content) [])
-## _ (!.use (\ file delete) [])]
-## (wrap (\ binary.equivalence = data content))))]
-## (_.assert "Can write/read files."
-## (try.default #0 result)))))
+ ["." /]}
+ {[1 #spec]
+ ["$." /]})
(def: #export test
Test
(<| (_.covering /._)
(do {! random.monad}
- [file_size (|> random.nat (\ ! map (|>> (n.% 100) (n.max 10))))
- dataL (_binary.random file_size)
- dataR (_binary.random file_size)
- new_modified (|> random.int (\ ! map (|>> i.abs
- (i.% +10,000,000,000,000)
- truncate_millis
- duration.from_millis
- instant.absolute)))]
+ [/ (random.ascii/upper 1)]
($_ _.and
- ## (..creation_and_deletion 0)
- ## (..read_and_write 1 dataL)
+ (_.for [/.mock]
+ ($/.spec (io.io (/.mock /))))
- ## (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) [])
- ## _ (!.use (\ file delete) [])]
- ## (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)
- ## _ (!.use (\ file append) dataR)
- ## content (!.use (\ file content) [])
- ## read_size (!.use (\ file size) [])
- ## _ (!.use (\ file delete) [])]
- ## (wrap (and (n.= (n.* 2 file_size) read_size)
- ## (\ binary.equivalence =
- ## dataL
- ## (try.assume (binary.slice 0 file_size content)))
- ## (\ binary.equivalence =
- ## dataR
- ## (try.assume (binary.slice file_size (n.- file_size 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))
- ## (try.lift io.monad (/.exists? io.monad /.default path)))]
- ## pre! check_existence!
- ## dir (!.use (\ /.default create_directory) path)
- ## post! check_existence!
- ## _ (!.use (\ dir discard) [])
- ## 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"]
- ## 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) [])
- ## _ (!.use (\ file delete) [])
- ## _ (!.use (\ dir discard) [])]
- ## (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"]
- ## 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) [])
-
- ## 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 (\ 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)))))))]
- ## (_.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) [])
- ## _ (!.use (\ file delete) [])]
- ## (wrap (\ instant.equivalence = new_modified current_modified))))]
- ## (_.assert "Can change the time of last modification."
- ## (try.default #0 result))))
- ## (wrap (do promise.monad
- ## [#let [path0 (format "temp_file_8+0")
- ## path1 (format "temp_file_8+1")]
- ## result (promise.future
- ## (do (try.with io.monad)
- ## [#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)
- ## file1 (: (IO (Try (File IO))) ## TODO: Remove :
- ## (!.use (\ file0 move) path1))
- ## post! (check_existence! path0)
- ## confirmed? (check_existence! path1)
- ## _ (!.use (\ file1 delete) [])]
- ## (wrap (and pre!
- ## (not post!)
- ## confirmed?))))]
- ## (_.assert "Can move a file from one path to another."
- ## (try.default #0 result))))
-
/watch.test
))))
diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux
index 9c1b31811..57511136e 100644
--- a/stdlib/source/test/lux/world/file/watch.lux
+++ b/stdlib/source/test/lux/world/file/watch.lux
@@ -5,12 +5,12 @@
[predicate (#+ Predicate)]
[monad (#+ do)]]
[control
- ["." try]
+ ["." try (#+ Try)]
["." exception]
[concurrency
- ["." promise]]]
+ ["." promise (#+ Promise)]]]
[data
- ["." binary ("#\." equivalence)]
+ ["." binary (#+ Binary) ("#\." equivalence)]
["." text ("#\." equivalence)
["%" format (#+ format)]]
[collection
@@ -18,10 +18,11 @@
[math
["." random (#+ Random) ("#\." monad)]]]
{1
- ["." /]}
+ ["." /
+ ["/#" //]]}
[////
[data
- ["_." binary]]])
+ ["$." binary]]])
(def: concern
(Random [/.Concern (Predicate /.Concern)])
@@ -87,6 +88,66 @@
false)))))
)))
+(def: (no_events_prior_to_creation! fs watcher directory)
+ (-> (//.System Promise) (/.Watcher Promise) //.Path (Promise (Try Bit)))
+ (do {! (try.with promise.monad)}
+ [_ (\ fs make_directory directory)
+ _ (\ watcher start /.all directory)]
+ (|> (\ watcher poll [])
+ (\ ! map list.empty?))))
+
+(def: (after_creation! fs watcher expected_path)
+ (-> (//.System Promise) (/.Watcher Promise) //.Path (Promise (Try Bit)))
+ (do (try.with promise.monad)
+ [_ (: (Promise (Try Any))
+ (//.make_file promise.monad fs (binary.create 0) expected_path))
+ poll/pre (\ watcher poll [])
+ poll/post (\ watcher poll [])]
+ (wrap (and (case poll/pre
+ (^ (list [concern actual_path]))
+ (and (text\= expected_path actual_path)
+ (and (/.creation? concern)
+ (not (/.modification? concern))
+ (not (/.deletion? concern))))
+
+ _
+ false)
+ (list.empty? poll/post)))))
+
+(def: (after_modification! fs watcher data expected_path)
+ (-> (//.System Promise) (/.Watcher Promise) Binary //.Path (Promise (Try Bit)))
+ (do (try.with promise.monad)
+ [_ (promise.delay 1 (#try.Success "Delay to make sure the over_write time-stamp always changes."))
+ _ (\ fs write data expected_path)
+ poll/2 (\ watcher poll [])
+ poll/2' (\ watcher poll [])]
+ (wrap (and (case poll/2
+ (^ (list [concern actual_path]))
+ (and (text\= expected_path actual_path)
+ (and (not (/.creation? concern))
+ (/.modification? concern)
+ (not (/.deletion? concern))))
+
+ _
+ false)
+ (list.empty? poll/2')))))
+
+(def: (after_deletion! fs watcher expected_path)
+ (-> (//.System Promise) (/.Watcher Promise) //.Path (Promise (Try Bit)))
+ (do (try.with promise.monad)
+ [_ (\ fs delete expected_path)
+ poll/3 (\ watcher poll [])
+ poll/3' (\ watcher poll [])]
+ (wrap (and (case poll/3
+ (^ (list [concern actual_path]))
+ (and (not (/.creation? concern))
+ (not (/.modification? concern))
+ (/.deletion? concern))
+
+ _
+ false)
+ (list.empty? poll/3')))))
+
(def: #export test
Test
(<| (_.covering /._)
@@ -101,56 +162,20 @@
[fs watcher] (/.mock /)]
expected_path (\ ! map (|>> (format directory /))
(random.ascii/alpha 5))
- data (_binary.random 10)]
+ data ($binary.random 10)]
(wrap (do {! promise.monad}
[verdict (do (try.with !)
- [_ (\ fs create_directory directory)
- _ (\ watcher start /.all directory)
- poll/0 (\ watcher poll [])
- #let [no_events_prior_to_creation!
- (list.empty? poll/0)]
- file (\ fs create_file expected_path)
- poll/1 (\ watcher poll [])
- poll/1' (\ watcher poll [])
- #let [after_creation!
- (and (case poll/1
- (^ (list [actual_path concern]))
- (and (text\= expected_path actual_path)
- (and (/.creation? concern)
- (not (/.modification? concern))
- (not (/.deletion? concern))))
-
- _
- false)
- (list.empty? poll/1'))]
- _ (promise.delay 1 (#try.Success "Delay to make sure the over_write time-stamp always changes."))
- _ (\ file over_write data)
- poll/2 (\ watcher poll [])
- poll/2' (\ watcher poll [])
- #let [after_modification!
- (and (case poll/2
- (^ (list [actual_path concern]))
- (and (text\= expected_path actual_path)
- (and (not (/.creation? concern))
- (/.modification? concern)
- (not (/.deletion? concern))))
-
- _
- false)
- (list.empty? poll/2'))]
- _ (\ file delete [])
- poll/3 (\ watcher poll [])
- poll/3' (\ watcher poll [])
- #let [after_deletion!
- (and (case poll/3
- (^ (list [actual_path concern]))
- (and (not (/.creation? concern))
- (not (/.modification? concern))
- (/.deletion? concern))
-
- _
- false)
- (list.empty? poll/3'))]]
+ [no_events_prior_to_creation!
+ (..no_events_prior_to_creation! fs watcher directory)
+
+ after_creation!
+ (..after_creation! fs watcher expected_path)
+
+ after_modification!
+ (..after_modification! fs watcher data expected_path)
+
+ after_deletion!
+ (..after_deletion! fs watcher expected_path)]
(wrap (and no_events_prior_to_creation!
after_creation!
after_modification!