diff options
author | Eduardo Julian | 2021-07-02 03:11:36 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-07-02 03:11:36 -0400 |
commit | 5cf4efa861075f8276f43a2516f5beacaf610b44 (patch) | |
tree | e21cf528d960c29d22cbc7e41180fa09e62f16d6 /stdlib/source/lux/tool | |
parent | 744ee69630de59ca3ba660b0aab6361cd17ce1b4 (diff) |
No longer employing the capabilities model on the lux/world/* modules.
Capabilities should be opt-in, but using them in the standard library makes them mandatory.
Diffstat (limited to 'stdlib/source/lux/tool')
6 files changed, 32 insertions, 44 deletions
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux index f429b0442..659dc0799 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux @@ -4,9 +4,7 @@ [monad (#+ do)]] [control ["." io (#+ IO)] - ["." try (#+ Try)] - [security - ["!" capability]]] + ["." try (#+ Try)]] [data [binary (#+ Binary)] [text @@ -23,7 +21,7 @@ [outcome (do (try.with @) [file (: (IO (Try (File IO))) (file.get-file io.monad file.default file-path))] - (!.use (\ file over-write) bytecode))] + (\ file over-write bytecode))] (wrap (case outcome (#try.Success definition) file-path diff --git a/stdlib/source/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/lux/tool/compiler/meta/io/archive.lux index e611f9f47..2006fcd79 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/archive.lux @@ -9,10 +9,8 @@ ["." exception (#+ exception:)] [concurrency ["." promise (#+ Promise) ("#\." monad)]] - [security - ["!" capability (#+ capability:)]] ["<>" parser - ["<b>" binary (#+ Parser)]]] + ["<.>" binary (#+ Parser)]]] [data [binary (#+ Binary)] ["." product] @@ -100,7 +98,7 @@ (do ! [_ (file.get_directory ! system (..unversioned_lux_archive system static)) _ (file.get_directory ! system (..versioned_lux_archive system static)) - outcome (!.use (\ system create_directory) module)] + outcome (\ system create_directory module)] (case outcome (#try.Success output) (wrap (#try.Success [])) @@ -116,7 +114,7 @@ [artifact (: (Promise (Try (File Promise))) (file.get_file promise.monad system (..artifact system static module_id artifact_id)))] - (!.use (\ artifact over_write) content))) + (\ artifact over_write content))) (def: #export (enable system static) (-> (file.System Promise) Static (Promise (Try Any))) @@ -138,7 +136,7 @@ (do (try.with promise.monad) [file (: (Promise (Try (File Promise))) (file.get_file promise.monad system (..general_descriptor system static)))] - (!.use (\ file over_write) (archive.export ///.version archive)))) + (\ file over_write (archive.export ///.version archive)))) (def: module_descriptor_file "module_descriptor") @@ -155,7 +153,7 @@ [file (: (Promise (Try (File Promise))) (file.get_file promise.monad system (..module_descriptor system static module_id)))] - (!.use (\ file over_write) content))) + (\ file over_write content))) (def: (read_module_descriptor system static module_id) (-> (file.System Promise) Static archive.ID (Promise (Try Binary))) @@ -163,7 +161,7 @@ [file (: (Promise (Try (File Promise))) (file.get_file promise.monad system (..module_descriptor system static module_id)))] - (!.use (\ file content) []))) + (\ file content []))) (def: parser (Parser [Descriptor (Document .Module)]) @@ -189,19 +187,19 @@ (def: (cached_artifacts system static module_id) (-> (file.System Promise) Static archive.ID (Promise (Try (Dictionary Text Binary)))) (do {! (try.with promise.monad)} - [module_dir (!.use (\ system directory) (..module system static module_id)) - cached_files (!.use (\ module_dir files) [])] + [module_dir (\ system directory (..module system static module_id)) + cached_files (\ module_dir files [])] (|> cached_files (list\map (function (_ file) - [(file.name system (!.use (\ file path) [])) - (!.use (\ file path) [])])) + [(file.name system (\ file path)) + (\ file path)])) (list.filter (|>> product.left (text\= ..module_descriptor_file) not)) (monad.map ! (function (_ [name path]) (do ! [file (: (Promise (Try (File Promise))) - (!.use (\ system file) path)) + (\ system file path)) data (: (Promise (Try Binary)) - (!.use (\ file content) []))] + (\ file content []))] (wrap [name data])))) (\ ! map (dictionary.from_list text.hash))))) @@ -338,12 +336,12 @@ (def: (purge! system static [module_name module_id]) (-> (file.System Promise) Static [Module archive.ID] (Promise (Try Any))) (do {! (try.with promise.monad)} - [cache (!.use (\ system directory) [(..module system static module_id)]) - artifacts (!.use (\ cache files) []) + [cache (\ system directory (..module system static module_id)) + artifacts (\ cache files []) _ (monad.map ! (function (_ artifact) - (!.use (\ artifact delete) [])) + (\ artifact delete [])) artifacts)] - (!.use (\ cache discard) []))) + (\ cache discard []))) (def: (valid_cache? expected actual) (-> Descriptor Input Bit) @@ -398,7 +396,7 @@ (monad.map ! (function (_ [module_name module_id]) (do ! [data (..read_module_descriptor system static module_id) - [descriptor document] (promise\wrap (<b>.run ..parser data))] + [descriptor document] (promise\wrap (<binary>.run ..parser data))] (if (text\= archive.runtime_module module_name) (wrap [true [module_name [module_id [descriptor document (: Output row.empty)]]]]) @@ -451,11 +449,11 @@ (-> (generation.Host expression directive) (file.System Promise) Static Import (List Context) (Promise (Try [Archive .Lux Bundles])))) (do promise.monad - [file (!.use (\ system file) (..general_descriptor system static))] + [file (\ system file (..general_descriptor system static))] (case file (#try.Success file) (do (try.with promise.monad) - [binary (!.use (\ file content) []) + [binary (\ file content []) archive (promise\wrap (archive.import ///.version binary))] (..load_every_reserved_module host_environment system static import contexts archive)) diff --git a/stdlib/source/lux/tool/compiler/meta/io/context.lux b/stdlib/source/lux/tool/compiler/meta/io/context.lux index 33f201571..788be9fed 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/context.lux @@ -7,8 +7,6 @@ [control ["." try (#+ Try)] ["." exception (#+ exception:)] - [security - ["!" capability]] [concurrency ["." promise (#+ Promise) ("#\." monad)]]] [data @@ -62,7 +60,7 @@ (#.Cons context contexts') (do promise.monad [#let [path (format (..path system context module) extension)] - file (!.use (\ system file) [path])] + file (\ system file [path])] (case file (#try.Success file) (wrap (#try.Success [path file])) @@ -84,13 +82,13 @@ (case outcome (#try.Success [path file]) (do (try.with !) - [data (!.use (\ file content) [])] + [data (\ file content [])] (wrap [path data])) (#try.Failure _) (do (try.with !) [[path file] (..find_source_file system importer contexts module ..lux_extension) - data (!.use (\ file content) [])] + data (\ file content [])] (wrap [path data]))))) (def: (find_library_source_file importer import partial_host_extension module) @@ -159,23 +157,23 @@ (def: (enumerate_context system context enumeration) (-> (file.System Promise) Context Enumeration (Promise (Try Enumeration))) (do {! (try.with promise.monad)} - [directory (!.use (\ system directory) [context])] + [directory (\ system directory context)] (loop [directory directory enumeration enumeration] (do ! - [files (!.use (\ directory files) []) + [files (\ directory files []) enumeration (monad.fold ! (function (_ file enumeration) - (let [path (!.use (\ file path) [])] + (let [path (\ file path)] (if (text.ends_with? ..lux_extension path) (do ! [path (promise\wrap (..clean_path system context path)) - source_code (!.use (\ file content) [])] + source_code (\ file content [])] (promise\wrap (dictionary.try_put path source_code enumeration))) (wrap enumeration)))) enumeration files) - directories (!.use (\ directory directories) [])] + directories (\ directory directories [])] (monad.fold ! recur enumeration directories))))) (def: Action diff --git a/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux index 1df76453c..86cec2ba1 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux @@ -7,9 +7,7 @@ [control ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)]] - [security - ["!" capability]]] + ["." promise (#+ Promise)]]] [data ["." binary (#+ Binary)] ["." text diff --git a/stdlib/source/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/lux/tool/compiler/meta/packager/scheme.lux index 64d7418eb..153aa79b5 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/scheme.lux @@ -4,9 +4,7 @@ [abstract ["." monad (#+ Monad do)]] [control - ["." try (#+ Try)] - [security - ["!" capability]]] + ["." try (#+ Try)]] [data [binary (#+ Binary)] ["." product] diff --git a/stdlib/source/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/lux/tool/compiler/meta/packager/script.lux index c23688a9e..5ddeac0d5 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/script.lux @@ -4,9 +4,7 @@ [abstract ["." monad (#+ Monad do)]] [control - ["." try (#+ Try)] - [security - ["!" capability]]] + ["." try (#+ Try)]] [data [binary (#+ Binary)] ["." product] |