aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/world
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/world')
-rw-r--r--stdlib/source/library/lux/world/console.lux136
-rw-r--r--stdlib/source/library/lux/world/file.lux1308
-rw-r--r--stdlib/source/library/lux/world/file/watch.lux4
-rw-r--r--stdlib/source/library/lux/world/net/http/client.lux4
-rw-r--r--stdlib/source/library/lux/world/program.lux488
-rw-r--r--stdlib/source/library/lux/world/shell.lux4
6 files changed, 972 insertions, 972 deletions
diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux
index 781a11c29..b8f3f6cbc 100644
--- a/stdlib/source/library/lux/world/console.lux
+++ b/stdlib/source/library/lux/world/console.lux
@@ -93,74 +93,74 @@
(def: close
(|>> (exception.except ..cannot_close) in)))))))))]
- (for [@.old (as_is <jvm>)
- @.jvm (as_is <jvm>)
- @.js (as_is (ffi.import: Buffer
- "[1]::[0]"
- (toString [] ffi.String))
-
- (ffi.import: Readable_Stream
- "[1]::[0]"
- (read [] "?" Buffer)
- (unshift "as" unshift|String [ffi.String] ffi.Boolean)
- (unshift "as" unshift|Buffer [Buffer] ffi.Boolean))
-
- (ffi.import: Writable_Stream
- "[1]::[0]"
- (write [ffi.String ffi.Function] ffi.Boolean)
- (once [ffi.String ffi.Function] Any))
-
- (ffi.import: process
- "[1]::[0]"
- ("static" stdout Writable_Stream)
- ("static" stdin Readable_Stream))
-
- (exception: .public cannot_read)
-
- (template: (!read <type> <query>)
- [(let [it (process::stdin)]
- (case (Readable_Stream::read it)
- {.#Some buffer}
- (let [input (Buffer::toString buffer)]
- (case (: (Maybe [<type> Text])
- <query>)
- {.#Some [head tail]}
- (exec
- (Readable_Stream::unshift|String tail it)
- (async#in {try.#Success head}))
-
- {.#None}
- (exec
- (Readable_Stream::unshift|Buffer buffer it)
- (async#in (exception.except ..cannot_read [])))))
-
- {.#None}
- (async#in (exception.except ..cannot_read []))))])
-
- (def: .public default
- (Maybe (Console Async))
- (if ffi.on_node_js?
- {.#Some (implementation
- (def: (read _)
- (!read Char (do maybe.monad
- [head (text.char 0 input)
- [_ tail] (text.split_at 1 input)]
- (in [head tail]))))
-
- (def: (read_line _)
- (!read Text (text.split_by text.\n input)))
-
- (def: (write it)
- (let [[read! write!] (: [(async.Async (Try [])) (async.Resolver (Try []))]
- (async.async []))]
- (exec
- (Writable_Stream::write it (ffi.function (_ []) Any (io.run! (write! {try.#Success []})))
- (process::stdout))
- read!)))
-
- (def: close
- (|>> (exception.except ..cannot_close) async#in)))}
- {.#None})))]
+ (for @.old (as_is <jvm>)
+ @.jvm (as_is <jvm>)
+ @.js (as_is (ffi.import: Buffer
+ "[1]::[0]"
+ (toString [] ffi.String))
+
+ (ffi.import: Readable_Stream
+ "[1]::[0]"
+ (read [] "?" Buffer)
+ (unshift "as" unshift|String [ffi.String] ffi.Boolean)
+ (unshift "as" unshift|Buffer [Buffer] ffi.Boolean))
+
+ (ffi.import: Writable_Stream
+ "[1]::[0]"
+ (write [ffi.String ffi.Function] ffi.Boolean)
+ (once [ffi.String ffi.Function] Any))
+
+ (ffi.import: process
+ "[1]::[0]"
+ ("static" stdout Writable_Stream)
+ ("static" stdin Readable_Stream))
+
+ (exception: .public cannot_read)
+
+ (template: (!read <type> <query>)
+ [(let [it (process::stdin)]
+ (case (Readable_Stream::read it)
+ {.#Some buffer}
+ (let [input (Buffer::toString buffer)]
+ (case (: (Maybe [<type> Text])
+ <query>)
+ {.#Some [head tail]}
+ (exec
+ (Readable_Stream::unshift|String tail it)
+ (async#in {try.#Success head}))
+
+ {.#None}
+ (exec
+ (Readable_Stream::unshift|Buffer buffer it)
+ (async#in (exception.except ..cannot_read [])))))
+
+ {.#None}
+ (async#in (exception.except ..cannot_read []))))])
+
+ (def: .public default
+ (Maybe (Console Async))
+ (if ffi.on_node_js?
+ {.#Some (implementation
+ (def: (read _)
+ (!read Char (do maybe.monad
+ [head (text.char 0 input)
+ [_ tail] (text.split_at 1 input)]
+ (in [head tail]))))
+
+ (def: (read_line _)
+ (!read Text (text.split_by text.\n input)))
+
+ (def: (write it)
+ (let [[read! write!] (: [(async.Async (Try [])) (async.Resolver (Try []))]
+ (async.async []))]
+ (exec
+ (Writable_Stream::write it (ffi.function (_ []) Any (io.run! (write! {try.#Success []})))
+ (process::stdout))
+ read!)))
+
+ (def: close
+ (|>> (exception.except ..cannot_close) async#in)))}
+ {.#None})))
(as_is)))
(def: .public (write_line message console)
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index c2e799be8..63fa2e88b 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -25,8 +25,8 @@
["[0]" list ("[1]#[0]" functor)]
["[0]" dictionary {"+" Dictionary}]]]
["[0]" ffi
- (~~ (.for ["JavaScript" (~~ (.as_is ["[0]" node_js]))
- "{old}" (~~ (.as_is ["node_js" //control/thread]))]
+ (~~ (.for "JavaScript" (~~ (.as_is ["[0]" node_js]))
+ "{old}" (~~ (.as_is ["node_js" //control/thread]))
(~~ (.as_is))))]
[macro
["[0]" template]]
@@ -298,662 +298,662 @@
java/io/File::new
(java/io/File::renameTo (java/io/File::new (ffi.as_string destination)))))
)))]
- (for [@.old (as_is <for_jvm>)
- @.jvm (as_is <for_jvm>)
-
- @.js
- (as_is (ffi.import: Buffer
- "[1]::[0]"
- ("static" from [Binary] ..Buffer))
-
- (ffi.import: FileDescriptor
- "[1]::[0]")
-
- (ffi.import: Stats
- "[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))
-
- (ffi.import: Error
- "[1]::[0]"
- (toString [] ffi.String))
-
- (template: (with_async <write> <type> <body>)
- [(template.with_locals [<read>]
- (let [[<read> <write>] (: [(Async <type>) (async.Resolver <type>)]
- (async.async []))]
- (exec
- <body>
- <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))
-
- (def: (any_callback write!)
- (-> (async.Resolver (Try Any)) ffi.Function)
- (<| (ffi.function (_ [error Error]) Any)
- io.run!
- write!
- (if (ffi.null? error)
- {try.#Success []}
- {try.#Failure (Error::toString error)})))
-
- (def: (value_callback write!)
- (All (_ a) (-> (async.Resolver (Try a)) ffi.Function))
- (<| (ffi.function (_ [error Error datum Any]) Any)
- io.run!
- write!
- (if (ffi.null? error)
- {try.#Success (:expected datum)}
- {try.#Failure (Error::toString error)})))
-
- (ffi.import: JsPath
- "[1]::[0]"
- (sep ffi.String))
-
- (def: .public default
- (Maybe (System Async))
- (do maybe.monad
- [node_fs (node_js.require "fs")
- node_path (node_js.require "path")
- .let [node_fs (:as ..Fs node_fs)
- js_separator (if ffi.on_node_js?
- (JsPath::sep (:as ..JsPath node_path))
- "/")]]
- (in (: (System Async)
- (`` (implementation
- (def: separator
- js_separator)
-
- (~~ (template [<name> <method>]
- [(def: (<name> path)
- (do async.monad
- [?stats (with_async write! (Try Stats)
- (Fs::stat path (..value_callback write!)
- node_fs))]
- (in (case ?stats
- {try.#Success stats}
- (<method> stats)
-
- {try.#Failure _}
- false))))]
-
- [file? Stats::isFile]
- [directory? Stats::isDirectory]
- ))
-
- (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!)
- node_fs))]
- (case outcome
- {try.#Success _}
- (in (exception.except ..cannot_make_directory [path]))
-
- {try.#Failure _}
- (with_async write! (Try Any)
- (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))]
- (|> subs
- (array.list {.#None})
- (list#each (|>> (format path js_separator)))
- (monad.each ! (function (_ sub)
- (# ! each (|>> <method> [sub])
- (with_async write! (Try Stats)
- (Fs::stat sub (..value_callback write!) node_fs)))))
- (# ! each (|>> (list.only product.right)
- (list#each product.left))))))]
-
- [directory_files Stats::isFile]
- [sub_directories Stats::isDirectory]
- ))
-
- (def: (file_size path)
- (do (try.with async.monad)
- [stats (with_async write! (Try Stats)
- (Fs::stat path (..value_callback write!)
- node_fs))]
- (in (|> stats
- Stats::size
- f.nat))))
-
- (def: (last_modified path)
- (do (try.with async.monad)
- [stats (with_async write! (Try Stats)
- (Fs::stat path (..value_callback write!)
- node_fs))]
- (in (|> stats
- Stats::mtimeMs
- f.int
- duration.of_millis
- instant.absolute))))
-
- (def: (can_execute? path)
- (# async.monad each
- (|>> (case> {try.#Success _}
- true
-
- {try.#Failure _}
- false)
- {try.#Success})
+ (for @.old (as_is <for_jvm>)
+ @.jvm (as_is <for_jvm>)
+
+ @.js
+ (as_is (ffi.import: Buffer
+ "[1]::[0]"
+ ("static" from [Binary] ..Buffer))
+
+ (ffi.import: FileDescriptor
+ "[1]::[0]")
+
+ (ffi.import: Stats
+ "[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))
+
+ (ffi.import: Error
+ "[1]::[0]"
+ (toString [] ffi.String))
+
+ (template: (with_async <write> <type> <body>)
+ [(template.with_locals [<read>]
+ (let [[<read> <write>] (: [(Async <type>) (async.Resolver <type>)]
+ (async.async []))]
+ (exec
+ <body>
+ <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))
+
+ (def: (any_callback write!)
+ (-> (async.Resolver (Try Any)) ffi.Function)
+ (<| (ffi.function (_ [error Error]) Any)
+ io.run!
+ write!
+ (if (ffi.null? error)
+ {try.#Success []}
+ {try.#Failure (Error::toString error)})))
+
+ (def: (value_callback write!)
+ (All (_ a) (-> (async.Resolver (Try a)) ffi.Function))
+ (<| (ffi.function (_ [error Error datum Any]) Any)
+ io.run!
+ write!
+ (if (ffi.null? error)
+ {try.#Success (:expected datum)}
+ {try.#Failure (Error::toString error)})))
+
+ (ffi.import: JsPath
+ "[1]::[0]"
+ (sep ffi.String))
+
+ (def: .public default
+ (Maybe (System Async))
+ (do maybe.monad
+ [node_fs (node_js.require "fs")
+ node_path (node_js.require "path")
+ .let [node_fs (:as ..Fs node_fs)
+ js_separator (if ffi.on_node_js?
+ (JsPath::sep (:as ..JsPath node_path))
+ "/")]]
+ (in (: (System Async)
+ (`` (implementation
+ (def: separator
+ js_separator)
+
+ (~~ (template [<name> <method>]
+ [(def: (<name> path)
+ (do async.monad
+ [?stats (with_async write! (Try Stats)
+ (Fs::stat path (..value_callback write!)
+ node_fs))]
+ (in (case ?stats
+ {try.#Success stats}
+ (<method> stats)
+
+ {try.#Failure _}
+ false))))]
+
+ [file? Stats::isFile]
+ [directory? Stats::isDirectory]
+ ))
+
+ (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!)
+ node_fs))]
+ (case outcome
+ {try.#Success _}
+ (in (exception.except ..cannot_make_directory [path]))
+
+ {try.#Failure _}
(with_async write! (Try Any)
- (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!)
- 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::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))]
+ (|> subs
+ (array.list {.#None})
+ (list#each (|>> (format path js_separator)))
+ (monad.each ! (function (_ sub)
+ (# ! each (|>> <method> [sub])
+ (with_async write! (Try Stats)
+ (Fs::stat sub (..value_callback write!) node_fs)))))
+ (# ! each (|>> (list.only product.right)
+ (list#each product.left))))))]
+
+ [directory_files Stats::isFile]
+ [sub_directories Stats::isDirectory]
+ ))
+
+ (def: (file_size path)
+ (do (try.with async.monad)
+ [stats (with_async write! (Try Stats)
+ (Fs::stat path (..value_callback write!)
+ node_fs))]
+ (in (|> stats
+ Stats::size
+ f.nat))))
+
+ (def: (last_modified path)
+ (do (try.with async.monad)
+ [stats (with_async write! (Try Stats)
+ (Fs::stat path (..value_callback write!)
+ node_fs))]
+ (in (|> stats
+ Stats::mtimeMs
+ f.int
+ duration.of_millis
+ instant.absolute))))
+
+ (def: (can_execute? path)
+ (# async.monad each
+ (|>> (case> {try.#Success _}
+ true
+
+ {try.#Failure _}
+ false)
+ {try.#Success})
(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)))))
-
- (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::access path
+ (|> node_fs Fs::constants FsConstants::X_OK)
+ (..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!)
- node_fs)))]
-
- [write Fs::writeFile]
- [append Fs::appendFile]
- ))
-
- (def: (move destination origin)
- (with_async write! (Try Any)
- (Fs::rename origin destination (..any_callback write!)
- node_fs))))))))))
-
- @.python
- (as_is (type: (Tuple/2 left right)
- (Primitive "python_tuple[2]" [left right]))
-
- (ffi.import: PyFile
- "[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)))
-
- (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))
-
- (def: python_separator
- (os/path::sep))
-
- (`` (implementation: .public default
- (System IO)
-
- (def: separator
- ..python_separator)
-
- (~~ (template [<name> <method>]
- [(def: <name>
- (|>> <method>
- (io#each (|>> (try.else false)))))]
-
- [file? os/path::isfile]
- [directory? os/path::isdir]
- ))
-
- (def: make_directory
- os::mkdir)
-
- (~~ (template [<name> <method>]
- [(def: (<name> path)
- (let [! (try.with io.monad)]
- (|> path
- os::listdir
- (# ! each (|>> (array.list {.#None})
- (list#each (|>> (format path ..python_separator)))
- (monad.each ! (function (_ sub)
- (# ! each (|>> [sub]) (<method> sub))))
- (# ! each (|>> (list.only product.right)
- (list#each product.left)))))
- (# ! conjoint))))]
-
- [directory_files os/path::isfile]
- [sub_directories os/path::isdir]
- ))
-
- (def: file_size
- (|>> os/path::getsize
- (# (try.with io.monad) each (|>> .nat))))
-
- (def: last_modified
- (|>> os/path::getmtime
- (# (try.with io.monad) each (|>> f.int
- (i.* +1,000)
- duration.of_millis
- instant.absolute))))
-
- (def: (can_execute? path)
- (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)]
- (in data)))
-
- (def: (delete path)
- (do (try.with io.monad)
- [? (os/path::isfile path)]
- (if ?
- (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]))))
-
- (~~ (template [<name> <mode>]
- [(def: (<name> data path)
- (do (try.with io.monad)
- [file (..open path <mode>)
- _ (PyFile::write data file)]
- (PyFile::close file)))]
-
- [write "w+b"]
- [append "ab"]
- ))
-
- (def: (move destination origin)
- (os::rename origin destination))
- )))
-
- @.ruby
- (as_is (ffi.import: Time
- "[1]::[0]"
- ("static" at [Frac] Time)
- (to_f [] Frac))
-
- (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" 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
- (..RubyFile::SEPARATOR))
-
- (`` (implementation: .public default
- (System IO)
-
- (def: separator
- ..ruby_separator)
-
- (~~ (template [<name> <test>]
- [(def: <name>
- (|>> <test>
- (io#each (|>> (try.else false)))))]
-
- [file? RubyFile::file?]
- [directory? RubyFile::directory?]
- ))
-
- (def: make_directory
- FileUtils::mkdir)
-
- (~~ (template [<name> <test>]
- [(def: (<name> path)
- (do [! (try.with io.monad)]
- [self (Dir::open path)
- children (Dir::children self)
- output (loop [input (|> children
- (array.list {.#None})
- (list#each (|>> (format path ..ruby_separator))))
- output (: (List ..Path)
- (list))]
- (case input
- {.#End}
- (in output)
-
- {.#Item head tail}
- (do !
- [verdict (<test> head)]
- (again tail (if verdict
- {.#Item head output}
- output)))))
- _ (Dir::close self)]
- (in output)))]
-
- [directory_files RubyFile::file?]
- [sub_directories RubyFile::directory?]
- ))
-
- (~~ (template [<name> <pipeline>]
- [(def: <name>
- (let [! (try.with io.monad)]
- (|>> RubyFile::stat
- (# ! each (`` (|>> (~~ (template.spliced <pipeline>))))))))]
-
- [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? [Stat::executable?]]
- ))
-
- (def: (read path)
- (do (try.with io.monad)
- [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)
- (FileUtils::rmdir path))))
-
- (def: (modify moment path)
- (let [moment (|> moment
- instant.relative
- duration.millis
- i.frac
- (f./ +1,000.0)
- 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)]
- (in [])))]
-
- ["wb" write]
- ["ab" append]
- ))
-
- (def: (move destination origin)
- (do (try.with io.monad)
- [_ (FileUtils::move origin destination)]
- (in [])))
- )))
-
- ... @.php
- ... (as_is (ffi.import: (FILE_APPEND Int))
- ... ... https://www.php.net/manual/en/dir.constants.php
- ... (ffi.import: (DIRECTORY_SEPARATOR ffi.String))
- ... ... https://www.php.net/manual/en/function.pack.php
- ... ... https://www.php.net/manual/en/function.unpack.php
- ... (ffi.import: (unpack [ffi.String ffi.String] Binary))
- ... ... https://www.php.net/manual/en/ref.filesystem.php
- ... ... https://www.php.net/manual/en/function.file-get-contents.php
- ... (ffi.import: (file_get_contents [Path] "io" "try" ffi.String))
- ... ... https://www.php.net/manual/en/function.file-put-contents.php
- ... (ffi.import: (file_put_contents [Path ffi.String Int] "io" "try" ffi.Integer))
- ... (ffi.import: (filemtime [Path] "io" "try" ffi.Integer))
- ... (ffi.import: (filesize [Path] "io" "try" ffi.Integer))
- ... (ffi.import: (is_executable [Path] "io" "try" ffi.Boolean))
- ... (ffi.import: (touch [Path ffi.Integer] "io" "try" ffi.Boolean))
- ... (ffi.import: (rename [Path Path] "io" "try" ffi.Boolean))
- ... (ffi.import: (unlink [Path] "io" "try" ffi.Boolean))
-
- ... ... https://www.php.net/manual/en/function.rmdir.php
- ... (ffi.import: (rmdir [Path] "io" "try" ffi.Boolean))
- ... ... https://www.php.net/manual/en/function.scandir.php
- ... (ffi.import: (scandir [Path] "io" "try" (Array Path)))
- ... ... https://www.php.net/manual/en/function.is-file.php
- ... (ffi.import: (is_file [Path] "io" "try" ffi.Boolean))
- ... ... https://www.php.net/manual/en/function.is-dir.php
- ... (ffi.import: (is_dir [Path] "io" "try" ffi.Boolean))
- ... ... https://www.php.net/manual/en/function.mkdir.php
- ... (ffi.import: (mkdir [Path] "io" "try" ffi.Boolean))
-
- ... (def: byte_array_format "C*")
- ... (def: default_separator (..DIRECTORY_SEPARATOR))
-
- ... (template [<name>]
- ... [(exception: .public (<name> [file Path])
- ... (exception.report
- ... ["Path" file]))]
-
- ... [cannot_write_to_file]
- ... )
-
- ... (`` (implementation: (file path)
- ... (-> Path (File IO))
-
- ... (~~ (template [<name> <mode>]
- ... [(def: (<name> data)
- ... (do [! (try.with io.monad)]
- ... [outcome (..file_put_contents [path ("php pack" ..byte_array_format data) <mode>])]
- ... (if (bit#= false (:as Bit outcome))
- ... (# io.monad in (exception.except ..cannot_write_to_file [path]))
- ... (in []))))]
-
- ... [over_write +0]
- ... [append (..FILE_APPEND)]
- ... ))
-
- ... (def: (content _)
- ... (do [! (try.with io.monad)]
- ... [data (..file_get_contents [path])]
- ... (if (bit#= false (:as Bit data))
- ... (# io.monad in (exception.except ..cannot_find_file [path]))
- ... (in (..unpack [..byte_array_format data])))))
-
- ... (def: path
- ... path)
-
- ... (~~ (template [<name> <ffi> <pipeline>]
- ... [(def: (<name> _)
- ... (do [! (try.with io.monad)]
- ... [value (<ffi> [path])]
- ... (if (bit#= false (:as Bit value))
- ... (# io.monad in (exception.except ..cannot_find_file [path]))
- ... (in (`` (|> value (~~ (template.spliced <pipeline>))))))))]
-
- ... [size ..filesize [.nat]]
- ... [last_modified ..filemtime [(i.* +1,000) duration.of_millis instant.absolute]]
- ... ))
-
- ... (def: (can_execute? _)
- ... (..is_executable [path]))
-
- ... (def: (modify moment)
- ... (do [! (try.with io.monad)]
- ... [verdict (..touch [path (|> moment instant.relative duration.millis (i./ +1,000))])]
- ... (if (bit#= false (:as Bit verdict))
- ... (# io.monad in (exception.except ..cannot_find_file [path]))
- ... (in []))))
-
- ... (def: (move destination)
- ... (do [! (try.with io.monad)]
- ... [verdict (..rename [path destination])]
- ... (if (bit#= false (:as Bit verdict))
- ... (# io.monad in (exception.except ..cannot_find_file [path]))
- ... (in (file destination)))))
-
- ... (def: (delete _)
- ... (do (try.with io.monad)
- ... [verdict (..unlink [path])]
- ... (if (bit#= false (:as Bit verdict))
- ... (# io.monad in (exception.except ..cannot_find_file [path]))
- ... (in []))))
- ... ))
-
- ... (`` (implementation: (directory path)
- ... (-> Path (Directory IO))
-
- ... (def: scope
- ... path)
-
- ... (~~ (template [<name> <test> <constructor> <capability>]
- ... [(def: (<name> _)
- ... (do [! (try.with io.monad)]
- ... [children (..scandir [path])]
- ... (loop [input (|> children
- ... (array.list {.#None})
- ... (list.only (function (_ child)
- ... (not (or (text#= "." child)
- ... (text#= ".." child))))))
- ... output (: (List (<capability> IO))
- ... (list))]
- ... (case input
- ... {.#End}
- ... (in output)
-
- ... {.#Item head tail}
- ... (do !
- ... [verdict (<test> head)]
- ... (if verdict
- ... (again tail {.#Item (<constructor> head) output})
- ... (again tail output)))))))]
-
- ... [files ..is_file ..file File]
- ... [directories ..is_dir directory Directory]
- ... ))
-
- ... (def: (discard _)
- ... (do (try.with io.monad)
- ... [verdict (..rmdir [path])]
- ... (if (bit#= false (:as Bit verdict))
- ... (# io.monad in (exception.except ..cannot_find_directory [path]))
- ... (in []))))
- ... ))
-
- ... (`` (implementation: .public default
- ... (System IO)
-
- ... (~~ (template [<name> <test> <constructor> <exception>]
- ... [(def: (<name> path)
- ... (do [! (try.with io.monad)]
- ... [verdict (<test> path)]
- ... (# io.monad in
- ... (if verdict
- ... {try.#Success (<constructor> path)}
- ... (exception.except <exception> [path])))))]
-
- ... [file ..is_file ..file ..cannot_find_file]
- ... [directory ..is_dir ..directory ..cannot_find_directory]
- ... ))
-
- ... (def: (make_file path)
- ... (do [! (try.with io.monad)]
- ... [verdict (..touch [path (|> instant.now io.run! instant.relative duration.millis (i./ +1,000))])]
- ... (# io.monad in
- ... (if verdict
- ... {try.#Success (..file path)}
- ... (exception.except ..cannot_make_file [path])))))
-
- ... (def: (make_directory path)
- ... (do [! (try.with io.monad)]
- ... [verdict (..mkdir path)]
- ... (# io.monad in
- ... (if verdict
- ... {try.#Success (..directory path)}
- ... (exception.except ..cannot_make_directory [path])))))
-
- ... (def: separator
- ... ..default_separator)
- ... ))
- ... )
- ]
+ (def: (read path)
+ (with_async write! (Try Binary)
+ (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))]
+ (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)))))
+
+ (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!)
+ node_fs))))
+
+ (~~ (template [<name> <method>]
+ [(def: (<name> data path)
+ (with_async write! (Try Any)
+ (<method> path (Buffer::from data) (..any_callback write!)
+ node_fs)))]
+
+ [write Fs::writeFile]
+ [append Fs::appendFile]
+ ))
+
+ (def: (move destination origin)
+ (with_async write! (Try Any)
+ (Fs::rename origin destination (..any_callback write!)
+ node_fs))))))))))
+
+ @.python
+ (as_is (type: (Tuple/2 left right)
+ (Primitive "python_tuple[2]" [left right]))
+
+ (ffi.import: PyFile
+ "[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)))
+
+ (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))
+
+ (def: python_separator
+ (os/path::sep))
+
+ (`` (implementation: .public default
+ (System IO)
+
+ (def: separator
+ ..python_separator)
+
+ (~~ (template [<name> <method>]
+ [(def: <name>
+ (|>> <method>
+ (io#each (|>> (try.else false)))))]
+
+ [file? os/path::isfile]
+ [directory? os/path::isdir]
+ ))
+
+ (def: make_directory
+ os::mkdir)
+
+ (~~ (template [<name> <method>]
+ [(def: (<name> path)
+ (let [! (try.with io.monad)]
+ (|> path
+ os::listdir
+ (# ! each (|>> (array.list {.#None})
+ (list#each (|>> (format path ..python_separator)))
+ (monad.each ! (function (_ sub)
+ (# ! each (|>> [sub]) (<method> sub))))
+ (# ! each (|>> (list.only product.right)
+ (list#each product.left)))))
+ (# ! conjoint))))]
+
+ [directory_files os/path::isfile]
+ [sub_directories os/path::isdir]
+ ))
+
+ (def: file_size
+ (|>> os/path::getsize
+ (# (try.with io.monad) each (|>> .nat))))
+
+ (def: last_modified
+ (|>> os/path::getmtime
+ (# (try.with io.monad) each (|>> f.int
+ (i.* +1,000)
+ duration.of_millis
+ instant.absolute))))
+
+ (def: (can_execute? path)
+ (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)]
+ (in data)))
+
+ (def: (delete path)
+ (do (try.with io.monad)
+ [? (os/path::isfile path)]
+ (if ?
+ (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]))))
+
+ (~~ (template [<name> <mode>]
+ [(def: (<name> data path)
+ (do (try.with io.monad)
+ [file (..open path <mode>)
+ _ (PyFile::write data file)]
+ (PyFile::close file)))]
+
+ [write "w+b"]
+ [append "ab"]
+ ))
+
+ (def: (move destination origin)
+ (os::rename origin destination))
+ )))
+
+ @.ruby
+ (as_is (ffi.import: Time
+ "[1]::[0]"
+ ("static" at [Frac] Time)
+ (to_f [] Frac))
+
+ (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" 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
+ (..RubyFile::SEPARATOR))
+
+ (`` (implementation: .public default
+ (System IO)
+
+ (def: separator
+ ..ruby_separator)
+
+ (~~ (template [<name> <test>]
+ [(def: <name>
+ (|>> <test>
+ (io#each (|>> (try.else false)))))]
+
+ [file? RubyFile::file?]
+ [directory? RubyFile::directory?]
+ ))
+
+ (def: make_directory
+ FileUtils::mkdir)
+
+ (~~ (template [<name> <test>]
+ [(def: (<name> path)
+ (do [! (try.with io.monad)]
+ [self (Dir::open path)
+ children (Dir::children self)
+ output (loop [input (|> children
+ (array.list {.#None})
+ (list#each (|>> (format path ..ruby_separator))))
+ output (: (List ..Path)
+ (list))]
+ (case input
+ {.#End}
+ (in output)
+
+ {.#Item head tail}
+ (do !
+ [verdict (<test> head)]
+ (again tail (if verdict
+ {.#Item head output}
+ output)))))
+ _ (Dir::close self)]
+ (in output)))]
+
+ [directory_files RubyFile::file?]
+ [sub_directories RubyFile::directory?]
+ ))
+
+ (~~ (template [<name> <pipeline>]
+ [(def: <name>
+ (let [! (try.with io.monad)]
+ (|>> RubyFile::stat
+ (# ! each (`` (|>> (~~ (template.spliced <pipeline>))))))))]
+
+ [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? [Stat::executable?]]
+ ))
+
+ (def: (read path)
+ (do (try.with io.monad)
+ [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)
+ (FileUtils::rmdir path))))
+
+ (def: (modify moment path)
+ (let [moment (|> moment
+ instant.relative
+ duration.millis
+ i.frac
+ (f./ +1,000.0)
+ 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)]
+ (in [])))]
+
+ ["wb" write]
+ ["ab" append]
+ ))
+
+ (def: (move destination origin)
+ (do (try.with io.monad)
+ [_ (FileUtils::move origin destination)]
+ (in [])))
+ )))
+
+ ... @.php
+ ... (as_is (ffi.import: (FILE_APPEND Int))
+ ... ... https://www.php.net/manual/en/dir.constants.php
+ ... (ffi.import: (DIRECTORY_SEPARATOR ffi.String))
+ ... ... https://www.php.net/manual/en/function.pack.php
+ ... ... https://www.php.net/manual/en/function.unpack.php
+ ... (ffi.import: (unpack [ffi.String ffi.String] Binary))
+ ... ... https://www.php.net/manual/en/ref.filesystem.php
+ ... ... https://www.php.net/manual/en/function.file-get-contents.php
+ ... (ffi.import: (file_get_contents [Path] "io" "try" ffi.String))
+ ... ... https://www.php.net/manual/en/function.file-put-contents.php
+ ... (ffi.import: (file_put_contents [Path ffi.String Int] "io" "try" ffi.Integer))
+ ... (ffi.import: (filemtime [Path] "io" "try" ffi.Integer))
+ ... (ffi.import: (filesize [Path] "io" "try" ffi.Integer))
+ ... (ffi.import: (is_executable [Path] "io" "try" ffi.Boolean))
+ ... (ffi.import: (touch [Path ffi.Integer] "io" "try" ffi.Boolean))
+ ... (ffi.import: (rename [Path Path] "io" "try" ffi.Boolean))
+ ... (ffi.import: (unlink [Path] "io" "try" ffi.Boolean))
+
+ ... ... https://www.php.net/manual/en/function.rmdir.php
+ ... (ffi.import: (rmdir [Path] "io" "try" ffi.Boolean))
+ ... ... https://www.php.net/manual/en/function.scandir.php
+ ... (ffi.import: (scandir [Path] "io" "try" (Array Path)))
+ ... ... https://www.php.net/manual/en/function.is-file.php
+ ... (ffi.import: (is_file [Path] "io" "try" ffi.Boolean))
+ ... ... https://www.php.net/manual/en/function.is-dir.php
+ ... (ffi.import: (is_dir [Path] "io" "try" ffi.Boolean))
+ ... ... https://www.php.net/manual/en/function.mkdir.php
+ ... (ffi.import: (mkdir [Path] "io" "try" ffi.Boolean))
+
+ ... (def: byte_array_format "C*")
+ ... (def: default_separator (..DIRECTORY_SEPARATOR))
+
+ ... (template [<name>]
+ ... [(exception: .public (<name> [file Path])
+ ... (exception.report
+ ... ["Path" file]))]
+
+ ... [cannot_write_to_file]
+ ... )
+
+ ... (`` (implementation: (file path)
+ ... (-> Path (File IO))
+
+ ... (~~ (template [<name> <mode>]
+ ... [(def: (<name> data)
+ ... (do [! (try.with io.monad)]
+ ... [outcome (..file_put_contents [path ("php pack" ..byte_array_format data) <mode>])]
+ ... (if (bit#= false (:as Bit outcome))
+ ... (# io.monad in (exception.except ..cannot_write_to_file [path]))
+ ... (in []))))]
+
+ ... [over_write +0]
+ ... [append (..FILE_APPEND)]
+ ... ))
+
+ ... (def: (content _)
+ ... (do [! (try.with io.monad)]
+ ... [data (..file_get_contents [path])]
+ ... (if (bit#= false (:as Bit data))
+ ... (# io.monad in (exception.except ..cannot_find_file [path]))
+ ... (in (..unpack [..byte_array_format data])))))
+
+ ... (def: path
+ ... path)
+
+ ... (~~ (template [<name> <ffi> <pipeline>]
+ ... [(def: (<name> _)
+ ... (do [! (try.with io.monad)]
+ ... [value (<ffi> [path])]
+ ... (if (bit#= false (:as Bit value))
+ ... (# io.monad in (exception.except ..cannot_find_file [path]))
+ ... (in (`` (|> value (~~ (template.spliced <pipeline>))))))))]
+
+ ... [size ..filesize [.nat]]
+ ... [last_modified ..filemtime [(i.* +1,000) duration.of_millis instant.absolute]]
+ ... ))
+
+ ... (def: (can_execute? _)
+ ... (..is_executable [path]))
+
+ ... (def: (modify moment)
+ ... (do [! (try.with io.monad)]
+ ... [verdict (..touch [path (|> moment instant.relative duration.millis (i./ +1,000))])]
+ ... (if (bit#= false (:as Bit verdict))
+ ... (# io.monad in (exception.except ..cannot_find_file [path]))
+ ... (in []))))
+
+ ... (def: (move destination)
+ ... (do [! (try.with io.monad)]
+ ... [verdict (..rename [path destination])]
+ ... (if (bit#= false (:as Bit verdict))
+ ... (# io.monad in (exception.except ..cannot_find_file [path]))
+ ... (in (file destination)))))
+
+ ... (def: (delete _)
+ ... (do (try.with io.monad)
+ ... [verdict (..unlink [path])]
+ ... (if (bit#= false (:as Bit verdict))
+ ... (# io.monad in (exception.except ..cannot_find_file [path]))
+ ... (in []))))
+ ... ))
+
+ ... (`` (implementation: (directory path)
+ ... (-> Path (Directory IO))
+
+ ... (def: scope
+ ... path)
+
+ ... (~~ (template [<name> <test> <constructor> <capability>]
+ ... [(def: (<name> _)
+ ... (do [! (try.with io.monad)]
+ ... [children (..scandir [path])]
+ ... (loop [input (|> children
+ ... (array.list {.#None})
+ ... (list.only (function (_ child)
+ ... (not (or (text#= "." child)
+ ... (text#= ".." child))))))
+ ... output (: (List (<capability> IO))
+ ... (list))]
+ ... (case input
+ ... {.#End}
+ ... (in output)
+
+ ... {.#Item head tail}
+ ... (do !
+ ... [verdict (<test> head)]
+ ... (if verdict
+ ... (again tail {.#Item (<constructor> head) output})
+ ... (again tail output)))))))]
+
+ ... [files ..is_file ..file File]
+ ... [directories ..is_dir directory Directory]
+ ... ))
+
+ ... (def: (discard _)
+ ... (do (try.with io.monad)
+ ... [verdict (..rmdir [path])]
+ ... (if (bit#= false (:as Bit verdict))
+ ... (# io.monad in (exception.except ..cannot_find_directory [path]))
+ ... (in []))))
+ ... ))
+
+ ... (`` (implementation: .public default
+ ... (System IO)
+
+ ... (~~ (template [<name> <test> <constructor> <exception>]
+ ... [(def: (<name> path)
+ ... (do [! (try.with io.monad)]
+ ... [verdict (<test> path)]
+ ... (# io.monad in
+ ... (if verdict
+ ... {try.#Success (<constructor> path)}
+ ... (exception.except <exception> [path])))))]
+
+ ... [file ..is_file ..file ..cannot_find_file]
+ ... [directory ..is_dir ..directory ..cannot_find_directory]
+ ... ))
+
+ ... (def: (make_file path)
+ ... (do [! (try.with io.monad)]
+ ... [verdict (..touch [path (|> instant.now io.run! instant.relative duration.millis (i./ +1,000))])]
+ ... (# io.monad in
+ ... (if verdict
+ ... {try.#Success (..file path)}
+ ... (exception.except ..cannot_make_file [path])))))
+
+ ... (def: (make_directory path)
+ ... (do [! (try.with io.monad)]
+ ... [verdict (..mkdir path)]
+ ... (# io.monad in
+ ... (if verdict
+ ... {try.#Success (..directory path)}
+ ... (exception.except ..cannot_make_directory [path])))))
+
+ ... (def: separator
+ ... ..default_separator)
+ ... ))
+ ... )
+
(as_is)))
(def: .public (exists? monad fs path)
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index 5ad94c22e..a5828f116 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -457,6 +457,6 @@
(async.future (..default_poll watcher)))
)))))
)]
- (for [@.old (as_is <jvm>)
- @.jvm (as_is <jvm>)]
+ (for @.old (as_is <jvm>)
+ @.jvm (as_is <jvm>)
(as_is)))
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index 85e9c2cbd..9ce51d32a 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -215,8 +215,8 @@
(in [(.nat (ffi.of_int status))
[//.#headers headers
//.#body (..default_body input)]]))))))]
- (for [@.old (as_is <jvm>)
- @.jvm (as_is <jvm>)]
+ (for @.old (as_is <jvm>)
+ @.jvm (as_is <jvm>)
(as_is)))
(implementation: .public (async client)
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index cb3c96f19..c3870d14d 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -24,8 +24,8 @@
["[0]" dictionary {"+" Dictionary}]
["[0]" list ("[1]#[0]" functor)]]]
["[0]" ffi {"+" import:}
- (~~ (.for ["JavaScript" (~~ (.as_is ["[0]" node_js]))
- "{old}" (~~ (.as_is ["node_js" //math]))]
+ (~~ (.for "JavaScript" (~~ (.as_is ["[0]" node_js]))
+ "{old}" (~~ (.as_is ["node_js" //math]))
(~~ (.as_is))))]
["[0]" macro
["[0]" template]]
@@ -144,144 +144,144 @@
(jvm##consume iterator)}
{.#End}))
)]
- (for [@.old (as_is <jvm>)
- @.jvm (as_is <jvm>)
- @.js (as_is (def: default_exit!
- (-> Exit (IO Nothing))
- (|>> %.int panic! io.io))
-
- (import: NodeJs_Process
- "[1]::[0]"
- (exit [ffi.Number] "io" Nothing)
- (cwd [] "io" Path))
-
- (def: (exit_node_js! code)
- (-> Exit (IO Nothing))
- (case (ffi.global ..NodeJs_Process [process])
- {.#Some process}
- (NodeJs_Process::exit (i.frac code) process)
-
- {.#None}
- (..default_exit! code)))
-
- (import: Browser_Window
+ (for @.old (as_is <jvm>)
+ @.jvm (as_is <jvm>)
+ @.js (as_is (def: default_exit!
+ (-> Exit (IO Nothing))
+ (|>> %.int panic! io.io))
+
+ (import: NodeJs_Process
+ "[1]::[0]"
+ (exit [ffi.Number] "io" Nothing)
+ (cwd [] "io" Path))
+
+ (def: (exit_node_js! code)
+ (-> Exit (IO Nothing))
+ (case (ffi.global ..NodeJs_Process [process])
+ {.#Some process}
+ (NodeJs_Process::exit (i.frac code) process)
+
+ {.#None}
+ (..default_exit! code)))
+
+ (import: Browser_Window
+ "[1]::[0]"
+ (close [] Nothing))
+
+ (import: Browser_Location
+ "[1]::[0]"
+ (reload [] Nothing))
+
+ (def: (exit_browser! code)
+ (-> Exit (IO Nothing))
+ (case [(ffi.global ..Browser_Window [window])
+ (ffi.global ..Browser_Location [location])]
+ [{.#Some window} {.#Some location}]
+ (exec
+ (Browser_Window::close window)
+ (Browser_Location::reload location)
+ (..default_exit! code))
+
+ [{.#Some window} {.#None}]
+ (exec
+ (Browser_Window::close window)
+ (..default_exit! code))
+
+ [{.#None} {.#Some location}]
+ (exec
+ (Browser_Location::reload location)
+ (..default_exit! code))
+
+ [{.#None} {.#None}]
+ (..default_exit! code)))
+
+ (import: Object
+ "[1]::[0]"
+ ("static" entries [Object] (Array (Array ffi.String))))
+
+ (import: NodeJs_OS
+ "[1]::[0]"
+ (homedir [] "io" Path)))
+ @.python (as_is (import: os
+ "[1]::[0]"
+ ("static" getcwd [] "io" ffi.String)
+ ("static" _exit [ffi.Integer] "io" Nothing))
+
+ (import: os/path
+ "[1]::[0]"
+ ("static" expanduser [ffi.String] "io" ffi.String))
+
+ (import: os/environ
+ "[1]::[0]"
+ ("static" keys [] "io" (Array ffi.String))
+ ("static" get [ffi.String] "io" "?" ffi.String)))
+ @.lua (as_is (ffi.import: LuaFile
"[1]::[0]"
- (close [] Nothing))
+ (read [ffi.String] "io" "?" ffi.String)
+ (close [] "io" ffi.Boolean))
+
+ (ffi.import: (io/popen [ffi.String] "io" "try" "?" LuaFile))
+ (ffi.import: (os/getenv [ffi.String] "io" "?" ffi.String))
+ (ffi.import: (os/exit [ffi.Integer] "io" Nothing))
+
+ (def: (run_command default command)
+ (-> Text Text (IO Text))
+ (do [! io.monad]
+ [outcome (io/popen [command])]
+ (case outcome
+ {try.#Success outcome}
+ (case outcome
+ {.#Some file}
+ (do !
+ [?output (LuaFile::read "*l" file)
+ _ (LuaFile::close file)]
+ (in (maybe.else default ?output)))
+
+ {.#None}
+ (in default))
+
+ {try.#Failure _}
+ (in default)))))
+ @.ruby (as_is (ffi.import: Env
+ "[1]::[0]"
+ ("static" keys [] (Array Text))
+ ("static" fetch [Text] "io" "?" Text))
- (import: Browser_Location
- "[1]::[0]"
- (reload [] Nothing))
-
- (def: (exit_browser! code)
- (-> Exit (IO Nothing))
- (case [(ffi.global ..Browser_Window [window])
- (ffi.global ..Browser_Location [location])]
- [{.#Some window} {.#Some location}]
- (exec
- (Browser_Window::close window)
- (Browser_Location::reload location)
- (..default_exit! code))
-
- [{.#Some window} {.#None}]
- (exec
- (Browser_Window::close window)
- (..default_exit! code))
-
- [{.#None} {.#Some location}]
- (exec
- (Browser_Location::reload location)
- (..default_exit! code))
-
- [{.#None} {.#None}]
- (..default_exit! code)))
-
- (import: Object
- "[1]::[0]"
- ("static" entries [Object] (Array (Array ffi.String))))
+ (ffi.import: "fileutils" FileUtils
+ "[1]::[0]"
+ ("static" pwd Path))
+
+ (ffi.import: Dir
+ "[1]::[0]"
+ ("static" home Path))
- (import: NodeJs_OS
- "[1]::[0]"
- (homedir [] "io" Path)))
- @.python (as_is (import: os
- "[1]::[0]"
- ("static" getcwd [] "io" ffi.String)
- ("static" _exit [ffi.Integer] "io" Nothing))
-
- (import: os/path
- "[1]::[0]"
- ("static" expanduser [ffi.String] "io" ffi.String))
-
- (import: os/environ
- "[1]::[0]"
- ("static" keys [] "io" (Array ffi.String))
- ("static" get [ffi.String] "io" "?" ffi.String)))
- @.lua (as_is (ffi.import: LuaFile
+ (ffi.import: Kernel
"[1]::[0]"
- (read [ffi.String] "io" "?" ffi.String)
- (close [] "io" ffi.Boolean))
-
- (ffi.import: (io/popen [ffi.String] "io" "try" "?" LuaFile))
- (ffi.import: (os/getenv [ffi.String] "io" "?" ffi.String))
- (ffi.import: (os/exit [ffi.Integer] "io" Nothing))
-
- (def: (run_command default command)
- (-> Text Text (IO Text))
- (do [! io.monad]
- [outcome (io/popen [command])]
- (case outcome
- {try.#Success outcome}
- (case outcome
- {.#Some file}
- (do !
- [?output (LuaFile::read "*l" file)
- _ (LuaFile::close file)]
- (in (maybe.else default ?output)))
-
- {.#None}
- (in default))
-
- {try.#Failure _}
- (in default)))))
- @.ruby (as_is (ffi.import: Env
- "[1]::[0]"
- ("static" keys [] (Array Text))
- ("static" fetch [Text] "io" "?" Text))
-
- (ffi.import: "fileutils" FileUtils
- "[1]::[0]"
- ("static" pwd Path))
-
- (ffi.import: Dir
- "[1]::[0]"
- ("static" home Path))
-
- (ffi.import: Kernel
- "[1]::[0]"
- ("static" exit [Int] "io" Nothing)))
-
- ... @.php
- ... (as_is (ffi.import: (exit [Int] "io" Nothing))
- ... ... https://www.php.net/manual/en/function.exit.php
- ... (ffi.import: (getcwd [] "io" ffi.String))
- ... ... https://www.php.net/manual/en/function.getcwd.php
- ... (ffi.import: (getenv "as" getenv/1 [ffi.String] "io" ffi.String))
- ... (ffi.import: (getenv "as" getenv/0 [] "io" (Array ffi.String)))
- ... ... https://www.php.net/manual/en/function.getenv.php
- ... ... https://www.php.net/manual/en/function.array-keys.php
- ... (ffi.import: (array_keys [(Array ffi.String)] (Array ffi.String)))
- ... )
-
- ... @.scheme
- ... (as_is (ffi.import: (exit [Int] "io" Nothing))
- ... ... https://srfi.schemers.org/srfi-98/srfi-98.html
- ... (abstract: Pair Any)
- ... (abstract: PList Any)
- ... (ffi.import: (get-environment-variables [] "io" PList))
- ... (ffi.import: (car [Pair] Text))
- ... (ffi.import: (cdr [Pair] Text))
- ... (ffi.import: (car "as" head [PList] Pair))
- ... (ffi.import: (cdr "as" tail [PList] PList)))
- ]
+ ("static" exit [Int] "io" Nothing)))
+
+ ... @.php
+ ... (as_is (ffi.import: (exit [Int] "io" Nothing))
+ ... ... https://www.php.net/manual/en/function.exit.php
+ ... (ffi.import: (getcwd [] "io" ffi.String))
+ ... ... https://www.php.net/manual/en/function.getcwd.php
+ ... (ffi.import: (getenv "as" getenv/1 [ffi.String] "io" ffi.String))
+ ... (ffi.import: (getenv "as" getenv/0 [] "io" (Array ffi.String)))
+ ... ... https://www.php.net/manual/en/function.getenv.php
+ ... ... https://www.php.net/manual/en/function.array-keys.php
+ ... (ffi.import: (array_keys [(Array ffi.String)] (Array ffi.String)))
+ ... )
+
+ ... @.scheme
+ ... (as_is (ffi.import: (exit [Int] "io" Nothing))
+ ... ... https://srfi.schemers.org/srfi-98/srfi-98.html
+ ... (abstract: Pair Any)
+ ... (abstract: PList Any)
+ ... (ffi.import: (get-environment-variables [] "io" PList))
+ ... (ffi.import: (car [Pair] Text))
+ ... (ffi.import: (cdr [Pair] Text))
+ ... (ffi.import: (car "as" head [PList] Pair))
+ ... (ffi.import: (cdr "as" tail [PList] PList)))
+
(as_is)))
(implementation: .public default
@@ -294,40 +294,40 @@
..jvm##consume
(list#each (|>> ffi.of_string))
io.io)]
- (for [@.old <jvm>
- @.jvm <jvm>
- @.js (io.io (if ffi.on_node_js?
- (case (ffi.global Object [process env])
- {.#Some process/env}
- (|> (Object::entries [process/env])
- (array.list {.#None})
- (list#each (|>> (array.read! 0) maybe.trusted)))
-
- {.#None}
- (list))
- (list)))
- @.python (# io.monad each (array.list {.#None}) (os/environ::keys []))
- ... Lua offers no way to get all the environment variables available.
- @.lua (io.io (list))
- @.ruby (io.io (array.list {.#None} (Env::keys [])))
- ... @.php (do io.monad
- ... [environment (..getenv/0 [])]
- ... (in (|> environment
- ... ..array_keys
- ... (array.list {.#None})
- ... (list#each (function (_ variable)
- ... [variable ("php array read" (:as Nat variable) environment)]))
- ... (dictionary.of_list text.hash))))
- ... @.scheme (do io.monad
- ... [input (..get-environment-variables [])]
- ... (loop [input input
- ... output environment.empty]
- ... (if ("scheme object nil?" input)
- ... (in output)
- ... (let [entry (..head input)]
- ... (again (..tail input)
- ... (dictionary.has (..car entry) (..cdr entry) output))))))
- ])))
+ (for @.old <jvm>
+ @.jvm <jvm>
+ @.js (io.io (if ffi.on_node_js?
+ (case (ffi.global Object [process env])
+ {.#Some process/env}
+ (|> (Object::entries [process/env])
+ (array.list {.#None})
+ (list#each (|>> (array.read! 0) maybe.trusted)))
+
+ {.#None}
+ (list))
+ (list)))
+ @.python (# io.monad each (array.list {.#None}) (os/environ::keys []))
+ ... Lua offers no way to get all the environment variables available.
+ @.lua (io.io (list))
+ @.ruby (io.io (array.list {.#None} (Env::keys [])))
+ ... @.php (do io.monad
+ ... [environment (..getenv/0 [])]
+ ... (in (|> environment
+ ... ..array_keys
+ ... (array.list {.#None})
+ ... (list#each (function (_ variable)
+ ... [variable ("php array read" (:as Nat variable) environment)]))
+ ... (dictionary.of_list text.hash))))
+ ... @.scheme (do io.monad
+ ... [input (..get-environment-variables [])]
+ ... (loop [input input
+ ... output environment.empty]
+ ... (if ("scheme object nil?" input)
+ ... (in output)
+ ... (let [entry (..head input)]
+ ... (again (..tail input)
+ ... (dictionary.has (..car entry) (..cdr entry) output))))))
+ )))
(def: (variable name)
(template.let [(!fetch <method> <post>)
@@ -340,23 +340,23 @@
{.#None}
(exception.except ..unknown_environment_variable [name]))))]]
(with_expansions [<jvm> (!fetch (<| java/lang/System::resolveEnv ffi.as_string) ffi.of_string)]
- (for [@.old <jvm>
- @.jvm <jvm>
- @.js (io.io (if ffi.on_node_js?
- (case (do maybe.monad
- [process/env (ffi.global Object [process env])]
- (array.read! (:as Nat name)
- (:as (Array Text) process/env)))
- {.#Some value}
- {try.#Success value}
-
- {.#None}
- (exception.except ..unknown_environment_variable [name]))
- (exception.except ..unknown_environment_variable [name])))
- @.python (!fetch os/environ::get |>)
- @.lua (!fetch os/getenv |>)
- @.ruby (!fetch Env::fetch |>)
- ]))))
+ (for @.old <jvm>
+ @.jvm <jvm>
+ @.js (io.io (if ffi.on_node_js?
+ (case (do maybe.monad
+ [process/env (ffi.global Object [process env])]
+ (array.read! (:as Nat name)
+ (:as (Array Text) process/env)))
+ {.#Some value}
+ {try.#Success value}
+
+ {.#None}
+ (exception.except ..unknown_environment_variable [name]))
+ (exception.except ..unknown_environment_variable [name])))
+ @.python (!fetch os/environ::get |>)
+ @.lua (!fetch os/getenv |>)
+ @.ruby (!fetch Env::fetch |>)
+ ))))
(def: home
(io.run!
@@ -365,23 +365,23 @@
(maybe#each (|>> ffi.of_string))
(maybe.else "")
io.io)]
- (for [@.old <jvm>
- @.jvm <jvm>
- @.js (if ffi.on_node_js?
- (|> (node_js.require "os")
- maybe.trusted
- (:as NodeJs_OS)
- NodeJs_OS::homedir)
- <default>)
- @.python (os/path::expanduser "~")
- @.lua (..run_command "~" "echo ~")
- @.ruby (io.io (Dir::home))
- ... @.php (do io.monad
- ... [output (..getenv/1 ["HOME"])]
- ... (in (if (bit#= false (:as Bit output))
- ... "~"
- ... output)))
- ]
+ (for @.old <jvm>
+ @.jvm <jvm>
+ @.js (if ffi.on_node_js?
+ (|> (node_js.require "os")
+ maybe.trusted
+ (:as NodeJs_OS)
+ NodeJs_OS::homedir)
+ <default>)
+ @.python (os/path::expanduser "~")
+ @.lua (..run_command "~" "echo ~")
+ @.ruby (io.io (Dir::home))
+ ... @.php (do io.monad
+ ... [output (..getenv/1 ["HOME"])]
+ ... (in (if (bit#= false (:as Bit output))
+ ... "~"
+ ... output)))
+
... TODO: Replace dummy implementation.
<default>))))
@@ -392,30 +392,30 @@
(maybe#each (|>> ffi.of_string))
(maybe.else "")
io.io)]
- (for [@.old <jvm>
- @.jvm <jvm>
- @.js (if ffi.on_node_js?
- (case (ffi.global ..NodeJs_Process [process])
- {.#Some process}
- (NodeJs_Process::cwd process)
-
- {.#None}
- (io.io <default>))
- (io.io <default>))
- @.python (os::getcwd [])
- @.lua (do io.monad
- [.let [default <default>]
- on_windows (..run_command default "cd")]
- (if (same? default on_windows)
- (..run_command default "pwd")
- (in on_windows)))
- @.ruby (io.io (FileUtils::pwd))
- ... @.php (do io.monad
- ... [output (..getcwd [])]
- ... (in (if (bit#= false (:as Bit output))
- ... "."
- ... output)))
- ]
+ (for @.old <jvm>
+ @.jvm <jvm>
+ @.js (if ffi.on_node_js?
+ (case (ffi.global ..NodeJs_Process [process])
+ {.#Some process}
+ (NodeJs_Process::cwd process)
+
+ {.#None}
+ (io.io <default>))
+ (io.io <default>))
+ @.python (os::getcwd [])
+ @.lua (do io.monad
+ [.let [default <default>]
+ on_windows (..run_command default "cd")]
+ (if (same? default on_windows)
+ (..run_command default "pwd")
+ (in on_windows)))
+ @.ruby (io.io (FileUtils::pwd))
+ ... @.php (do io.monad
+ ... [output (..getcwd [])]
+ ... (in (if (bit#= false (:as Bit output))
+ ... "."
+ ... output)))
+
... TODO: Replace dummy implementation.
(io.io <default>)))))
@@ -423,19 +423,19 @@
(with_expansions [<jvm> (do io.monad
[_ (java/lang/System::exit (ffi.as_int code))]
(in (undefined)))]
- (for [@.old <jvm>
- @.jvm <jvm>
- @.js (cond ffi.on_node_js?
- (..exit_node_js! code)
-
- ffi.on_browser?
- (..exit_browser! code)
-
- ... else
- (..default_exit! code))
- @.python (os::_exit code)
- @.lua (os/exit code)
- @.ruby (Kernel::exit code)
- ... @.php (..exit [code])
- ... @.scheme (..exit [code])
- ]))))
+ (for @.old <jvm>
+ @.jvm <jvm>
+ @.js (cond ffi.on_node_js?
+ (..exit_node_js! code)
+
+ ffi.on_browser?
+ (..exit_browser! code)
+
+ ... else
+ (..default_exit! code))
+ @.python (os::_exit code)
+ @.lua (os/exit code)
+ @.ruby (Kernel::exit code)
+ ... @.php (..exit [code])
+ ... @.scheme (..exit [code])
+ ))))
diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux
index 22f63e05b..154fb6290 100644
--- a/stdlib/source/library/lux/world/shell.lux
+++ b/stdlib/source/library/lux/world/shell.lux
@@ -306,8 +306,8 @@
process (java/lang/ProcessBuilder::start builder)]
(..default_process process))))
)]
- (for [@.old (as_is <jvm>)
- @.jvm (as_is <jvm>)]
+ (for @.old (as_is <jvm>)
+ @.jvm (as_is <jvm>)
(as_is)))
(type: .public (Mock s)