diff options
author | Eduardo Julian | 2021-09-12 15:39:55 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-09-12 15:39:55 -0400 |
commit | 2dbbaaec93a53f8dd0b96a0028b9cf125c9066cd (patch) | |
tree | 14bc8b5abe09b46ef005c3ff7cf132f1d98ddf0d /stdlib/source/specification | |
parent | dda05bca0956af5e5b3875c4cc36e61aa04772e4 (diff) |
Re-named \ => # && \\ => ##
Diffstat (limited to 'stdlib/source/specification')
19 files changed, 173 insertions, 173 deletions
diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux index 717df9bf4..7ed477767 100644 --- a/stdlib/source/specification/aedifex/repository.lux +++ b/stdlib/source/specification/aedifex/repository.lux @@ -30,17 +30,17 @@ (in ($_ _.and' (do async.monad [.let [good_uri (/remote.uri (value@ //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! (# subject upload good_uri expected) + good_download! (# subject download good_uri) .let [bad_uri (/remote.uri (value@ //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! (# subject upload bad_uri expected) + bad_download! (# subject download bad_uri)] (_.cover' [/.Repository] (let [successfull_flow! (case [good_upload! good_download!] [{try.#Success _} {try.#Success actual}] - (\ binary.equivalence = expected actual) + (# binary.equivalence = expected actual) _ false) diff --git a/stdlib/source/specification/compositor/common.lux b/stdlib/source/specification/compositor/common.lux index e5d3dab25..c71082a94 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)))) + (# host evaluate! evaluation_name expressionG)))) (def: (definer (^slots [platform.#runtime platform.#phase platform.#host]) state) @@ -55,7 +55,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)))) + (# 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 52689480e..8343cbb67 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -7,13 +7,13 @@ [pipe {"+" [case>]}] ["[0]" try {"+" [Try]}]] [data - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}]] [number ["n" nat] ["f" frac]] [collection - ["[0]" list ("[1]\[0]" mix)]]] + ["[0]" list ("[1]#[0]" mix)]]] [math ["r" random {"+" [Random]}]] [tool @@ -32,7 +32,7 @@ (def: size (Random Nat) - (|> r.nat (\ r.monad each (|>> (n.% ..limit) (n.max 2))))) + (|> r.nat (# r.monad each (|>> (n.% ..limit) (n.max 2))))) (def: (tail? size idx) (-> Nat Nat Bit) @@ -66,7 +66,7 @@ [(r.unicode 5) synthesis.text synthesis.path/text])) (do [! r.monad] [size ..size - idx (|> r.nat (\ ! each (n.% size))) + idx (|> r.nat (# ! each (n.% size))) [subS subP] case .let [unitS (synthesis.text synthesis.unit) caseS (synthesis.tuple @@ -81,7 +81,7 @@ (in [caseS caseP])) (do [! r.monad] [size ..size - idx (|> r.nat (\ ! each (n.% size))) + idx (|> r.nat (# ! each (n.% size))) [subS subP] case .let [right? (tail? size idx) caseS (synthesis.variant @@ -152,7 +152,7 @@ (function (_ head tail) (synthesis.variant [0 #1 (synthesis.tuple (list head tail))]))) _list_ (: (-> (List Synthesis) Synthesis) - (list\mix _item_ _end_))] + (list#mix _item_ _end_))] (let [__tuple__ (: (-> (List Synthesis) Synthesis) (|>> list.reversed _list_ [9 #0] synthesis.variant _code_)) __form__ (: (-> (List Synthesis) Synthesis) @@ -169,7 +169,7 @@ (_code_ (synthesis.variant [7 #0 (synthesis.tuple (list (synthesis.text module) (synthesis.text short)))])))) __list__ (: (-> (List Synthesis) Synthesis) - (list\mix (function (_ head tail) + (list#mix (function (_ head tail) (__form__ (list (__tag__ ["" "Item"]) head tail))) (__tag__ ["" "End"]))) __apply__ (: (-> Synthesis Synthesis Synthesis) @@ -247,9 +247,9 @@ (-> Runner Test) ($_ _.and (_.test "===" - (and (text\= (synthesis.%path special_path) + (and (text#= (synthesis.%path special_path) (synthesis.%path special_pattern_path)) - (\ synthesis.path_equivalence = special_path special_pattern_path))) + (# synthesis.path_equivalence = special_path special_pattern_path))) (_.test "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 eeaa68a94..82dc698f9 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -7,13 +7,13 @@ [pipe {"+" [case>]}] ["[0]" try {"+" [Try]}]] [data - ["[0]" bit ("[1]\[0]" equivalence)] + ["[0]" bit ("[1]#[0]" equivalence)] [number ["[0]" i64] ["n" nat] ["i" int] ["f" frac]] - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}]] [collection ["[0]" list]]] @@ -90,7 +90,7 @@ (let [subject <subject_expr>])))] ["lux i64 f64" Frac i.frac f.= subject] - ["lux i64 char" Text (|>> (:as Nat) text.from_code) text\= (|> subject + ["lux i64 char" Text (|>> (:as Nat) text.from_code) text#= (|> subject (:as Nat) (n.% (i64.left_shifted 8 1)) (:as Int))] @@ -111,14 +111,14 @@ ["lux i64 *" i.* Int i.=] ["lux i64 /" i./ Int i.=] ["lux i64 %" i.% Int i.=] - ["lux i64 =" i.= Bit bit\=] - ["lux i64 <" i.< Bit bit\=] + ["lux i64 =" i.= Bit bit#=] + ["lux i64 <" i.< Bit bit#=] )) )))) (def: simple_frac (Random Frac) - (|> r.nat (\ r.monad each (|>> (n.% 1000) .int i.frac)))) + (|> r.nat (# r.monad each (|>> (n.% 1000) .int i.frac)))) (def: (f64 run) (-> Runner Test) @@ -145,7 +145,7 @@ (synthesis.f64 subject))} (run (..safe <extension>)) (case> {try.#Success valueV} - (bit\= (<text> param subject) + (bit#= (<text> param subject) (:as Bit valueV)) _ @@ -175,12 +175,12 @@ (def: (text run) (-> Runner Test) (do [! r.monad] - [sample_size (|> r.nat (\ ! each (|>> (n.% 10) (n.max 1)))) + [sample_size (|> r.nat (# ! each (|>> (n.% 10) (n.max 1)))) sample_lower (r.ascii/lower_alpha sample_size) sample_upper (r.ascii/upper_alpha sample_size) sample_alpha (|> (r.ascii/alpha sample_size) - (r.only (|>> (text\= sample_upper) not))) - char_idx (|> r.nat (\ ! each (n.% sample_size))) + (r.only (|>> (text#= sample_upper) not))) + char_idx (|> r.nat (# ! each (n.% sample_size))) .let [sample_lowerS (synthesis.text sample_lower) sample_upperS (synthesis.text sample_upper) sample_alphaS (synthesis.text sample_alpha) @@ -262,7 +262,7 @@ (case> (^multi {try.#Success valueV} [(:as (Maybe Text) valueV) {.#Some valueV}]) - (text\= expected valueV) + (text#= expected valueV) _ false))))] @@ -322,7 +322,7 @@ (case> (^multi {try.#Success valueV} [(:as (Try Text) valueV) {try.#Success valueV}]) - (text\= message valueV) + (text#= message valueV) _ false)))) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index 9a2f68a8a..8250a8d71 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -11,9 +11,9 @@ [number ["n" nat]] [collection - ["[0]" list ("[1]\[0]" functor)]]] + ["[0]" list ("[1]#[0]" functor)]]] [math - ["r" random {"+" [Random]} ("[1]\[0]" monad)]] + ["r" random {"+" [Random]} ("[1]#[0]" monad)]] [tool [compiler [analysis {"+" [Arity]}] @@ -30,11 +30,11 @@ (def: arity (Random Arity) - (|> r.nat (r\each (|>> (n.% max_arity) (n.max 1))))) + (|> r.nat (r#each (|>> (n.% max_arity) (n.max 1))))) (def: (local arity) (-> Arity (Random Register)) - (|> r.nat (r\each (|>> (n.% arity) ++)))) + (|> r.nat (r#each (|>> (n.% arity) ++)))) (def: function (Random [Arity Register Synthesis]) @@ -51,10 +51,10 @@ (-> Runner Test) (do [! r.monad] [[arity local functionS] ..function - partial_arity (|> r.nat (\ ! each (|>> (n.% arity) (n.max 1)))) + partial_arity (|> r.nat (# ! 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)]] + inputsS (list#each (|>> synthesis.f64) inputs)]] ($_ _.and (_.test "Can read arguments." (|> (synthesis.function/apply [synthesis.#function functionS @@ -75,7 +75,7 @@ (or (n.= 1 arity) (let [environment (|> partial_arity (enum.range n.enum 1) - (list\each (|>> {reference.#Local}))) + (list#each (|>> {reference.#Local}))) variableS (if (n.<= partial_arity local) (synthesis.variable/foreign (-- local)) (synthesis.variable/local (|> local (n.- partial_arity)))) diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index f4bf220a4..531b48c88 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -7,10 +7,10 @@ [pipe {"+" [case>]}] ["[0]" try]] [data - ["[0]" bit ("[1]\[0]" equivalence)] + ["[0]" bit ("[1]#[0]" equivalence)] [number ["f" frac]] - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}]]] [math ["r" random]] @@ -40,9 +40,9 @@ {try.#Failure _} false))))] - ["bit" synthesis.bit r.bit bit\=] + ["bit" synthesis.bit r.bit bit#=] ["i64" synthesis.i64 r.i64 "lux i64 ="] ["f64" synthesis.f64 r.frac f.='] - ["text" synthesis.text (r.ascii 5) text\=] + ["text" synthesis.text (r.ascii 5) text#=] )) ))) diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index a8391f63a..ddeab3146 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -40,7 +40,7 @@ (def: (variable run) (-> Runner Test) (do [! r.monad] - [register (|> r.nat (\ ! each (n.% 100))) + [register (|> r.nat (# ! each (n.% 100))) expected r.safe_frac] (_.test "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 1b98fc558..9045c60e1 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -11,11 +11,11 @@ [number ["n" nat] ["i" int]] - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}]] [collection ["[0]" array {"+" [Array]}] - ["[0]" list ("[1]\[0]" functor)]]] + ["[0]" list ("[1]#[0]" functor)]]] [math ["r" random]] ["[0]" ffi {"+" [import:]}] @@ -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 (# ! each (|>> (n.% 10) (n.max 2)))) + tag_in (|> r.nat (# ! each (n.% num_tags))) .let [last?_in (|> num_tags -- (n.= tag_in))] value_in r.i64] (_.test (%.name (name_of synthesis.variant)) @@ -51,7 +51,7 @@ same_tag? (|> tag_out ffi.int_to_long (:as Nat) (n.= tag_in)) same_flag? (case last?_out {.#Some last?_out'} - (and last?_in (text\= "" (:as Text last?_out'))) + (and last?_in (text#= "" (:as Text last?_out'))) {.#None} (not last?_in)) @@ -66,10 +66,10 @@ (def: (tuple run) (-> Runner Test) (do [! r.monad] - [size (|> r.nat (\ ! each (|>> (n.% 10) (n.max 2)))) + [size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) tuple_in (r.list size r.i64)] (_.test (%.name (name_of synthesis.tuple)) - (|> (synthesis.tuple (list\each (|>> synthesis.i64) tuple_in)) + (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) (run "tuple") (case> {try.#Success tuple_out} (let [tuple_out (:as (Array Any) tuple_out)] diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux index f14a43aa5..9b52df567 100644 --- a/stdlib/source/specification/lux/abstract/apply.lux +++ b/stdlib/source/specification/lux/abstract/apply.lux @@ -15,49 +15,49 @@ [// [functor {"+" [Injection Comparison]}]]) -(def: (identity injection comparison (^open "\[0]")) +(def: (identity injection comparison (^open "#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] - [sample (\ ! each injection random.nat)] + [sample (# ! each injection random.nat)] (_.test "Identity." ((comparison n.=) - (\on sample (injection function.identity)) + (#on sample (injection function.identity)) sample)))) -(def: (homomorphism injection comparison (^open "\[0]")) +(def: (homomorphism injection comparison (^open "#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat - increase (\ ! each n.+ random.nat)] + increase (# ! each n.+ random.nat)] (_.test "Homomorphism." ((comparison n.=) - (\on (injection sample) (injection increase)) + (#on (injection sample) (injection increase)) (injection (increase sample)))))) -(def: (interchange injection comparison (^open "\[0]")) +(def: (interchange injection comparison (^open "#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat - increase (\ ! each n.+ random.nat)] + increase (# ! each n.+ random.nat)] (_.test "Interchange." ((comparison n.=) - (\on (injection sample) (injection increase)) - (\on (injection increase) (injection (: (-> (-> Nat Nat) Nat) + (#on (injection sample) (injection increase)) + (#on (injection increase) (injection (: (-> (-> Nat Nat) Nat) (function (_ f) (f sample))))))))) -(def: (composition injection comparison (^open "\[0]")) +(def: (composition injection comparison (^open "#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat - increase (\ ! each n.+ random.nat) - decrease (\ ! each n.- random.nat)] + increase (# ! each n.+ random.nat) + decrease (# ! each n.- random.nat)] (_.test "Composition." ((comparison n.=) (|> (injection function.composite) - (\on (injection increase)) - (\on (injection decrease)) - (\on (injection sample))) - (\on (\on (injection sample) + (#on (injection increase)) + (#on (injection decrease)) + (#on (injection sample))) + (#on (#on (injection sample) (injection increase)) (injection decrease)))))) diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index ee28bfb49..e465bee7e 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -17,7 +17,7 @@ (All (_ f) (-> (Injection f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat - morphism (\ ! each (function (_ diff) + morphism (# ! each (function (_ diff) (|>> _//out (n.+ diff))) random.nat) .let [start (injection sample)]] @@ -39,10 +39,10 @@ (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat - increase (\ ! each (function (_ diff) + increase (# ! each (function (_ diff) (|>> _//out (n.+ diff))) random.nat) - decrease (\ ! each (function (_ diff) + decrease (# ! each (function (_ diff) (|>> _//out(n.- diff))) random.nat) .let [start (injection sample) diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux index 26fdf0828..4b0a66fa1 100644 --- a/stdlib/source/specification/lux/abstract/enum.lux +++ b/stdlib/source/specification/lux/abstract/enum.lux @@ -9,19 +9,19 @@ [\\library ["[0]" /]]) -(def: .public (spec (^open "\[0]") gen_sample) +(def: .public (spec (^open "_#[0]") gen_sample) (All (_ a) (-> (/.Enum a) (Random a) Test)) (do random.monad [sample gen_sample] (<| (_.for [/.Enum]) ($_ _.and (_.test "Successor and predecessor are inverse functions." - (and (\= (|> sample \succ \pred) - sample) - (\= (|> sample \pred \succ) - sample) - (not (\= (\succ sample) - sample)) - (not (\= (\pred sample) - sample)))) + (and (_#= (|> sample _#succ _#pred) + sample) + (_#= (|> sample _#pred _#succ) + sample) + (not (_#= (_#succ sample) + sample)) + (not (_#= (_#pred sample) + sample)))) )))) diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux index 37e38ad42..b446b565c 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 (# ! each injection random.nat)] (_.test "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 (# ! each n.+ random.nat)] (_.test "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 (# ! each injection random.nat) + increase (# ! each n.+ random.nat) + decrease (# ! each n.- random.nat)] (_.test "Composition." ((comparison n.=) (|> sample (@//each increase) (@//each decrease)) diff --git a/stdlib/source/specification/lux/abstract/hash.lux b/stdlib/source/specification/lux/abstract/hash.lux index 65b78a5cb..1671647b3 100644 --- a/stdlib/source/specification/lux/abstract/hash.lux +++ b/stdlib/source/specification/lux/abstract/hash.lux @@ -11,12 +11,12 @@ [\\library ["[0]" /]]) -(def: .public (spec (^open "\[0]") random) +(def: .public (spec (^open "_#[0]") random) (All (_ a) (-> (/.Hash a) (Random a) Test)) (do random.monad [parameter random subject random] (_.cover [/.Hash] - (if (\= parameter subject) - (n.= (\hash parameter) (\hash subject)) + (if (_#= parameter subject) + (n.= (_#hash parameter) (_#hash subject)) true)))) diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index e193e1ecd..7de5df858 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -15,7 +15,7 @@ (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat - morphism (\ ! each (function (_ diff) + morphism (# ! each (function (_ diff) (|>> (n.+ diff) _//in)) random.nat)] (_.test "Left identity." @@ -36,10 +36,10 @@ (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat - increase (\ ! each (function (_ diff) + increase (# ! each (function (_ diff) (|>> (n.+ diff) _//in)) random.nat) - decrease (\ ! each (function (_ diff) + decrease (# ! each (function (_ diff) (|>> (n.- diff) _//in)) random.nat)] (_.test "Associativity." diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux index dba042a60..531a246a2 100644 --- a/stdlib/source/specification/lux/abstract/monoid.lux +++ b/stdlib/source/specification/lux/abstract/monoid.lux @@ -11,7 +11,7 @@ [// [equivalence {"+" [Equivalence]}]]]]) -(def: .public (spec (^open "\[0]") (^open "\[0]") gen_sample) +(def: .public (spec (^open "_#[0]") (^open "_#[0]") gen_sample) (All (_ a) (-> (Equivalence a) (/.Monoid a) (Random a) Test)) (do random.monad [sample gen_sample @@ -21,12 +21,12 @@ (<| (_.for [/.Monoid]) ($_ _.and (_.test "Left identity." - (\= sample - (\composite \identity sample))) + (_#= sample + (_#composite _#identity sample))) (_.test "Right identity." - (\= sample - (\composite sample \identity))) + (_#= sample + (_#composite sample _#identity))) (_.test "Associativity." - (\= (\composite left (\composite mid right)) - (\composite (\composite left mid) right))) + (_#= (_#composite left (_#composite mid right)) + (_#composite (_#composite left mid) right))) )))) diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux index 5ca3f7c05..aa51422de 100644 --- a/stdlib/source/specification/lux/world/console.lux +++ b/stdlib/source/specification/lux/world/console.lux @@ -23,11 +23,11 @@ [message (random.ascii/alpha 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 (# console write (format message text.new_line)) + ?read (# console read []) + ?read_line (# console read_line []) + ?close/good (# console close []) + ?close/bad (# 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 ea5913175..d768d446c 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -8,17 +8,17 @@ [control [pipe {"+" [case>]}] [io {"+" [IO]}] - ["[0]" maybe ("[1]\[0]" functor)] - ["[0]" try ("[1]\[0]" functor)] + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try ("[1]#[0]" functor)] ["[0]" exception] [concurrency ["[0]" async {"+" [Async]}]]] [data - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}] [encoding - ["[0]" utf8 ("[1]\[0]" codec)]]] - ["[0]" binary {"+" [Binary]} ("[1]\[0]" equivalence monoid) + ["[0]" utf8 ("[1]#[0]" codec)]]] + ["[0]" binary {"+" [Binary]} ("[1]#[0]" equivalence monoid) ["$[1]" \\test]] [collection ["[0]" list]]] @@ -27,7 +27,7 @@ [number ["n" nat]]] [time - ["[0]" instant {"+" [Instant]} ("[1]\[0]" equivalence)]]]] + ["[0]" instant {"+" [Instant]} ("[1]#[0]" equivalence)]]]] [\\library ["[0]" /]]) @@ -48,20 +48,20 @@ (_.cover' [/.parent] (|> (/.rooted fs parent child) (/.parent fs) - (maybe\each (text\= parent)) + (maybe#each (text#= parent)) (maybe.else false))) (_.cover' [/.name] (|> (/.rooted fs parent child) (/.name fs) - (text\= child))) + (text#= child))) )))) (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! (# fs directory? parent) + made? (# fs make_directory parent) + directory_post! (# fs directory? parent)] (in (and (not directory_pre!) (case made? {try.#Success _} true @@ -71,9 +71,9 @@ (def: (file?&write fs content path) (-> (/.System Async) Binary /.Path (Async Bit)) (do async.monad - [file_pre! (\ fs file? path) - made? (\ fs write content path) - file_post! (\ fs file? path)] + [file_pre! (# fs file? path) + made? (# fs write content path) + file_post! (# fs file? path)] (in (and (not file_pre!) (case made? {try.#Success _} true @@ -83,26 +83,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 appendix path) - post_file_size (\ fs file_size path) - post_content (\ fs read path)] + [pre_file_size (# fs file_size path) + pre_content (# fs read path) + appended? (# fs append appendix path) + post_file_size (# fs file_size path) + post_content (# fs read path)] (in (<| (try.else false) (do [! try.monad] [pre_file_size! - (\ ! each (n.= expected_file_size) pre_file_size) + (# ! each (n.= expected_file_size) pre_file_size) pre_content! - (\ ! each (binary\= content) pre_content) + (# ! each (binary#= content) pre_content) _ appended? post_file_size! - (\ ! each (n.= (n.* 2 expected_file_size)) post_file_size) + (# ! each (n.= (n.* 2 expected_file_size)) post_file_size) post_content! - (\ ! each (binary\= (binary\composite content appendix)) post_content)] + (# ! each (binary#= (binary#composite content appendix)) post_content)] (in (and pre_file_size! pre_content! post_file_size! @@ -111,30 +111,30 @@ (def: (modified?&last_modified fs expected_time path) (-> (/.System Async) Instant /.Path (Async Bit)) (do async.monad - [modified? (\ fs modify expected_time path) - last_modified (\ fs last_modified path)] + [modified? (# fs modify expected_time path) + last_modified (# fs last_modified path)] (in (<| (try.else false) (do [! try.monad] [_ modified?] - (\ ! each (instant\= expected_time) last_modified)))))) + (# ! 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) - .let [(^open "list\[0]") (list.equivalence text.equivalence)]] + [made_sub? (# fs make_directory sub_dir) + directory_files (# fs directory_files parent) + sub_directories (# fs sub_directories parent) + .let [(^open "list#[0]") (list.equivalence text.equivalence)]] (in (<| (try.else false) (do try.monad [_ made_sub?] (in (and (|> directory_files - (try\each (list\= (list child))) + (try#each (list#= (list child))) (try.else false)) (|> sub_directories - (try\each (list\= (list sub_dir))) + (try#each (list#= (list sub_dir))) (try.else false)))))))))) (def: (move&delete fs parent child alternate_child) @@ -142,12 +142,12 @@ (let [origin (/.rooted fs parent child) destination (/.rooted fs parent alternate_child)] (do [! async.monad] - [moved? (\ fs move destination origin) + [moved? (# fs move destination origin) lost? (|> origin - (\ fs file?) - (\ ! each not)) - found? (\ fs file? destination) - deleted? (\ fs delete destination)] + (# fs file?) + (# ! each not)) + found? (# fs file? destination) + deleted? (# fs delete destination)] (in (<| (try.else false) (do try.monad [_ moved? @@ -160,13 +160,13 @@ (<| (do [! random.monad] [parent (random.ascii/numeric 2) child (random.ascii/numeric 2) - sub_dir (random.only (|>> (text\= child) not) + sub_dir (random.only (|>> (text#= child) not) (random.ascii/numeric 2)) alternate_child (random.only (predicate.and - (|>> (text\= child) not) - (|>> (text\= sub_dir) not)) + (|>> (text#= child) not) + (|>> (text#= sub_dir) not)) (random.ascii/numeric 2)) - expected_file_size (\ ! each (|>> (n.% 10) ++) random.nat) + expected_file_size (# ! each (|>> (n.% 10) ++) random.nat) content ($binary.random expected_file_size) appendix ($binary.random expected_file_size) expected_time random.instant]) @@ -189,8 +189,8 @@ can_execute? (|> path - (\ fs can_execute?) - (\ ! each (|>> (try.else true) not))) + (# fs can_execute?) + (# ! each (|>> (try.else true) not))) directory_files&sub_directories (..directory_files&sub_directories fs parent sub_dir child) @@ -217,16 +217,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 (# fs directory? dir/0) + pre_dir/1 (# fs directory? dir/1) + pre_dir/2 (# 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 (# fs directory? dir/0) + post_dir/1 (# fs directory? dir/1) + post_dir/2 (# 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 (# fs separator))]) ($_ _.and' (_.cover' [/.make_directories] (and (not pre_dir/0) @@ -260,8 +260,8 @@ in (do [! async.monad] [fs (async.future fs) - make_file!/0 (/.make_file ! fs (utf8\encoded file/0) file/0) - make_file!/1 (/.make_file ! fs (utf8\encoded file/0) file/0)]) + make_file!/0 (/.make_file ! fs (utf8#encoded file/0) file/0) + make_file!/1 (/.make_file ! fs (utf8#encoded file/0) file/0)]) ($_ _.and' (_.cover' [/.make_file] (case make_file!/0 @@ -287,23 +287,23 @@ (-> (IO (/.System Async)) Test) (<| (do [! random.monad] [file (random.ascii/numeric 2) - dir (random.only (|>> (text\= file) not) + dir (random.only (|>> (text#= file) not) (random.ascii/numeric 2))]) in (do [! async.monad] [fs (async.future fs) - pre_file/0 (\ fs file? file) + pre_file/0 (# fs file? file) pre_file/1 (/.exists? ! fs file) - pre_dir/0 (\ fs directory? dir) + pre_dir/0 (# 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_file? (/.make_file ! fs (utf8#encoded file) file) + made_dir? (# fs make_directory dir) - post_file/0 (\ fs file? file) + post_file/0 (# fs file? file) post_file/1 (/.exists? ! fs file) - post_dir/0 (\ fs directory? dir) + post_dir/0 (# fs directory? dir) post_dir/1 (/.exists? ! fs dir)]) (_.cover' [/.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 e647e316b..401422fc4 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? (# subject home))) + (not (text.empty? (# subject directory))))))))) diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux index bd0ac70b4..6d80fbbd8 100644 --- a/stdlib/source/specification/lux/world/shell.lux +++ b/stdlib/source/specification/lux/world/shell.lux @@ -5,14 +5,14 @@ [abstract [monad {"+" [do]}]] [control - ["[0]" try ("[1]\[0]" functor)] + ["[0]" try ("[1]#[0]" functor)] [concurrency - ["[0]" async {"+" [Async]} ("[1]\[0]" monad)]] + ["[0]" async {"+" [Async]} ("[1]#[0]" monad)]] [parser ["[0]" environment {"+" [Environment]}]]] [data ["[0]" product] - ["[0]" text ("[1]\[0]" equivalence) + ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" [format]}]]] [math ["[0]" random] @@ -35,23 +35,23 @@ (def: (can_wait! process) (-> (/.Process Async) _.Assertion) - (|> (\ process await []) - (async\each (|>> (try\each (i.= /.normal)) + (|> (# process await []) + (async#each (|>> (try#each (i.= /.normal)) (try.else false) (_.cover' [/.Exit /.normal]))) - async\conjoint)) + async#conjoint)) (def: (can_read! expected process) (-> Text (/.Process Async) (Async Bit)) - (|> (\ process read []) - (async\each (|>> (try\each (text\= expected)) + (|> (# 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 (# process destroy []) + ?await (# process await [])] (in (and (case ?destroy {try.#Success _} true @@ -71,10 +71,10 @@ (<| (_.for [/.Shell /.Process]) (do [! random.monad] [message (random.ascii/alpha 10) - seconds (\ ! each (|>> (n.% 5) (n.+ 5)) random.nat)] + seconds (# ! each (|>> (n.% 5) (n.+ 5)) random.nat)] (in (do [! async.monad] - [?echo (\ shell execute (..echo! message)) - ?sleep (\ shell execute (..sleep! seconds))] + [?echo (# shell execute (..echo! message)) + ?sleep (# shell execute (..sleep! seconds))] (case [?echo ?sleep] [{try.#Success echo} {try.#Success sleep}] (do ! |