aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/world/file.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/world/file.lux')
-rw-r--r--stdlib/source/library/lux/world/file.lux294
1 files changed, 147 insertions, 147 deletions
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index 606cadc3f..cf1a5fc83 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -303,29 +303,29 @@
@.js
(as_is (ffi.import: Buffer
- ["[1]::[0]"
- ("static" from [Binary] ..Buffer)])
+ "[1]::[0]"
+ ("static" from [Binary] ..Buffer))
(ffi.import: FileDescriptor
- ["[1]::[0]"])
+ "[1]::[0]")
(ffi.import: Stats
- ["[1]::[0]"
- (size ffi.Number)
- (mtimeMs ffi.Number)
- (isFile [] ffi.Boolean)
- (isDirectory [] ffi.Boolean)])
+ "[1]::[0]"
+ (size ffi.Number)
+ (mtimeMs ffi.Number)
+ (isFile [] ffi.Boolean)
+ (isDirectory [] ffi.Boolean))
(ffi.import: FsConstants
- ["[1]::[0]"
- (F_OK ffi.Number)
- (R_OK ffi.Number)
- (W_OK ffi.Number)
- (X_OK ffi.Number)])
+ "[1]::[0]"
+ (F_OK ffi.Number)
+ (R_OK ffi.Number)
+ (W_OK ffi.Number)
+ (X_OK ffi.Number))
(ffi.import: Error
- ["[1]::[0]"
- (toString [] ffi.String)])
+ "[1]::[0]"
+ (toString [] ffi.String))
(template: (with_async <write> <type> <body>)
[(template.with_locals [<read>]
@@ -336,41 +336,41 @@
<read>)))])
(ffi.import: Fs
- ["[1]::[0]"
- (constants FsConstants)
- (readFile [ffi.String ffi.Function] Any)
- (appendFile [ffi.String Buffer ffi.Function] Any)
- (writeFile [ffi.String Buffer ffi.Function] Any)
- (stat [ffi.String ffi.Function] Any)
- (access [ffi.String ffi.Number ffi.Function] Any)
- (rename [ffi.String ffi.String ffi.Function] Any)
- (utimes [ffi.String ffi.Number ffi.Number ffi.Function] Any)
- (readdir [ffi.String ffi.Function] Any)
- (mkdir [ffi.String ffi.Function] Any)
- (unlink [ffi.String ffi.Function] Any)
- (rmdir [ffi.String ffi.Function] Any)])
+ "[1]::[0]"
+ (constants FsConstants)
+ (readFile [ffi.String ffi.Function] Any)
+ (appendFile [ffi.String Buffer ffi.Function] Any)
+ (writeFile [ffi.String Buffer ffi.Function] Any)
+ (stat [ffi.String ffi.Function] Any)
+ (access [ffi.String ffi.Number ffi.Function] Any)
+ (rename [ffi.String ffi.String ffi.Function] Any)
+ (utimes [ffi.String ffi.Number ffi.Number ffi.Function] Any)
+ (readdir [ffi.String ffi.Function] Any)
+ (mkdir [ffi.String ffi.Function] Any)
+ (unlink [ffi.String ffi.Function] Any)
+ (rmdir [ffi.String ffi.Function] Any))
(def: (any_callback write!)
(-> (async.Resolver (Try Any)) ffi.Function)
- (<| (ffi.closure [error])
+ (<| (ffi.function [error])
io.run!
write!
(if (ffi.null? error)
{try.#Success []}
- {try.#Failure (Error::toString [] (:as Error error))})))
+ {try.#Failure (Error::toString (:as Error error))})))
(def: (value_callback write!)
(All (_ a) (-> (async.Resolver (Try a)) ffi.Function))
- (<| (ffi.closure [error datum])
+ (<| (ffi.function [error datum])
io.run!
write!
(if (ffi.null? error)
{try.#Success (:expected datum)}
- {try.#Failure (Error::toString [] (:as Error error))})))
+ {try.#Failure (Error::toString (:as Error error))})))
(ffi.import: JsPath
- ["[1]::[0]"
- (sep ffi.String)])
+ "[1]::[0]"
+ (sep ffi.String))
(def: .public default
(Maybe (System Async))
@@ -390,11 +390,11 @@
[(def: (<name> path)
(do async.monad
[?stats (with_async write! (Try Stats)
- (Fs::stat [path (..value_callback write!)]
+ (Fs::stat path (..value_callback write!)
node_fs))]
(in (case ?stats
{try.#Success stats}
- (<method> [] stats)
+ (<method> stats)
{try.#Failure _}
false))))]
@@ -406,9 +406,9 @@
(def: (make_directory path)
(do async.monad
[outcome (with_async write! (Try Any)
- (Fs::access [path
- (|> node_fs Fs::constants FsConstants::F_OK)
- (..any_callback write!)]
+ (Fs::access path
+ (|> node_fs Fs::constants FsConstants::F_OK)
+ (..any_callback write!)
node_fs))]
(case outcome
{try.#Success _}
@@ -416,20 +416,20 @@
{try.#Failure _}
(with_async write! (Try Any)
- (Fs::mkdir [path (..any_callback write!)] node_fs)))))
+ (Fs::mkdir path (..any_callback write!) node_fs)))))
(~~ (template [<name> <method>]
[(def: (<name> path)
(do [! (try.with async.monad)]
[subs (with_async write! (Try (Array ffi.String))
- (Fs::readdir [path (..value_callback write!)] node_fs))]
+ (Fs::readdir path (..value_callback write!) node_fs))]
(|> subs
(array.list {.#None})
(list#each (|>> (format path js_separator)))
(monad.each ! (function (_ sub)
- (# ! each (|>> (<method> []) [sub])
+ (# ! each (|>> <method> [sub])
(with_async write! (Try Stats)
- (Fs::stat [sub (..value_callback write!)] node_fs)))))
+ (Fs::stat sub (..value_callback write!) node_fs)))))
(# ! each (|>> (list.only product.right)
(list#each product.left))))))]
@@ -440,7 +440,7 @@
(def: (file_size path)
(do (try.with async.monad)
[stats (with_async write! (Try Stats)
- (Fs::stat [path (..value_callback write!)]
+ (Fs::stat path (..value_callback write!)
node_fs))]
(in (|> stats
Stats::size
@@ -449,7 +449,7 @@
(def: (last_modified path)
(do (try.with async.monad)
[stats (with_async write! (Try Stats)
- (Fs::stat [path (..value_callback write!)]
+ (Fs::stat path (..value_callback write!)
node_fs))]
(in (|> stats
Stats::mtimeMs
@@ -466,35 +466,35 @@
false)
{try.#Success})
(with_async write! (Try Any)
- (Fs::access [path
- (|> node_fs Fs::constants FsConstants::X_OK)
- (..any_callback write!)]
+ (Fs::access path
+ (|> node_fs Fs::constants FsConstants::X_OK)
+ (..any_callback write!)
node_fs))))
(def: (read path)
(with_async write! (Try Binary)
- (Fs::readFile [path (..value_callback write!)]
+ (Fs::readFile path (..value_callback write!)
node_fs)))
(def: (delete path)
(do (try.with async.monad)
[stats (with_async write! (Try Stats)
- (Fs::stat [path (..value_callback write!)] node_fs))]
+ (Fs::stat path (..value_callback write!) node_fs))]
(with_async write! (Try Any)
- (if (Stats::isFile [] stats)
- (Fs::unlink [path (..any_callback write!)] node_fs)
- (Fs::rmdir [path (..any_callback write!)] node_fs)))))
+ (if (Stats::isFile stats)
+ (Fs::unlink path (..any_callback write!) node_fs)
+ (Fs::rmdir path (..any_callback write!) node_fs)))))
(def: (modify time_stamp path)
(with_async write! (Try Any)
(let [when (|> time_stamp instant.relative duration.millis i.frac)]
- (Fs::utimes [path when when (..any_callback write!)]
+ (Fs::utimes path when when (..any_callback write!)
node_fs))))
(~~ (template [<name> <method>]
[(def: (<name> data path)
(with_async write! (Try Any)
- (<method> [path (Buffer::from data) (..any_callback write!)]
+ (<method> path (Buffer::from data) (..any_callback write!)
node_fs)))]
[write Fs::writeFile]
@@ -503,7 +503,7 @@
(def: (move destination origin)
(with_async write! (Try Any)
- (Fs::rename [origin destination (..any_callback write!)]
+ (Fs::rename origin destination (..any_callback write!)
node_fs))))))))))
@.python
@@ -511,36 +511,36 @@
(Primitive "python_tuple[2]" [left right]))
(ffi.import: PyFile
- ["[1]::[0]"
- (read [] "io" "try" Binary)
- (write [Binary] "io" "try" "?" Any)
- (close [] "io" "try" "?" Any)])
+ "[1]::[0]"
+ (read [] "io" "try" Binary)
+ (write [Binary] "io" "try" "?" Any)
+ (close [] "io" "try" "?" Any))
(ffi.import: (open [ffi.String ffi.String] "io" "try" PyFile))
(ffi.import: (tuple [[ffi.Integer ffi.Integer]] (Tuple/2 ffi.Integer ffi.Integer)))
(ffi.import: os
- ["[1]::[0]"
- ("static" F_OK ffi.Integer)
- ("static" R_OK ffi.Integer)
- ("static" W_OK ffi.Integer)
- ("static" X_OK ffi.Integer)
-
- ("static" mkdir [ffi.String] "io" "try" "?" Any)
- ("static" access [ffi.String ffi.Integer] "io" "try" ffi.Boolean)
- ("static" remove [ffi.String] "io" "try" "?" Any)
- ("static" rmdir [ffi.String] "io" "try" "?" Any)
- ("static" rename [ffi.String ffi.String] "io" "try" "?" Any)
- ("static" utime [ffi.String (Tuple/2 ffi.Integer ffi.Integer)] "io" "try" "?" Any)
- ("static" listdir [ffi.String] "io" "try" (Array ffi.String))])
+ "[1]::[0]"
+ ("static" F_OK ffi.Integer)
+ ("static" R_OK ffi.Integer)
+ ("static" W_OK ffi.Integer)
+ ("static" X_OK ffi.Integer)
+
+ ("static" mkdir [ffi.String] "io" "try" "?" Any)
+ ("static" access [ffi.String ffi.Integer] "io" "try" ffi.Boolean)
+ ("static" remove [ffi.String] "io" "try" "?" Any)
+ ("static" rmdir [ffi.String] "io" "try" "?" Any)
+ ("static" rename [ffi.String ffi.String] "io" "try" "?" Any)
+ ("static" utime [ffi.String (Tuple/2 ffi.Integer ffi.Integer)] "io" "try" "?" Any)
+ ("static" listdir [ffi.String] "io" "try" (Array ffi.String)))
(ffi.import: os/path
- ["[1]::[0]"
- ("static" isfile [ffi.String] "io" "try" ffi.Boolean)
- ("static" isdir [ffi.String] "io" "try" ffi.Boolean)
- ("static" sep ffi.String)
- ("static" getsize [ffi.String] "io" "try" ffi.Integer)
- ("static" getmtime [ffi.String] "io" "try" ffi.Float)])
+ "[1]::[0]"
+ ("static" isfile [ffi.String] "io" "try" ffi.Boolean)
+ ("static" isdir [ffi.String] "io" "try" ffi.Boolean)
+ ("static" sep ffi.String)
+ ("static" getsize [ffi.String] "io" "try" ffi.Integer)
+ ("static" getmtime [ffi.String] "io" "try" ffi.Float))
(def: python_separator
(os/path::sep))
@@ -571,7 +571,7 @@
(# ! each (|>> (array.list {.#None})
(list#each (|>> (format path ..python_separator)))
(monad.each ! (function (_ sub)
- (# ! each (|>> [sub]) (<method> [sub]))))
+ (# ! each (|>> [sub]) (<method> sub))))
(# ! each (|>> (list.only product.right)
(list#each product.left)))))
(# ! conjoint))))]
@@ -592,80 +592,80 @@
instant.absolute))))
(def: (can_execute? path)
- (os::access [path (os::X_OK)]))
+ (os::access path (os::X_OK)))
(def: (read path)
(do (try.with io.monad)
- [file (..open [path "rb"])
- data (PyFile::read [] file)
- _ (PyFile::close [] file)]
+ [file (..open path "rb")
+ data (PyFile::read file)
+ _ (PyFile::close file)]
(in data)))
(def: (delete path)
(do (try.with io.monad)
- [? (os/path::isfile [path])]
+ [? (os/path::isfile path)]
(if ?
- (os::remove [path])
- (os::rmdir [path]))))
+ (os::remove path)
+ (os::rmdir path))))
(def: (modify time_stamp path)
(let [when (|> time_stamp instant.relative duration.millis (i./ +1,000))]
- (os::utime [path (..tuple [when when])])))
+ (os::utime path (..tuple [when when]))))
(~~ (template [<name> <mode>]
[(def: (<name> data path)
(do (try.with io.monad)
- [file (..open [path <mode>])
- _ (PyFile::write [data] file)]
- (PyFile::close [] file)))]
+ [file (..open path <mode>)
+ _ (PyFile::write data file)]
+ (PyFile::close file)))]
[write "w+b"]
[append "ab"]
))
(def: (move destination origin)
- (os::rename [origin destination]))
+ (os::rename origin destination))
)))
@.ruby
- (as_is (ffi.import: Time "as" RubyTime
- ["[1]::[0]"
- ("static" at [Frac] RubyTime)
- (to_f [] Frac)])
+ (as_is (ffi.import: Time
+ "[1]::[0]"
+ ("static" at [Frac] Time)
+ (to_f [] Frac))
- (ffi.import: Stat "as" RubyStat
- ["[1]::[0]"
- (executable? [] Bit)
- (size Int)
- (mtime [] RubyTime)])
+ (ffi.import: Stat
+ "[1]::[0]"
+ (executable? [] Bit)
+ (size Int)
+ (mtime [] Time))
(ffi.import: File "as" RubyFile
- ["[1]::[0]"
- ("static" SEPARATOR ffi.String)
- ("static" open [Path ffi.String] "io" "try" RubyFile)
- ("static" stat [Path] "io" "try" RubyStat)
- ("static" delete [Path] "io" "try" Int)
- ("static" file? [Path] "io" "try" Bit)
- ("static" directory? [Path] "io" "try" Bit)
- ("static" utime [RubyTime RubyTime Path] "io" "try" Int)
-
- (read [] "io" "try" Binary)
- (write [Binary] "io" "try" Int)
- (flush [] "io" "try" "?" Any)
- (close [] "io" "try" "?" Any)])
-
- (ffi.import: Dir "as" RubyDir
- ["[1]::[0]"
- ("static" open [Path] "io" "try" RubyDir)
-
- (children [] "io" "try" (Array Path))
- (close [] "io" "try" "?" Any)])
-
- (ffi.import: "fileutils" FileUtils "as" RubyFileUtils
- ["[1]::[0]"
- ("static" move [Path Path] "io" "try" "?" Any)
- ("static" rmdir [Path] "io" "try" "?" Any)
- ("static" mkdir [Path] "io" "try" "?" Any)])
+ "[1]::[0]"
+ ("static" SEPARATOR ffi.String)
+ ("static" open [Path ffi.String] "io" "try" RubyFile)
+ ("static" stat [Path] "io" "try" Stat)
+ ("static" delete [Path] "io" "try" Int)
+ ("static" file? [Path] "io" "try" Bit)
+ ("static" directory? [Path] "io" "try" Bit)
+ ("static" utime [Time Time Path] "io" "try" Int)
+
+ (read [] "io" "try" Binary)
+ (write [Binary] "io" "try" Int)
+ (flush [] "io" "try" "?" Any)
+ (close [] "io" "try" "?" Any))
+
+ (ffi.import: Dir
+ "[1]::[0]"
+ ("static" open [Path] "io" "try" Dir)
+
+ (children [] "io" "try" (Array Path))
+ (close [] "io" "try" "?" Any))
+
+ (ffi.import: "fileutils" FileUtils
+ "[1]::[0]"
+ ("static" move [Path Path] "io" "try" "?" Any)
+ ("static" rmdir [Path] "io" "try" "?" Any)
+ ("static" mkdir [Path] "io" "try" "?" Any))
(def: ruby_separator
Text
@@ -687,13 +687,13 @@
))
(def: make_directory
- RubyFileUtils::mkdir)
+ FileUtils::mkdir)
(~~ (template [<name> <test>]
[(def: (<name> path)
(do [! (try.with io.monad)]
- [self (RubyDir::open [path])
- children (RubyDir::children [] self)
+ [self (Dir::open path)
+ children (Dir::children self)
output (loop [input (|> children
(array.list {.#None})
(list#each (|>> (format path ..ruby_separator))))
@@ -709,7 +709,7 @@
(again tail (if verdict
{.#Item head output}
output)))))
- _ (RubyDir::close [] self)]
+ _ (Dir::close self)]
(in output)))]
[directory_files RubyFile::file?]
@@ -722,29 +722,29 @@
(|>> RubyFile::stat
(# ! each (`` (|>> (~~ (template.spliced <pipeline>))))))))]
- [file_size [RubyStat::size .nat]]
- [last_modified [(RubyStat::mtime [])
- (RubyTime::to_f [])
+ [file_size [Stat::size .nat]]
+ [last_modified [Stat::mtime
+ Time::to_f
(f.* +1,000.0)
f.int
duration.of_millis
instant.absolute]]
- [can_execute? [(RubyStat::executable? [])]]
+ [can_execute? [Stat::executable?]]
))
(def: (read path)
(do (try.with io.monad)
- [file (RubyFile::open [path "rb"])
- data (RubyFile::read [] file)
- _ (RubyFile::close [] file)]
+ [file (RubyFile::open path "rb")
+ data (RubyFile::read file)
+ _ (RubyFile::close file)]
(in data)))
(def: (delete path)
(do (try.with io.monad)
[? (RubyFile::file? path)]
(if ?
- (RubyFile::delete [path])
- (RubyFileUtils::rmdir [path]))))
+ (RubyFile::delete path)
+ (FileUtils::rmdir path))))
(def: (modify moment path)
(let [moment (|> moment
@@ -752,16 +752,16 @@
duration.millis
i.frac
(f./ +1,000.0)
- RubyTime::at)]
- (RubyFile::utime [moment moment path])))
+ Time::at)]
+ (RubyFile::utime moment moment path)))
(~~ (template [<mode> <name>]
[(def: (<name> data path)
(do [! (try.with io.monad)]
- [file (RubyFile::open [path <mode>])
- data (RubyFile::write [data] file)
- _ (RubyFile::flush [] file)
- _ (RubyFile::close [] file)]
+ [file (RubyFile::open path <mode>)
+ data (RubyFile::write data file)
+ _ (RubyFile::flush file)
+ _ (RubyFile::close file)]
(in [])))]
["wb" write]
@@ -770,7 +770,7 @@
(def: (move destination origin)
(do (try.with io.monad)
- [_ (RubyFileUtils::move [origin destination])]
+ [_ (FileUtils::move origin destination)]
(in [])))
)))