diff options
Diffstat (limited to 'stdlib/source/specification')
12 files changed, 147 insertions, 147 deletions
diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux index bf430a368..293b7f1e0 100644 --- a/stdlib/source/specification/aedifex/repository.lux +++ b/stdlib/source/specification/aedifex/repository.lux @@ -39,7 +39,7 @@ (_.cover' [/.Repository] (let [successfull_flow! (case [good_upload! good_download!] - [(#try.Success _) (#try.Success actual)] + [{#try.Success _} {#try.Success actual}] (\ binary.equivalence = expected actual) _ @@ -47,7 +47,7 @@ failed_flow! (case [bad_upload! bad_download!] - [(#try.Failure _) (#try.Failure _)] + [{#try.Failure _} {#try.Failure _}] true _ diff --git a/stdlib/source/specification/compositor.lux b/stdlib/source/specification/compositor.lux index a2569f334..2668d36ca 100644 --- a/stdlib/source/specification/compositor.lux +++ b/stdlib/source/specification/compositor.lux @@ -58,10 +58,10 @@ expander program))]] (case ?state,runner,definer - (#try.Success [[directive_bundle directive_state] runner definer]) + {#try.Success [[directive_bundle directive_state] runner definer]} (..test runner definer (value@ [#directive.analysis #directive.state] directive_state) expander) - (#try.Failure error) + {#try.Failure error} (_.failure error)))) diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux index be7677848..f0856eb1f 100644 --- a/stdlib/source/specification/compositor/analysis/type.lux +++ b/stdlib/source/specification/compositor/analysis/type.lux @@ -26,10 +26,10 @@ (analysis/type.with_type output_type (analysis.phase expander (` ((~ (code.text extension)) (~+ params)))))) (phase.result state) - (case> (#try.Success _) + (case> {#try.Success _} true - (#try.Failure _) + {#try.Failure _} false))) (def: check @@ -42,12 +42,12 @@ <type> (<code> value)]))] - [r.bit (0 #0 "#Bit" (0 #0)) code.bit] - [r.nat (0 #0 "#I64" (0 #1 (0 #0 "#Nat" (0 #0)) (0 #0))) code.nat] - [r.int (0 #0 "#I64" (0 #1 (0 #0 "#Int" (0 #0)) (0 #0))) code.int] - [r.rev (0 #0 "#I64" (0 #1 (0 #0 "#Rev" (0 #0)) (0 #0))) code.rev] - [r.safe_frac (0 #0 "#Frac" (0 #0)) code.frac] - [(r.ascii/upper_alpha 5) (0 #0 "#Text" (0 #0)) code.text] + [r.bit {0 #0 "#Bit" {0 #0}} code.bit] + [r.nat {0 #0 "#I64" {0 #1 {0 #0 "#Nat" {0 #0}} {0 #0}}} code.nat] + [r.int {0 #0 "#I64" {0 #1 {0 #0 "#Int" {0 #0}} {0 #0}}} code.int] + [r.rev {0 #0 "#I64" {0 #1 {0 #0 "#Rev" {0 #0}} {0 #0}}} code.rev] + [r.safe_frac {0 #0 "#Frac" {0 #0}} code.frac] + [(r.ascii/upper_alpha 5) {0 #0 "#Text" {0 #0}} code.text] ))))) (def: .public (spec expander state) diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux index d699aa74b..eb27aea29 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -40,10 +40,10 @@ (def: .public (verify expected) (-> Frac (Try Any) Bit) - (|>> (case> (#try.Success actual) + (|>> (case> {#try.Success actual} (f.= expected (:as Frac actual)) - (#try.Failure _) + {#try.Failure _} false))) (def: case @@ -187,11 +187,11 @@ (def: special_path Path - (let [_end_ (synthesis.path/side (#.Left 0)) - _item_ (synthesis.path/side (#.Right 0)) - _head_ (synthesis.path/member (#.Left 0)) - _tail_ (synthesis.path/member (#.Right 0)) - _tuple_ (synthesis.path/side (#.Left 9))] + (let [_end_ (synthesis.path/side {#.Left 0}) + _item_ (synthesis.path/side {#.Right 0}) + _head_ (synthesis.path/member {#.Left 0}) + _tail_ (synthesis.path/member {#.Right 0}) + _tuple_ (synthesis.path/side {#.Left 9})] ($_ synthesis.path/alt ($_ synthesis.path/seq _item_ @@ -213,18 +213,18 @@ (def: special_pattern analysis.Pattern - (let [... [_ (#Tuple (#Item arg args'))] + (let [... [_ {#Tuple {#Item arg args'}}] head (<| analysis.pattern/tuple (list (analysis.pattern/bind 2)) analysis.pattern/variant [9 #0] analysis.pattern/variant [0 #1] analysis.pattern/tuple (list (analysis.pattern/bind 3) (analysis.pattern/bind 4))) - ... (#Item body #End) + ... {#Item body #End} tail (<| analysis.pattern/variant [0 #1] analysis.pattern/tuple (list (analysis.pattern/bind 5)) analysis.pattern/variant [0 #0] (analysis.pattern/unit))] - ... (#Item <head> <tail>) + ... {#Item <head> <tail>} (<| analysis.pattern/variant [0 #1] (analysis.pattern/tuple (list head tail))))) @@ -253,28 +253,28 @@ (_.test "CODE" (|> special_input (run "special_input") - (case> (#try.Success output) + (case> {#try.Success output} true - (#try.Failure _) + {#try.Failure _} false))) (_.test "PATTERN_MATCHING 0" (|> (synthesis.branch/case [special_input special_path]) (run "special_path") - (case> (#try.Success output) + (case> {#try.Success output} true - (#try.Failure _) + {#try.Failure _} false))) (_.test "PATTERN_MATCHING 1" (|> (synthesis.branch/case [special_input special_pattern_path]) (run "special_pattern_path") - (case> (#try.Success output) + (case> {#try.Success output} true - (#try.Failure _) + {#try.Failure _} false))) )) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 2db239415..9c03349f4 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -39,13 +39,13 @@ subject r.i64] (with_expansions [<binary> (template [<extension> <reference> <param_expr>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list (synthesis.i64 param) - (synthesis.i64 subject))) + (|> {#synthesis.Extension <extension> (list (synthesis.i64 param) + (synthesis.i64 subject))} (run (..safe <extension>)) - (case> (#try.Success valueT) + (case> {#try.Success valueT} (n.= (<reference> param subject) (:as Nat valueT)) - (#try.Failure _) + {#try.Failure _} false) (let [param <param_expr>])))] @@ -58,16 +58,16 @@ ($_ _.and <binary> (_.test "lux i64 arithmetic-right-shift" - (|> (#synthesis.Extension "lux i64 arithmetic-right-shift" - (list (synthesis.i64 subject) - (synthesis.i64 param))) + (|> {#synthesis.Extension "lux i64 arithmetic-right-shift" + (list (synthesis.i64 subject) + (synthesis.i64 param))} (run (..safe "lux i64 arithmetic-right-shift")) - (case> (#try.Success valueT) + (case> {#try.Success valueT} ("lux i64 =" (i64.arithmetic_right_shifted param subject) (:as I64 valueT)) - (#try.Failure _) + {#try.Failure _} false) (let [param (n.% 64 param)]))) )))) @@ -80,12 +80,12 @@ (`` ($_ _.and (~~ (template [<extension> <type> <prepare> <comp> <subject_expr>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list (synthesis.i64 subject))) + (|> {#synthesis.Extension <extension> (list (synthesis.i64 subject))} (run (..safe <extension>)) - (case> (#try.Success valueT) + (case> {#try.Success valueT} (<comp> (<prepare> subject) (:as <type> valueT)) - (#try.Failure _) + {#try.Failure _} false) (let [subject <subject_expr>])))] @@ -97,13 +97,13 @@ )) (~~ (template [<extension> <reference> <outputT> <comp>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list (synthesis.i64 param) - (synthesis.i64 subject))) + (|> {#synthesis.Extension <extension> (list (synthesis.i64 param) + (synthesis.i64 subject))} (run (..safe <extension>)) - (case> (#try.Success valueT) + (case> {#try.Success valueT} (<comp> (<reference> param subject) (:as <outputT> valueT)) - (#try.Failure _) + {#try.Failure _} false)))] ["lux i64 +" i.+ Int i.=] @@ -128,8 +128,8 @@ (`` ($_ _.and (~~ (template [<extension> <reference> <comp>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list (synthesis.f64 param) - (synthesis.f64 subject))) + (|> {#synthesis.Extension <extension> (list (synthesis.f64 param) + (synthesis.f64 subject))} (run (..safe <extension>)) (//case.verify (<reference> param subject))))] @@ -141,10 +141,10 @@ )) (~~ (template [<extension> <text>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list (synthesis.f64 param) - (synthesis.f64 subject))) + (|> {#synthesis.Extension <extension> (list (synthesis.f64 param) + (synthesis.f64 subject))} (run (..safe <extension>)) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (bit\= (<text> param subject) (:as Bit valueV)) @@ -156,7 +156,7 @@ )) (~~ (template [<extension> <reference>] [(_.test <extension> - (|> (#synthesis.Extension <extension> (list)) + (|> {#synthesis.Extension <extension> (list)} (run (..safe <extension>)) (//case.verify <reference>)))] @@ -167,8 +167,8 @@ (_.test "'lux f64 i64 && 'lux i64 f64'" (|> (run (..safe "lux f64 i64") (|> subject synthesis.f64 - (list) (#synthesis.Extension "lux f64 i64") - (list) (#synthesis.Extension "lux i64 f64"))) + (list) {#synthesis.Extension "lux f64 i64"} + (list) {#synthesis.Extension "lux i64 f64"})) (//case.verify subject))) )))) @@ -184,84 +184,84 @@ .let [sample_lowerS (synthesis.text sample_lower) sample_upperS (synthesis.text sample_upper) sample_alphaS (synthesis.text sample_alpha) - concatenatedS (#synthesis.Extension "lux text concat" (list sample_lowerS sample_upperS)) + concatenatedS {#synthesis.Extension "lux text concat" (list sample_lowerS sample_upperS)} pre_rep_once (format sample_lower sample_upper) post_rep_once (format sample_lower sample_alpha) pre_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_upper)) post_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_alpha))]] ($_ _.and (_.test "Can compare texts for equality." - (and (|> (#synthesis.Extension "lux text =" (list sample_lowerS sample_lowerS)) + (and (|> {#synthesis.Extension "lux text =" (list sample_lowerS sample_lowerS)} (run (..safe "lux text =")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (:as Bit valueV) _ false)) - (|> (#synthesis.Extension "lux text =" (list sample_upperS sample_lowerS)) + (|> {#synthesis.Extension "lux text =" (list sample_upperS sample_lowerS)} (run (..safe "lux text =")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (not (:as Bit valueV)) _ false)))) (_.test "Can compare texts for order." - (|> (#synthesis.Extension "lux text <" (list sample_lowerS sample_upperS)) + (|> {#synthesis.Extension "lux text <" (list sample_lowerS sample_upperS)} (run (..safe "lux text <")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (:as Bit valueV) - (#try.Failure _) + {#try.Failure _} false))) (_.test "Can get length of text." - (|> (#synthesis.Extension "lux text size" (list sample_lowerS)) + (|> {#synthesis.Extension "lux text size" (list sample_lowerS)} (run (..safe "lux text size")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (n.= sample_size (:as Nat valueV)) _ false))) (_.test "Can concatenate text." - (|> (#synthesis.Extension "lux text size" (list concatenatedS)) + (|> {#synthesis.Extension "lux text size" (list concatenatedS)} (run (..safe "lux text size")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (n.= (n.* 2 sample_size) (:as Nat valueV)) _ false))) (_.test "Can find index of sub-text." - (and (|> (#synthesis.Extension "lux text index" - (list concatenatedS sample_lowerS - (synthesis.i64 +0))) + (and (|> {#synthesis.Extension "lux text index" + (list concatenatedS sample_lowerS + (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Maybe Nat) valueV) - (#.Some valueV)]) + {#.Some valueV}]) (n.= 0 valueV) _ false)) - (|> (#synthesis.Extension "lux text index" - (list concatenatedS sample_upperS - (synthesis.i64 +0))) + (|> {#synthesis.Extension "lux text index" + (list concatenatedS sample_upperS + (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Maybe Nat) valueV) - (#.Some valueV)]) + {#.Some valueV}]) (n.= sample_size valueV) _ false)))) (let [test_clip (: (-> (I64 Any) (I64 Any) Text Bit) (function (_ offset length expected) - (|> (#synthesis.Extension "lux text clip" - (list concatenatedS - (synthesis.i64 offset) - (synthesis.i64 length))) + (|> {#synthesis.Extension "lux text clip" + (list concatenatedS + (synthesis.i64 offset) + (synthesis.i64 length))} (run (..safe "lux text clip")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Maybe Text) valueV) - (#.Some valueV)]) + {#.Some valueV}]) (text\= expected valueV) _ @@ -270,13 +270,13 @@ (and (test_clip 0 sample_size sample_lower) (test_clip sample_size sample_size sample_upper)))) (_.test "Can extract individual characters from text." - (|> (#synthesis.Extension "lux text char" - (list sample_lowerS - (synthesis.i64 char_idx))) + (|> {#synthesis.Extension "lux text char" + (list sample_lowerS + (synthesis.i64 char_idx))} (run (..safe "lux text char")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Maybe Int) valueV) - (#.Some valueV)]) + {#.Some valueV}]) (text.contains? ("lux i64 char" valueV) sample_lower) @@ -290,51 +290,51 @@ [message (r.ascii/alpha 5)] ($_ _.and (_.test "Can log messages." - (|> (#synthesis.Extension "lux io log" - (list (synthesis.text (format "LOG: " message)))) + (|> {#synthesis.Extension "lux io log" + (list (synthesis.text (format "LOG: " message)))} (run (..safe "lux io log")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} true - (#try.Failure _) + {#try.Failure _} false))) (_.test "Can throw runtime errors." - (and (|> (#synthesis.Extension "lux try" - (list (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity 1 - #synthesis.body (#synthesis.Extension "lux io error" - (list (synthesis.text message)))]))) + (and (|> {#synthesis.Extension "lux try" + (list (synthesis.function/abstraction + [#synthesis.environment (list) + #synthesis.arity 1 + #synthesis.body {#synthesis.Extension "lux io error" + (list (synthesis.text message))}]))} (run (..safe "lux try")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Try Text) valueV) - (#try.Failure error)]) + {#try.Failure error}]) (text.contains? message error) _ false)) - (|> (#synthesis.Extension "lux try" - (list (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity 1 - #synthesis.body (synthesis.text message)]))) + (|> {#synthesis.Extension "lux try" + (list (synthesis.function/abstraction + [#synthesis.environment (list) + #synthesis.arity 1 + #synthesis.body (synthesis.text message)]))} (run (..safe "lux try")) - (case> (^multi (#try.Success valueV) + (case> (^multi {#try.Success valueV} [(:as (Try Text) valueV) - (#try.Success valueV)]) + {#try.Success valueV}]) (text\= message valueV) _ false)))) (_.test "Can obtain current time in milli-seconds." - (|> (synthesis.tuple (list (#synthesis.Extension "lux io current-time" (list)) - (#synthesis.Extension "lux io current-time" (list)))) + (|> (synthesis.tuple (list {#synthesis.Extension "lux io current-time" (list)} + {#synthesis.Extension "lux io current-time" (list)})) (run (..safe "lux io current-time")) - (case> (#try.Success valueV) + (case> {#try.Success valueV} (let [[pre post] (:as [Nat Nat] valueV)] (n.>= pre post)) - (#try.Failure _) + {#try.Failure _} false))) ))) diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index ba20601a3..670b30d30 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -34,10 +34,10 @@ [expected <gen>] (_.test (%.name (name_of <synthesis>)) (|> (run <evaluation_name> (<synthesis> expected)) - (case> (#try.Success actual) + (case> {#try.Success actual} (<test> expected (:expected actual)) - (#try.Failure _) + {#try.Failure _} false))))] ["bit" synthesis.bit r.bit bit\=] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index ce3c7332a..d98e660e0 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -31,10 +31,10 @@ expected r.safe_frac] (_.test "Definitions." (|> (define name (synthesis.f64 expected)) - (case> (#try.Success actual) + (case> {#try.Success actual} (f.= expected (:as Frac actual)) - (#try.Failure _) + {#try.Failure _} false))))) (def: (variable run) @@ -47,10 +47,10 @@ register (synthesis.variable/local register)]) (run "variable") - (case> (#try.Success actual) + (case> {#try.Success actual} (f.= expected (:as Frac actual)) - (#try.Failure _) + {#try.Failure _} false))))) (def: .public (spec runner definer) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index a70e61531..c98013875 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -42,7 +42,7 @@ #analysis.right? last?_in #analysis.value (synthesis.i64 value_in)]) (run "variant") - (case> (#try.Success valueT) + (case> {#try.Success valueT} (let [valueT (:as (Array Any) valueT)] (and (n.= 3 (array.size valueT)) (let [tag_out (:as java/lang/Integer (maybe.trusted (array.read! 0 valueT))) @@ -50,7 +50,7 @@ value_out (:as Any (maybe.trusted (array.read! 2 valueT))) same_tag? (|> tag_out ffi.int_to_long (:as Nat) (n.= tag_in)) same_flag? (case last?_out - (#.Some last?_out') + {#.Some last?_out'} (and last?_in (text\= "" (:as Text last?_out'))) #.None @@ -60,7 +60,7 @@ same_flag? same_value?)))) - (#try.Failure _) + {#try.Failure _} false))))) (def: (tuple run) @@ -71,14 +71,14 @@ (_.test (%.name (name_of synthesis.tuple)) (|> (synthesis.tuple (list\each (|>> synthesis.i64) tuple_in)) (run "tuple") - (case> (#try.Success tuple_out) + (case> {#try.Success tuple_out} (let [tuple_out (:as (Array Any) tuple_out)] (and (n.= size (array.size tuple_out)) (list.every? (function (_ [left right]) (i.= left (:as Int right))) (list.zipped/2 tuple_in (array.list tuple_out))))) - (#try.Failure _) + {#try.Failure _} false))))) (def: .public (spec runner) diff --git a/stdlib/source/specification/lux/abstract/codec.lux b/stdlib/source/specification/lux/abstract/codec.lux index 5cbdb2aa1..f30d9c94c 100644 --- a/stdlib/source/specification/lux/abstract/codec.lux +++ b/stdlib/source/specification/lux/abstract/codec.lux @@ -20,8 +20,8 @@ (_.for [/.Codec] (_.test "Isomorphism." (case (|> expected @//encoded @//decoded) - (#try.Success actual) + {#try.Success actual} (@//= expected actual) - (#try.Failure _) + {#try.Failure _} false))))) diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux index 15305d236..e2f73db67 100644 --- a/stdlib/source/specification/lux/world/console.lux +++ b/stdlib/source/specification/lux/world/console.lux @@ -31,7 +31,7 @@ .let [can_write! (case ?write - (#try.Success _) + {#try.Success _} true _ @@ -39,7 +39,7 @@ can_read! (case [?read ?read_line] - [(#try.Success _) (#try.Success _)] + [{#try.Success _} {#try.Success _}] true _ @@ -47,7 +47,7 @@ can_close! (case [?close/good ?close/bad] - [(#try.Success _) (#try.Failure _)] + [{#try.Success _} {#try.Failure _}] true _ diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux index f7c056624..3c6679dd7 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -64,8 +64,8 @@ directory_post! (\ fs directory? parent)] (in (and (not directory_pre!) (case made? - (#try.Success _) true - (#try.Failure _) false) + {#try.Success _} true + {#try.Failure _} false) directory_post!)))) (def: (file?&write fs content path) @@ -76,8 +76,8 @@ file_post! (\ fs file? path)] (in (and (not file_pre!) (case made? - (#try.Success _) true - (#try.Failure _) false) + {#try.Success _} true + {#try.Failure _} false) file_post!)))) (def: (file_size&read&append fs expected_file_size content appendix path) @@ -233,23 +233,23 @@ (not pre_dir/1) (not pre_dir/2) (case made? - (#try.Success _) true - (#try.Failure _) false) + {#try.Success _} true + {#try.Failure _} false) post_dir/0 post_dir/1 post_dir/2)) (_.cover' [/.cannot_make_directory] (and (case cannot_make_directory!/0 - (#try.Success _) + {#try.Success _} false - (#try.Failure error) + {#try.Failure error} (exception.match? /.cannot_make_directory error)) (case cannot_make_directory!/1 - (#try.Success _) + {#try.Success _} false - (#try.Failure error) + {#try.Failure error} (exception.match? /.cannot_make_directory error)))) ))) @@ -265,14 +265,14 @@ ($_ _.and' (_.cover' [/.make_file] (case make_file!/0 - (#try.Success _) true - (#try.Failure error) false)) + {#try.Success _} true + {#try.Failure error} false)) (_.cover' [/.cannot_make_file] (case make_file!/1 - (#try.Success _) + {#try.Success _} false - (#try.Failure error) + {#try.Failure error} (exception.match? /.cannot_make_file error))) ))) @@ -312,11 +312,11 @@ (not pre_dir/1) (case made_file? - (#try.Success _) true - (#try.Failure _) false) + {#try.Success _} true + {#try.Failure _} false) (case made_dir? - (#try.Success _) true - (#try.Failure _) false) + {#try.Success _} true + {#try.Failure _} false) post_file/0 post_file/1 diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux index 2d844ce9a..5fa846019 100644 --- a/stdlib/source/specification/lux/world/shell.lux +++ b/stdlib/source/specification/lux/world/shell.lux @@ -53,16 +53,16 @@ [?destroy (\ process destroy []) ?await (\ process await [])] (in (and (case ?destroy - (#try.Success _) + {#try.Success _} true - (#try.Failure error) + {#try.Failure error} false) (case ?await - (#try.Success _) + {#try.Success _} false - (#try.Failure error) + {#try.Failure error} true))))) (with_expansions [<shell_coverage> (as_is [/.Command /.Argument])] @@ -76,7 +76,7 @@ [?echo (\ shell execute (..echo! message)) ?sleep (\ shell execute (..sleep! seconds))] (case [?echo ?sleep] - [(#try.Success echo) (#try.Success sleep)] + [{#try.Success echo} {#try.Success sleep}] (do ! [can_read! (..can_read! message echo) can_destroy! (..can_destroy! sleep)] |