From f9e33ae96aec4741385a576719786092c9e68043 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 4 Jun 2022 19:34:42 -0400 Subject: De-sigil-ification: # --- stdlib/source/specification/aedifex/repository.lux | 10 +-- stdlib/source/specification/compositor/common.lux | 4 +- .../specification/compositor/generation/case.lux | 8 +-- .../specification/compositor/generation/common.lux | 6 +- .../compositor/generation/function.lux | 2 +- .../compositor/generation/reference.lux | 2 +- .../compositor/generation/structure.lux | 6 +- stdlib/source/specification/lux/abstract/apply.lux | 10 +-- .../source/specification/lux/abstract/comonad.lux | 18 ++--- .../source/specification/lux/abstract/functor.lux | 10 +-- stdlib/source/specification/lux/abstract/monad.lux | 18 ++--- stdlib/source/specification/lux/world/console.lux | 10 +-- stdlib/source/specification/lux/world/file.lux | 82 +++++++++++----------- stdlib/source/specification/lux/world/program.lux | 4 +- stdlib/source/specification/lux/world/shell.lux | 14 ++-- 15 files changed, 102 insertions(+), 102 deletions(-) (limited to 'stdlib/source/specification') diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux index d35058c45..d71b95e75 100644 --- a/stdlib/source/specification/aedifex/repository.lux +++ b/stdlib/source/specification/aedifex/repository.lux @@ -30,17 +30,17 @@ (in (all _.and' (do async.monad [.let [good_uri (/remote.uri (the //artifact.#version valid_artifact) valid_artifact //artifact/extension.lux_library)] - good_upload! (# subject upload good_uri expected) - good_download! (# subject download good_uri) + good_upload! (at subject upload good_uri expected) + good_download! (at subject download good_uri) .let [bad_uri (/remote.uri (the //artifact.#version invalid_artifact) invalid_artifact //artifact/extension.lux_library)] - bad_upload! (# subject upload bad_uri expected) - bad_download! (# subject download bad_uri)] + bad_upload! (at subject upload bad_uri expected) + bad_download! (at subject download bad_uri)] (_.coverage' [/.Repository] (let [successfull_flow! (case [good_upload! good_download!] [{try.#Success _} {try.#Success actual}] - (# binary.equivalence = expected actual) + (at binary.equivalence = expected actual) _ false) diff --git a/stdlib/source/specification/compositor/common.lux b/stdlib/source/specification/compositor/common.lux index 5e197472b..947131032 100644 --- a/stdlib/source/specification/compositor/common.lux +++ b/stdlib/source/specification/compositor/common.lux @@ -40,7 +40,7 @@ (do phase.monad [_ runtime] (phase expressionS)))] - (# host evaluate! evaluation_name expressionG)))) + (at host evaluate! evaluation_name expressionG)))) (def: (definer (open "[0]") state) (Instancer Definer) @@ -54,7 +54,7 @@ [host_name host_value host_directive] (generation.define! lux_name expressionG) _ (generation.learn lux_name host_name)] (phase (synthesis.constant lux_name))))] - (# host evaluate! "definer" definitionG)))) + (at host evaluate! "definer" definitionG)))) (def: .public (executors target expander platform analysis_bundle generation_bundle directive_bundle diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux index 1fbde2917..05e58e21f 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -32,7 +32,7 @@ (def: size (Random Nat) - (|> r.nat (# r.monad each (|>> (n.% ..limit) (n.max 2))))) + (|> r.nat (at r.monad each (|>> (n.% ..limit) (n.max 2))))) (def: (tail? size idx) (-> Nat Nat Bit) @@ -67,7 +67,7 @@ [(r.unicode 5) synthesis.text synthesis.path/text])) (do [! r.monad] [size ..size - idx (|> r.nat (# ! each (n.% size))) + idx (|> r.nat (at ! each (n.% size))) [subS subP] case .let [unitS (synthesis.text synthesis.unit) caseS (synthesis.tuple @@ -82,7 +82,7 @@ (in [caseS caseP])) (do [! r.monad] [size ..size - idx (|> r.nat (# ! each (n.% size))) + idx (|> r.nat (at ! each (n.% size))) [subS subP] case .let [right? (tail? size idx) caseS (synthesis.variant @@ -246,7 +246,7 @@ (_.property "===" (and (text#= (synthesis.%path special_path) (synthesis.%path special_pattern_path)) - (# synthesis.path_equivalence = special_path special_pattern_path))) + (at synthesis.path_equivalence = special_path special_pattern_path))) (_.property "CODE" (|> special_input (run "special_input") diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index e8d5e6ab4..8012798f8 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -124,7 +124,7 @@ (def: simple_frac (Random Frac) - (|> r.nat (# r.monad each (|>> (n.% 1000) .int i.frac)))) + (|> r.nat (at r.monad each (|>> (n.% 1000) .int i.frac)))) (def: (f64 run) (-> Runner Test) @@ -182,12 +182,12 @@ (def: (text run) (-> Runner Test) (do [! r.monad] - [sample_size (|> r.nat (# ! each (|>> (n.% 10) (n.max 1)))) + [sample_size (|> r.nat (at ! each (|>> (n.% 10) (n.max 1)))) sample_lower (r.lower_case_alpha sample_size) sample_upper (r.upper_case_alpha sample_size) sample_alpha (|> (r.alphabetic sample_size) (r.only (|>> (text#= sample_upper) not))) - char_idx (|> r.nat (# ! each (n.% sample_size))) + char_idx (|> r.nat (at ! each (n.% sample_size))) .let [sample_lowerS (synthesis.text sample_lower) sample_upperS (synthesis.text sample_upper) sample_alphaS (synthesis.text sample_alpha) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index 7e2c6d66f..86c495c3b 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -50,7 +50,7 @@ (-> Runner Test) (do [! r.monad] [[arity local functionS] ..function - partial_arity (|> r.nat (# ! each (|>> (n.% arity) (n.max 1)))) + partial_arity (|> r.nat (at ! each (|>> (n.% arity) (n.max 1)))) inputs (r.list arity r.safe_frac) .let [expectation (maybe.trusted (list.item (-- local) inputs)) inputsS (list#each (|>> synthesis.f64) inputs)]] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index e7b9ceeb0..f8f68c51e 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -41,7 +41,7 @@ (def: (variable run) (-> Runner Test) (do [! r.monad] - [register (|> r.nat (# ! each (n.% 100))) + [register (|> r.nat (at ! each (n.% 100))) expected r.safe_frac] (_.property "Local variables." (|> (synthesis.branch/let [(synthesis.f64 expected) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index d914c309f..86054b07e 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -31,8 +31,8 @@ (def: (variant run) (-> Runner Test) (do [! r.monad] - [num_tags (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) - tag_in (|> r.nat (# ! each (n.% num_tags))) + [num_tags (|> r.nat (at ! each (|>> (n.% 10) (n.max 2)))) + tag_in (|> r.nat (at ! each (n.% num_tags))) .let [last?_in (|> num_tags -- (n.= tag_in))] value_in r.i64] (_.property (%.symbol (symbol synthesis.variant)) @@ -67,7 +67,7 @@ (def: (tuple run) (-> Runner Test) (do [! r.monad] - [size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) + [size (|> r.nat (at ! each (|>> (n.% 10) (n.max 2)))) tuple_in (r.list size r.i64)] (_.property (%.symbol (symbol synthesis.tuple)) (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux index fcb51c926..8d0fe390e 100644 --- a/stdlib/source/specification/lux/abstract/apply.lux +++ b/stdlib/source/specification/lux/abstract/apply.lux @@ -19,7 +19,7 @@ (def: (identity injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] - [sample (# ! each injection random.nat)] + [sample (at ! each injection random.nat)] (_.property "Identity." ((comparison n.=) (/#on sample (injection function.identity)) @@ -29,7 +29,7 @@ (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat - increase (# ! each n.+ random.nat)] + increase (at ! each n.+ random.nat)] (_.property "Homomorphism." ((comparison n.=) (/#on (injection sample) (injection increase)) @@ -39,7 +39,7 @@ (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat - increase (# ! each n.+ random.nat)] + increase (at ! each n.+ random.nat)] (_.property "Interchange." ((comparison n.=) (/#on (injection sample) (injection increase)) @@ -52,9 +52,9 @@ (do [! random.monad] [sample random.nat increase (is (Random :$/1:) - (# ! each n.+ random.nat)) + (at ! each n.+ random.nat)) decrease (is (Random :$/1:) - (# ! each n.- random.nat))] + (at ! each n.- random.nat))] (_.property "Composition." ((comparison n.=) (|> (injection (is (-> :$/1: :$/1: :$/1:) diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index 6486cecd8..c9a03c6d3 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -17,9 +17,9 @@ (All (_ f) (-> (Injection f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat - morphism (# ! each (function (_ diff) - (|>> _//out (n.+ diff))) - random.nat) + morphism (at ! each (function (_ diff) + (|>> _//out (n.+ diff))) + random.nat) .let [start (injection sample)]] (_.property "Left identity." (n.= (morphism start) @@ -39,12 +39,12 @@ (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat - increase (# ! each (function (_ diff) - (|>> _//out (n.+ diff))) - random.nat) - decrease (# ! each (function (_ diff) - (|>> _//out(n.- diff))) - random.nat) + increase (at ! each (function (_ diff) + (|>> _//out (n.+ diff))) + random.nat) + decrease (at ! each (function (_ diff) + (|>> _//out(n.- diff))) + random.nat) .let [start (injection sample) == (comparison n.=)]] (_.property "Associativity." diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux index cc53413ca..8ac207e97 100644 --- a/stdlib/source/specification/lux/abstract/functor.lux +++ b/stdlib/source/specification/lux/abstract/functor.lux @@ -25,7 +25,7 @@ (def: (identity injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] - [sample (# ! each injection random.nat)] + [sample (at ! each injection random.nat)] (_.property "Identity." ((comparison n.=) (@//each function.identity sample) @@ -35,7 +35,7 @@ (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample random.nat - increase (# ! each n.+ random.nat)] + increase (at ! each n.+ random.nat)] (_.property "Homomorphism." ((comparison n.=) (@//each increase (injection sample)) @@ -44,9 +44,9 @@ (def: (composition injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] - [sample (# ! each injection random.nat) - increase (# ! each n.+ random.nat) - decrease (# ! each n.- random.nat)] + [sample (at ! each injection random.nat) + increase (at ! each n.+ random.nat) + decrease (at ! each n.- random.nat)] (_.property "Composition." ((comparison n.=) (|> sample (@//each increase) (@//each decrease)) diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index 70911488b..25a2f3e4f 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -15,9 +15,9 @@ (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat - morphism (# ! each (function (_ diff) - (|>> (n.+ diff) _//in)) - random.nat)] + morphism (at ! each (function (_ diff) + (|>> (n.+ diff) _//in)) + random.nat)] (_.property "Left identity." ((comparison n.=) (|> (injection sample) (_//each morphism) _//conjoint) @@ -36,12 +36,12 @@ (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat - increase (# ! each (function (_ diff) - (|>> (n.+ diff) _//in)) - random.nat) - decrease (# ! each (function (_ diff) - (|>> (n.- diff) _//in)) - random.nat)] + increase (at ! each (function (_ diff) + (|>> (n.+ diff) _//in)) + random.nat) + decrease (at ! each (function (_ diff) + (|>> (n.- diff) _//in)) + random.nat)] (_.property "Associativity." ((comparison n.=) (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint) diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux index e80610389..fd31486a2 100644 --- a/stdlib/source/specification/lux/world/console.lux +++ b/stdlib/source/specification/lux/world/console.lux @@ -23,11 +23,11 @@ [message (random.alphabetic 10)] (in (do async.monad [console (async.future console) - ?write (# console write (format message text.new_line)) - ?read (# console read []) - ?read_line (# console read_line []) - ?close/good (# console close []) - ?close/bad (# console close []) + ?write (at console write (format message text.new_line)) + ?read (at console read []) + ?read_line (at console read_line []) + ?close/good (at console close []) + ?close/bad (at console close []) .let [can_write! (case ?write diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux index 0956528de..33c42637d 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -58,9 +58,9 @@ (def: (directory?&make_directory fs parent) (-> (/.System Async) /.Path (Async Bit)) (do async.monad - [directory_pre! (# fs directory? parent) - made? (# fs make_directory parent) - directory_post! (# fs directory? parent)] + [directory_pre! (at fs directory? parent) + made? (at fs make_directory parent) + directory_post! (at fs directory? parent)] (in (and (not directory_pre!) (case made? {try.#Success _} true @@ -70,9 +70,9 @@ (def: (file?&write fs content path) (-> (/.System Async) Binary /.Path (Async Bit)) (do async.monad - [file_pre! (# fs file? path) - made? (# fs write path content) - file_post! (# fs file? path)] + [file_pre! (at fs file? path) + made? (at fs write path content) + file_post! (at fs file? path)] (in (and (not file_pre!) (case made? {try.#Success _} true @@ -82,26 +82,26 @@ (def: (file_size&read&append fs expected_file_size content appendix path) (-> (/.System Async) Nat Binary Binary /.Path (Async Bit)) (do async.monad - [pre_file_size (# fs file_size path) - pre_content (# fs read path) - appended? (# fs append path appendix) - post_file_size (# fs file_size path) - post_content (# fs read path)] + [pre_file_size (at fs file_size path) + pre_content (at fs read path) + appended? (at fs append path appendix) + post_file_size (at fs file_size path) + post_content (at fs read path)] (in (<| (try.else false) (do [! try.monad] [pre_file_size! - (# ! each (n.= expected_file_size) pre_file_size) + (at ! each (n.= expected_file_size) pre_file_size) pre_content! - (# ! each (binary#= content) pre_content) + (at ! each (binary#= content) pre_content) _ appended? post_file_size! - (# ! each (n.= (n.* 2 expected_file_size)) post_file_size) + (at ! each (n.= (n.* 2 expected_file_size)) post_file_size) post_content! - (# ! each (binary#= (binary#composite content appendix)) post_content)] + (at ! each (binary#= (binary#composite content appendix)) post_content)] (in (and pre_file_size! pre_content! post_file_size! @@ -110,21 +110,21 @@ (def: (modified?&last_modified fs expected_time path) (-> (/.System Async) Instant /.Path (Async Bit)) (do async.monad - [modified? (# fs modify path expected_time) - last_modified (# fs last_modified path)] + [modified? (at fs modify path expected_time) + last_modified (at fs last_modified path)] (in (<| (try.else false) (do [! try.monad] [_ modified?] - (# ! each (instant#= expected_time) last_modified)))))) + (at ! each (instant#= expected_time) last_modified)))))) (def: (directory_files&sub_directories fs parent sub_dir child) (-> (/.System Async) /.Path /.Path /.Path (Async Bit)) (let [sub_dir (/.rooted fs parent sub_dir) child (/.rooted fs parent child)] (do async.monad - [made_sub? (# fs make_directory sub_dir) - directory_files (# fs directory_files parent) - sub_directories (# fs sub_directories parent) + [made_sub? (at fs make_directory sub_dir) + directory_files (at fs directory_files parent) + sub_directories (at fs sub_directories parent) .let [(open "list#[0]") (list.equivalence text.equivalence)]] (in (<| (try.else false) (do try.monad @@ -141,12 +141,12 @@ (let [origin (/.rooted fs parent child) destination (/.rooted fs parent alternate_child)] (do [! async.monad] - [moved? (# fs move origin destination) + [moved? (at fs move origin destination) lost? (|> origin - (# fs file?) - (# ! each not)) - found? (# fs file? destination) - deleted? (# fs delete destination)] + (at fs file?) + (at ! each not)) + found? (at fs file? destination) + deleted? (at fs delete destination)] (in (<| (try.else false) (do try.monad [_ moved? @@ -165,7 +165,7 @@ (|>> (text#= child) not) (|>> (text#= sub_dir) not)) (random.numeric 2)) - expected_file_size (# ! each (|>> (n.% 10) ++) random.nat) + expected_file_size (at ! each (|>> (n.% 10) ++) random.nat) content ($binary.random expected_file_size) appendix ($binary.random expected_file_size) expected_time random.instant]) @@ -188,8 +188,8 @@ can_execute? (|> path - (# fs can_execute?) - (# ! each (|>> (try.else true) not))) + (at fs can_execute?) + (at ! each (|>> (try.else true) not))) directory_files&sub_directories (..directory_files&sub_directories fs parent sub_dir child) @@ -216,16 +216,16 @@ [fs (async.future fs) .let [dir/1 (/.rooted fs dir/0 dir/1) dir/2 (/.rooted fs dir/1 dir/2)] - pre_dir/0 (# fs directory? dir/0) - pre_dir/1 (# fs directory? dir/1) - pre_dir/2 (# fs directory? dir/2) + pre_dir/0 (at fs directory? dir/0) + pre_dir/1 (at fs directory? dir/1) + pre_dir/2 (at fs directory? dir/2) made? (/.make_directories ! fs dir/2) - post_dir/0 (# fs directory? dir/0) - post_dir/1 (# fs directory? dir/1) - post_dir/2 (# fs directory? dir/2) + post_dir/0 (at fs directory? dir/0) + post_dir/1 (at fs directory? dir/1) + post_dir/2 (at fs directory? dir/2) cannot_make_directory!/0 (/.make_directories ! fs "") - cannot_make_directory!/1 (/.make_directories ! fs (# fs separator))]) + cannot_make_directory!/1 (/.make_directories ! fs (at fs separator))]) (all _.and' (_.coverage' [/.make_directories] (and (not pre_dir/0) @@ -292,17 +292,17 @@ (do [! async.monad] [fs (async.future fs) - pre_file/0 (# fs file? file) + pre_file/0 (at fs file? file) pre_file/1 (/.exists? ! fs file) - pre_dir/0 (# fs directory? dir) + pre_dir/0 (at fs directory? dir) pre_dir/1 (/.exists? ! fs dir) made_file? (/.make_file ! fs (utf8#encoded file) file) - made_dir? (# fs make_directory dir) + made_dir? (at fs make_directory dir) - post_file/0 (# fs file? file) + post_file/0 (at fs file? file) post_file/1 (/.exists? ! fs file) - post_dir/0 (# fs directory? dir) + post_dir/0 (at fs directory? dir) post_dir/1 (/.exists? ! fs dir)]) (_.coverage' [/.exists?] (and (not pre_file/0) diff --git a/stdlib/source/specification/lux/world/program.lux b/stdlib/source/specification/lux/world/program.lux index 26371c1e6..3830dfb2a 100644 --- a/stdlib/source/specification/lux/world/program.lux +++ b/stdlib/source/specification/lux/world/program.lux @@ -28,5 +28,5 @@ (and (not (dictionary.empty? environment)) (list.every? (|>> text.empty? not) (dictionary.keys environment)) - (not (text.empty? (# subject home))) - (not (text.empty? (# subject directory))))))))) + (not (text.empty? (at subject home))) + (not (text.empty? (at subject directory))))))))) diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux index 64e31abfe..702d29d97 100644 --- a/stdlib/source/specification/lux/world/shell.lux +++ b/stdlib/source/specification/lux/world/shell.lux @@ -35,7 +35,7 @@ (def: (can_wait! process) (-> (/.Process Async) _.Assertion) - (|> (# process await []) + (|> (at process await []) (async#each (|>> (try#each (i.= /.normal)) (try.else false) (_.coverage' [/.Exit /.normal]))) @@ -43,15 +43,15 @@ (def: (can_read! expected process) (-> Text (/.Process Async) (Async Bit)) - (|> (# process read []) + (|> (at process read []) (async#each (|>> (try#each (text#= expected)) (try.else false))))) (def: (can_destroy! process) (-> (/.Process Async) (Async Bit)) (do async.monad - [?destroy (# process destroy []) - ?await (# process await [])] + [?destroy (at process destroy []) + ?await (at process await [])] (in (and (case ?destroy {try.#Success _} true @@ -71,10 +71,10 @@ (<| (_.for [/.Shell /.Process]) (do [! random.monad] [message (random.alphabetic 10) - seconds (# ! each (|>> (n.% 5) (n.+ 5)) random.nat)] + seconds (at ! each (|>> (n.% 5) (n.+ 5)) random.nat)] (in (do [! async.monad] - [?echo (# shell execute (..echo! message)) - ?sleep (# shell execute (..sleep! seconds))] + [?echo (at shell execute (..echo! message)) + ?sleep (at shell execute (..sleep! seconds))] (case [?echo ?sleep] [{try.#Success echo} {try.#Success sleep}] (do ! -- cgit v1.2.3