From 0d909187d5b9effcd08f533d50af7d29c0d6bfd8 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 8 Apr 2022 05:42:36 -0400 Subject: De-sigil-ification: $ --- stdlib/source/specification/aedifex/repository.lux | 48 +- stdlib/source/specification/compositor.lux | 18 +- .../specification/compositor/analysis/type.lux | 40 +- .../specification/compositor/generation/case.lux | 240 ++++----- .../specification/compositor/generation/common.lux | 534 ++++++++++----------- .../compositor/generation/function.lux | 122 ++--- .../compositor/generation/primitive.lux | 34 +- .../compositor/generation/reference.lux | 6 +- .../compositor/generation/structure.lux | 8 +- stdlib/source/specification/lux/abstract/apply.lux | 12 +- .../source/specification/lux/abstract/comonad.lux | 10 +- stdlib/source/specification/lux/abstract/enum.lux | 22 +- .../specification/lux/abstract/equivalence.lux | 10 +- .../source/specification/lux/abstract/functor.lux | 10 +- .../lux/abstract/functor/contravariant.lux | 6 +- .../source/specification/lux/abstract/interval.lux | 12 +- stdlib/source/specification/lux/abstract/monad.lux | 10 +- .../source/specification/lux/abstract/monoid.lux | 22 +- stdlib/source/specification/lux/abstract/order.lux | 84 ++-- stdlib/source/specification/lux/world/file.lux | 126 ++--- stdlib/source/specification/lux/world/shell.lux | 12 +- 21 files changed, 693 insertions(+), 693 deletions(-) (limited to 'stdlib/source/specification') diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux index 9e22c1ac4..3d4fdd69e 100644 --- a/stdlib/source/specification/aedifex/repository.lux +++ b/stdlib/source/specification/aedifex/repository.lux @@ -27,31 +27,31 @@ (-> Artifact Artifact (/.Repository Async) Test) (do random.monad [expected (_binary.random 100)] - (in ($_ _.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) + (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) - .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)] - (_.cover' [/.Repository] - (let [successfull_flow! - (case [good_upload! good_download!] - [{try.#Success _} {try.#Success actual}] - (# binary.equivalence = expected actual) + .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)] + (_.cover' [/.Repository] + (let [successfull_flow! + (case [good_upload! good_download!] + [{try.#Success _} {try.#Success actual}] + (# binary.equivalence = expected actual) - _ - false) + _ + false) - failed_flow! - (case [bad_upload! bad_download!] - [{try.#Failure _} {try.#Failure _}] - true + failed_flow! + (case [bad_upload! bad_download!] + [{try.#Failure _} {try.#Failure _}] + true - _ - false)] - (and successfull_flow! - failed_flow!)))) - )))) + _ + false)] + (and successfull_flow! + failed_flow!)))) + )))) diff --git a/stdlib/source/specification/compositor.lux b/stdlib/source/specification/compositor.lux index f2af26161..ebf509498 100644 --- a/stdlib/source/specification/compositor.lux +++ b/stdlib/source/specification/compositor.lux @@ -31,15 +31,15 @@ (def: (test runner definer state expander) (-> Runner Definer analysis.State+ Expander Test) - ($_ _.and - (/analysis/type.spec expander state) - (/generation/primitive.spec runner) - (/generation/structure.spec runner) - (/generation/reference.spec runner definer) - (/generation/case.spec runner) - (/generation/function.spec runner) - (/generation/common.spec runner) - )) + (all _.and + (/analysis/type.spec expander state) + (/generation/primitive.spec runner) + (/generation/structure.spec runner) + (/generation/reference.spec runner definer) + (/generation/case.spec runner) + (/generation/function.spec runner) + (/generation/common.spec runner) + )) (def: .public (spec platform bundle expander program) (All (_ anchor expression directive) diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux index c51f0cced..b84e18888 100644 --- a/stdlib/source/specification/compositor/analysis/type.lux +++ b/stdlib/source/specification/compositor/analysis/type.lux @@ -35,30 +35,30 @@ (def: check (Random [Code Type Code]) - (`` ($_ r.either - (~~ (template [ ] - [(do r.monad - [value ] - (in [(` ) - - ( value)]))] + (`` (all r.either + (~~ (template [ ] + [(do r.monad + [value ] + (in [(` ) + + ( 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) (-> Expander State+ Test) (do r.monad [[typeC exprT exprC] ..check [other_typeC other_exprT other_exprC] ..check] - ($_ _.and - (_.test "lux check" - (check_success+ expander state "lux check" (list typeC exprC) exprT)) - (_.test "lux coerce" - (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT)) - ))) + (all _.and + (_.test "lux check" + (check_success+ expander state "lux check" (list typeC exprC) exprT)) + (_.test "lux coerce" + (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT)) + ))) diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux index 80faa246f..12fa81a14 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -50,52 +50,52 @@ (def: case (Random [Synthesis Path]) (<| r.rec (function (_ case)) - (`` ($_ r.either - (do r.monad - [value r.i64] - (in [(synthesis.i64 value) - synthesis.path/pop])) - (~~ (template [ ] - [(do r.monad - [value ] - (in [( value) - ( value)]))] + (`` (all r.either + (do r.monad + [value r.i64] + (in [(synthesis.i64 value) + synthesis.path/pop])) + (~~ (template [ ] + [(do r.monad + [value ] + (in [( value) + ( value)]))] - [r.bit synthesis.bit synthesis.path/bit] - [r.i64 synthesis.i64 synthesis.path/i64] - [r.frac synthesis.f64 synthesis.path/f64] - [(r.unicode 5) synthesis.text synthesis.path/text])) - (do [! r.monad] - [size ..size - idx (|> r.nat (# ! each (n.% size))) - [subS subP] case - .let [unitS (synthesis.text synthesis.unit) - caseS (synthesis.tuple - (list.together (list (list.repeated idx unitS) - (list subS) - (list.repeated (|> size -- (n.- idx)) unitS)))) - caseP ($_ synthesis.path/seq - (if (tail? size idx) - (synthesis.member/right idx) - (synthesis.member/left idx)) - subP)]] - (in [caseS caseP])) - (do [! r.monad] - [size ..size - idx (|> r.nat (# ! each (n.% size))) - [subS subP] case - .let [right? (tail? size idx) - caseS (synthesis.variant - [analysis.#lefts idx - analysis.#right? right? - analysis.#value subS]) - caseP ($_ synthesis.path/seq - (if right? - (synthesis.side/right idx) - (synthesis.side/left idx)) - subP)]] - (in [caseS caseP])) - )))) + [r.bit synthesis.bit synthesis.path/bit] + [r.i64 synthesis.i64 synthesis.path/i64] + [r.frac synthesis.f64 synthesis.path/f64] + [(r.unicode 5) synthesis.text synthesis.path/text])) + (do [! r.monad] + [size ..size + idx (|> r.nat (# ! each (n.% size))) + [subS subP] case + .let [unitS (synthesis.text synthesis.unit) + caseS (synthesis.tuple + (list.together (list (list.repeated idx unitS) + (list subS) + (list.repeated (|> size -- (n.- idx)) unitS)))) + caseP (all synthesis.path/seq + (if (tail? size idx) + (synthesis.member/right idx) + (synthesis.member/left idx)) + subP)]] + (in [caseS caseP])) + (do [! r.monad] + [size ..size + idx (|> r.nat (# ! each (n.% size))) + [subS subP] case + .let [right? (tail? size idx) + caseS (synthesis.variant + [analysis.#lefts idx + analysis.#right? right? + analysis.#value subS]) + caseP (all synthesis.path/seq + (if right? + (synthesis.side/right idx) + (synthesis.side/left idx)) + subP)]] + (in [caseS caseP])) + )))) (def: (let_spec run) (-> Runner Test) @@ -130,11 +130,11 @@ (_.test (%.symbol (symbol synthesis.branch/case)) (|> (synthesis.branch/case [inputS - ($_ synthesis.path/alt - ($_ synthesis.path/seq - pathS - (synthesis.path/then (synthesis.f64 on_success))) - (synthesis.path/then (synthesis.f64 on_failure)))]) + (all synthesis.path/alt + (all synthesis.path/seq + pathS + (synthesis.path/then (synthesis.f64 on_success))) + (synthesis.path/then (synthesis.f64 on_failure)))]) (run "case_spec") (verify on_success))))) @@ -189,24 +189,24 @@ _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_ - _head_ - _head_ (synthesis.path/bind 2) synthesis.path/pop - _tail_ _tuple_ _item_ - _head_ (synthesis.path/bind 3) synthesis.path/pop - _tail_ (synthesis.path/bind 4) synthesis.path/pop - synthesis.path/pop synthesis.path/pop synthesis.path/pop synthesis.path/pop - _tail_ _item_ - _head_ (synthesis.path/bind 5) synthesis.path/pop - _tail_ _end_ - ... THEN - (synthesis.path/then (synthesis.bit #1))) - ($_ synthesis.path/seq - (synthesis.path/bind 2) - ... THEN - (synthesis.path/then (synthesis.bit #0)))))) + (all synthesis.path/alt + (all synthesis.path/seq + _item_ + _head_ + _head_ (synthesis.path/bind 2) synthesis.path/pop + _tail_ _tuple_ _item_ + _head_ (synthesis.path/bind 3) synthesis.path/pop + _tail_ (synthesis.path/bind 4) synthesis.path/pop + synthesis.path/pop synthesis.path/pop synthesis.path/pop synthesis.path/pop + _tail_ _item_ + _head_ (synthesis.path/bind 5) synthesis.path/pop + _tail_ _end_ + ... THEN + (synthesis.path/then (synthesis.bit #1))) + (all synthesis.path/seq + (synthesis.path/bind 2) + ... THEN + (synthesis.path/then (synthesis.bit #0)))))) (def: special_pattern analysis.Pattern @@ -227,62 +227,62 @@ (def: special_pattern_path Path - ($_ synthesis.path/alt - (<| try.trusted - (phase.result [extension/synthesis.bundle - synthesis.init]) - (case.path phase/synthesis.phase - special_pattern) - (analysis.bit #1)) - ($_ synthesis.path/seq - (synthesis.path/bind 2) - ... THEN - (synthesis.path/then (synthesis.bit #0))))) + (all synthesis.path/alt + (<| try.trusted + (phase.result [extension/synthesis.bundle + synthesis.init]) + (case.path phase/synthesis.phase + special_pattern) + (analysis.bit #1)) + (all synthesis.path/seq + (synthesis.path/bind 2) + ... THEN + (synthesis.path/then (synthesis.bit #0))))) ... TODO: Get rid of this ASAP (def: (special_spec run) (-> Runner Test) - ($_ _.and - (_.test "===" - (and (text#= (synthesis.%path special_path) - (synthesis.%path special_pattern_path)) - (# synthesis.path_equivalence = special_path special_pattern_path))) - (_.test "CODE" - (|> special_input - (run "special_input") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 0" - (|> (synthesis.branch/case [special_input - special_path]) - (run "special_path") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 1" - (|> (synthesis.branch/case [special_input - special_pattern_path]) - (run "special_pattern_path") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) - )) + (all _.and + (_.test "===" + (and (text#= (synthesis.%path special_path) + (synthesis.%path special_pattern_path)) + (# synthesis.path_equivalence = special_path special_pattern_path))) + (_.test "CODE" + (|> special_input + (run "special_input") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.test "PATTERN_MATCHING 0" + (|> (synthesis.branch/case [special_input + special_path]) + (run "special_path") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.test "PATTERN_MATCHING 1" + (|> (synthesis.branch/case [special_input + special_pattern_path]) + (run "special_pattern_path") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + )) (def: .public (spec run) (-> Runner Test) - ($_ _.and - (..special_spec run) - (..let_spec run) - (..if_spec run) - (..case_spec run) - )) + (all _.and + (..special_spec run) + (..let_spec run) + (..if_spec run) + (..case_spec run) + )) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index dc2bf6ec7..599dae209 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -58,69 +58,69 @@ ["lux i64 left-shift" i64.left_shifted (n.% 64 param)] ["lux i64 logical-right-shift" i64.logic_right_shifted (n.% 64 param)] )] - ($_ _.and - - (_.test "lux i64 arithmetic-right-shift" - (|> {synthesis.#Extension "lux i64 arithmetic-right-shift" - (list (synthesis.i64 subject) - (synthesis.i64 param))} - (run (..safe "lux i64 arithmetic-right-shift")) - (pipe.case - {try.#Success valueT} - ("lux i64 =" - (i64.arithmetic_right_shifted param subject) - (as I64 valueT)) - - {try.#Failure _} - false) - (let [param (n.% 64 param)]))) - )))) + (all _.and + + (_.test "lux i64 arithmetic-right-shift" + (|> {synthesis.#Extension "lux i64 arithmetic-right-shift" + (list (synthesis.i64 subject) + (synthesis.i64 param))} + (run (..safe "lux i64 arithmetic-right-shift")) + (pipe.case + {try.#Success valueT} + ("lux i64 =" + (i64.arithmetic_right_shifted param subject) + (as I64 valueT)) + + {try.#Failure _} + false) + (let [param (n.% 64 param)]))) + )))) (def: (i64 run) (-> Runner Test) (do r.monad [param (|> r.i64 (r.only (|>> ("lux i64 =" 0) not))) subject r.i64] - (`` ($_ _.and - (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.i64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueT} - ( ( subject) (as valueT)) - - {try.#Failure _} - false) - (let [subject ])))] - - ["lux i64 f64" Frac i.frac f.= subject] - ["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject - (as Nat) - (n.% (i64.left_shifted 8 1)) - (as Int))] - )) - (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueT} - ( ( param subject) (as valueT)) - - {try.#Failure _} - false)))] - - ["lux i64 +" i.+ Int i.=] - ["lux i64 -" i.- Int i.=] - ["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#=] - )) - )))) + (`` (all _.and + (~~ (template [ ] + [(_.test + (|> {synthesis.#Extension (list (synthesis.i64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueT} + ( ( subject) (as valueT)) + + {try.#Failure _} + false) + (let [subject ])))] + + ["lux i64 f64" Frac i.frac f.= subject] + ["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject + (as Nat) + (n.% (i64.left_shifted 8 1)) + (as Int))] + )) + (~~ (template [ ] + [(_.test + (|> {synthesis.#Extension (list (synthesis.i64 param) + (synthesis.i64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueT} + ( ( param subject) (as valueT)) + + {try.#Failure _} + false)))] + + ["lux i64 +" i.+ Int i.=] + ["lux i64 -" i.- Int i.=] + ["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#=] + )) + )))) (def: simple_frac (Random Frac) @@ -131,53 +131,53 @@ (do r.monad [param (|> ..simple_frac (r.only (|>> (f.= +0.0) not))) subject ..simple_frac] - (`` ($_ _.and - (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe )) - (//case.verify ( param subject))))] - - ["lux f64 +" f.+ f.=] - ["lux f64 -" f.- f.=] - ["lux f64 *" f.* f.=] - ["lux f64 /" f./ f.=] - ["lux f64 %" f.% f.=] - )) - (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueV} - (bit#= ( param subject) - (as Bit valueV)) - - _ - false)))] - - ["lux f64 =" f.=] - ["lux f64 <" f.<] - )) - (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list)} - (run (..safe )) - (//case.verify )))] - - ["lux f64 min" ("lux f64 min")] - ["lux f64 max" ("lux f64 max")] - ["lux f64 smallest" ("lux f64 smallest")] - )) - (_.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"})) - (//case.verify subject))) - )))) + (`` (all _.and + (~~ (template [ ] + [(_.test + (|> {synthesis.#Extension (list (synthesis.f64 param) + (synthesis.f64 subject))} + (run (..safe )) + (//case.verify ( param subject))))] + + ["lux f64 +" f.+ f.=] + ["lux f64 -" f.- f.=] + ["lux f64 *" f.* f.=] + ["lux f64 /" f./ f.=] + ["lux f64 %" f.% f.=] + )) + (~~ (template [ ] + [(_.test + (|> {synthesis.#Extension (list (synthesis.f64 param) + (synthesis.f64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueV} + (bit#= ( param subject) + (as Bit valueV)) + + _ + false)))] + + ["lux f64 =" f.=] + ["lux f64 <" f.<] + )) + (~~ (template [ ] + [(_.test + (|> {synthesis.#Extension (list)} + (run (..safe )) + (//case.verify )))] + + ["lux f64 min" ("lux f64 min")] + ["lux f64 max" ("lux f64 max")] + ["lux f64 smallest" ("lux f64 smallest")] + )) + (_.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"})) + (//case.verify subject))) + )))) (def: (text run) (-> Runner Test) @@ -196,174 +196,174 @@ 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)} - (run (..safe "lux text =")) - (pipe.case - {try.#Success valueV} - (as Bit valueV) - - _ - false)) - (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} - (run (..safe "lux text =")) - (pipe.case - {try.#Success valueV} - (not (as Bit valueV)) - - _ - false)))) - (_.test "Can compare texts for order." - (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} - (run (..safe "lux text <")) - (pipe.case - {try.#Success valueV} - (as Bit valueV) - - {try.#Failure _} - false))) - (_.test "Can get length of text." - (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} - (run (..safe "lux text size")) - (pipe.case - {try.#Success valueV} - (n.= sample_size (as Nat valueV)) - - _ - false))) - (_.test "Can concatenate text." - (|> {synthesis.#Extension "lux text size" (list concatenatedS)} - (run (..safe "lux text size")) - (pipe.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))} - (run (..safe "lux text index")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= 0 valueV) - - _ - false)) - (|> {synthesis.#Extension "lux text index" - (list concatenatedS sample_upperS - (synthesis.i64 +0))} - (run (..safe "lux text index")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= sample_size valueV) - - _ - false)))) - (let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit) - (function (_ offset length expected) - (|> {synthesis.#Extension "lux text clip" - (list concatenatedS - (synthesis.i64 offset) - (synthesis.i64 length))} - (run (..safe "lux text clip")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Text) valueV) - {.#Some valueV}]) - (text#= expected valueV) - - _ - false))))] - (_.test "Can clip text to extract sub-text." - (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))} - (run (..safe "lux text char")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Int) valueV) - {.#Some valueV}]) - (text.contains? ("lux i64 char" valueV) - sample_lower) - - _ - false))) - ))) + (all _.and + (_.test "Can compare texts for equality." + (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)} + (run (..safe "lux text =")) + (pipe.case + {try.#Success valueV} + (as Bit valueV) + + _ + false)) + (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} + (run (..safe "lux text =")) + (pipe.case + {try.#Success valueV} + (not (as Bit valueV)) + + _ + false)))) + (_.test "Can compare texts for order." + (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} + (run (..safe "lux text <")) + (pipe.case + {try.#Success valueV} + (as Bit valueV) + + {try.#Failure _} + false))) + (_.test "Can get length of text." + (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} + (run (..safe "lux text size")) + (pipe.case + {try.#Success valueV} + (n.= sample_size (as Nat valueV)) + + _ + false))) + (_.test "Can concatenate text." + (|> {synthesis.#Extension "lux text size" (list concatenatedS)} + (run (..safe "lux text size")) + (pipe.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))} + (run (..safe "lux text index")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= 0 valueV) + + _ + false)) + (|> {synthesis.#Extension "lux text index" + (list concatenatedS sample_upperS + (synthesis.i64 +0))} + (run (..safe "lux text index")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= sample_size valueV) + + _ + false)))) + (let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit) + (function (_ offset length expected) + (|> {synthesis.#Extension "lux text clip" + (list concatenatedS + (synthesis.i64 offset) + (synthesis.i64 length))} + (run (..safe "lux text clip")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Text) valueV) + {.#Some valueV}]) + (text#= expected valueV) + + _ + false))))] + (_.test "Can clip text to extract sub-text." + (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))} + (run (..safe "lux text char")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Int) valueV) + {.#Some valueV}]) + (text.contains? ("lux i64 char" valueV) + sample_lower) + + _ + false))) + ))) (def: (io run) (-> Runner Test) (do r.monad [message (r.ascii/alpha 5)] - ($_ _.and - (_.test "Can log messages." - (|> {synthesis.#Extension "lux io log" - (list (synthesis.text (format "LOG: " message)))} - (run (..safe "lux io log")) - (pipe.case - {try.#Success valueV} - true - - {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))}]))} - (run (..safe "lux try")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Try Text) valueV) - {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)]))} - (run (..safe "lux try")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Try Text) 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)})) - (run (..safe "lux io current-time")) - (pipe.case - {try.#Success valueV} - (let [[pre post] (as [Nat Nat] valueV)] - (n.>= pre post)) - - {try.#Failure _} - false))) - ))) + (all _.and + (_.test "Can log messages." + (|> {synthesis.#Extension "lux io log" + (list (synthesis.text (format "LOG: " message)))} + (run (..safe "lux io log")) + (pipe.case + {try.#Success valueV} + true + + {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))}]))} + (run (..safe "lux try")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Try Text) valueV) + {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)]))} + (run (..safe "lux try")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Try Text) 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)})) + (run (..safe "lux io current-time")) + (pipe.case + {try.#Success valueV} + (let [[pre post] (as [Nat Nat] valueV)] + (n.>= pre post)) + + {try.#Failure _} + false))) + ))) (def: .public (spec runner) (-> Runner Test) - ($_ _.and - (..bit runner) - (..i64 runner) - (..f64 runner) - (..text runner) - (..io runner) - )) + (all _.and + (..bit runner) + (..i64 runner) + (..f64 runner) + (..text runner) + (..io runner) + )) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index e6bdf79c0..6cc0d14b5 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -1,27 +1,27 @@ (.using - [lux {"-" function} - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - ["[0]" enum]] - [control - ["[0]" maybe]] - [data - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["r" random {"+" Random} ("[1]#[0]" monad)]] - [tool - [compiler - [analysis {"+" Arity}] - ["[0]" reference {"+" Register}] - ["[0]" synthesis {"+" Synthesis}]]]] - ["[0]" // "_" - ["[1][0]" case] - [// - [common {"+" Runner}]]]) + [lux {"-" function} + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + ["[0]" enum]] + [control + ["[0]" maybe]] + [data + [number + ["n" nat]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["r" random {"+" Random} ("[1]#[0]" monad)]] + [tool + [compiler + [analysis {"+" Arity}] + ["[0]" reference {"+" Register}] + ["[0]" synthesis {"+" Synthesis}]]]] + ["[0]" // "_" + ["[1][0]" case] + [// + [common {"+" Runner}]]]) (def: max_arity Arity @@ -54,41 +54,41 @@ inputs (r.list arity r.safe_frac) .let [expectation (maybe.trusted (list.item (-- local) inputs)) inputsS (list#each (|>> synthesis.f64) inputs)]] - ($_ _.and - (_.test "Can read arguments." - (|> (synthesis.function/apply [synthesis.#function functionS - synthesis.#arguments inputsS]) - (run "with_local") - (//case.verify expectation))) - (_.test "Can partially apply functions." - (or (n.= 1 arity) - (let [preS (list.first partial_arity inputsS) - postS (list.after partial_arity inputsS) - partialS (synthesis.function/apply [synthesis.#function functionS - synthesis.#arguments preS])] - (|> (synthesis.function/apply [synthesis.#function partialS - synthesis.#arguments postS]) - (run "partial_application") - (//case.verify expectation))))) - (_.test "Can read environment." - (or (n.= 1 arity) - (let [environment (|> partial_arity - (enum.range n.enum 1) - (list#each (|>> {reference.#Local}))) - variableS (if (n.<= partial_arity local) - (synthesis.variable/foreign (-- local)) - (synthesis.variable/local (|> local (n.- partial_arity)))) - inner_arity (n.- partial_arity arity) - innerS (synthesis.function/abstraction - [synthesis.#environment environment - synthesis.#arity inner_arity - synthesis.#body variableS]) - outerS (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity partial_arity - synthesis.#body innerS])] - (|> (synthesis.function/apply [synthesis.#function outerS - synthesis.#arguments inputsS]) - (run "with_foreign") - (//case.verify expectation))))) - ))) + (all _.and + (_.test "Can read arguments." + (|> (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments inputsS]) + (run "with_local") + (//case.verify expectation))) + (_.test "Can partially apply functions." + (or (n.= 1 arity) + (let [preS (list.first partial_arity inputsS) + postS (list.after partial_arity inputsS) + partialS (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments preS])] + (|> (synthesis.function/apply [synthesis.#function partialS + synthesis.#arguments postS]) + (run "partial_application") + (//case.verify expectation))))) + (_.test "Can read environment." + (or (n.= 1 arity) + (let [environment (|> partial_arity + (enum.range n.enum 1) + (list#each (|>> {reference.#Local}))) + variableS (if (n.<= partial_arity local) + (synthesis.variable/foreign (-- local)) + (synthesis.variable/local (|> local (n.- partial_arity)))) + inner_arity (n.- partial_arity arity) + innerS (synthesis.function/abstraction + [synthesis.#environment environment + synthesis.#arity inner_arity + synthesis.#body variableS]) + outerS (synthesis.function/abstraction + [synthesis.#environment (list) + synthesis.#arity partial_arity + synthesis.#body innerS])] + (|> (synthesis.function/apply [synthesis.#function outerS + synthesis.#arguments inputsS]) + (run "with_foreign") + (//case.verify expectation))))) + ))) diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index db50dc185..46ba10d00 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -28,22 +28,22 @@ (def: .public (spec run) (-> Runner Test) - (`` ($_ _.and - (~~ (template [ ] - [(do r.monad - [expected ] - (_.test (%.symbol (symbol )) - (|> (run ( expected)) - (pipe.case - {try.#Success actual} - ( expected (as_expected actual)) + (`` (all _.and + (~~ (template [ ] + [(do r.monad + [expected ] + (_.test (%.symbol (symbol )) + (|> (run ( expected)) + (pipe.case + {try.#Success actual} + ( expected (as_expected actual)) - {try.#Failure _} - false))))] + {try.#Failure _} + false))))] - ["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#=] - )) - ))) + ["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#=] + )) + ))) diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index 687c3ef88..f9d5e3ec9 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -57,6 +57,6 @@ (def: .public (spec runner definer) (-> Runner Definer Test) - ($_ _.and - (..definition definer) - (..variable runner))) + (all _.and + (..definition definer) + (..variable runner))) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index b7cf6423d..4423a85bf 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -85,7 +85,7 @@ (def: .public (spec runner) (-> Runner Test) - ($_ _.and - (..variant runner) - (..tuple runner) - )) + (all _.and + (..variant runner) + (..tuple runner) + )) diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux index fb4ddd758..461f304c3 100644 --- a/stdlib/source/specification/lux/abstract/apply.lux +++ b/stdlib/source/specification/lux/abstract/apply.lux @@ -69,9 +69,9 @@ (def: .public (spec injection comparison apply) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (_.for [/.Apply] - ($_ _.and - (..identity injection comparison apply) - (..homomorphism injection comparison apply) - (..interchange injection comparison apply) - (..composition injection comparison apply) - ))) + (all _.and + (..identity injection comparison apply) + (..homomorphism injection comparison apply) + (..interchange injection comparison apply) + (..composition injection comparison apply) + ))) diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index 6147cff90..dca713ac2 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -54,8 +54,8 @@ (def: .public (spec injection comparison subject) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) (<| (_.for [/.CoMonad]) - ($_ _.and - (..left_identity injection subject) - (..right_identity injection comparison subject) - (..associativity injection comparison subject) - ))) + (all _.and + (..left_identity injection subject) + (..right_identity injection comparison subject) + (..associativity injection comparison subject) + ))) diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux index c2feb2a3f..bff39db70 100644 --- a/stdlib/source/specification/lux/abstract/enum.lux +++ b/stdlib/source/specification/lux/abstract/enum.lux @@ -14,14 +14,14 @@ (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)))) - )))) + (all _.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)))) + )))) diff --git a/stdlib/source/specification/lux/abstract/equivalence.lux b/stdlib/source/specification/lux/abstract/equivalence.lux index 386fafc8d..892d77524 100644 --- a/stdlib/source/specification/lux/abstract/equivalence.lux +++ b/stdlib/source/specification/lux/abstract/equivalence.lux @@ -17,8 +17,8 @@ [left random right random] (<| (_.for [/.Equivalence]) - ($_ _.and - (_.test "Reflexivity" - (/#= left left)) - (_.test "Symmetry" - (bit#= (/#= left right) (/#= right left))))))) + (all _.and + (_.test "Reflexivity" + (/#= left left)) + (_.test "Symmetry" + (bit#= (/#= left right) (/#= right left))))))) diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux index b82a0c83d..f5b3a6205 100644 --- a/stdlib/source/specification/lux/abstract/functor.lux +++ b/stdlib/source/specification/lux/abstract/functor.lux @@ -55,8 +55,8 @@ (def: .public (spec injection comparison functor) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (<| (_.for [/.Functor]) - ($_ _.and - (..identity injection comparison functor) - (..homomorphism injection comparison functor) - (..composition injection comparison functor) - ))) + (all _.and + (..identity injection comparison functor) + (..homomorphism injection comparison functor) + (..composition injection comparison functor) + ))) diff --git a/stdlib/source/specification/lux/abstract/functor/contravariant.lux b/stdlib/source/specification/lux/abstract/functor/contravariant.lux index 8f379472e..0fca98448 100644 --- a/stdlib/source/specification/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/specification/lux/abstract/functor/contravariant.lux @@ -26,6 +26,6 @@ (do random.monad [sample random.nat] (<| (_.for [/.Functor]) - ($_ _.and - (..identity equivalence value functor) - )))) + (all _.and + (..identity equivalence value functor) + )))) diff --git a/stdlib/source/specification/lux/abstract/interval.lux b/stdlib/source/specification/lux/abstract/interval.lux index 3fada2cf8..4ea7ca50e 100644 --- a/stdlib/source/specification/lux/abstract/interval.lux +++ b/stdlib/source/specification/lux/abstract/interval.lux @@ -15,9 +15,9 @@ (<| (_.for [/.Interval]) (do random.monad [sample gen_sample] - ($_ _.and - (_.test "No value is bigger than the top." - (@//< @//top sample)) - (_.test "No value is smaller than the bottom." - (order.> @//order @//bottom sample)) - )))) + (all _.and + (_.test "No value is bigger than the top." + (@//< @//top sample)) + (_.test "No value is smaller than the bottom." + (order.> @//order @//bottom sample)) + )))) diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index fe14440fd..e42b0dbdf 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -50,8 +50,8 @@ (def: .public (spec injection comparison monad) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (<| (_.for [/.Monad]) - ($_ _.and - (..left_identity injection comparison monad) - (..right_identity injection comparison monad) - (..associativity injection comparison monad) - ))) + (all _.and + (..left_identity injection comparison monad) + (..right_identity injection comparison monad) + (..associativity injection comparison monad) + ))) diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux index 6d5ab67fc..f6daaa867 100644 --- a/stdlib/source/specification/lux/abstract/monoid.lux +++ b/stdlib/source/specification/lux/abstract/monoid.lux @@ -19,14 +19,14 @@ mid gen_sample right gen_sample] (<| (_.for [/.Monoid]) - ($_ _.and - (_.test "Left identity." - (_#= sample - (_#composite _#identity sample))) - (_.test "Right identity." - (_#= sample - (_#composite sample _#identity))) - (_.test "Associativity." - (_#= (_#composite left (_#composite mid right)) - (_#composite (_#composite left mid) right))) - )))) + (all _.and + (_.test "Left identity." + (_#= sample + (_#composite _#identity sample))) + (_.test "Right identity." + (_#= sample + (_#composite sample _#identity))) + (_.test "Associativity." + (_#= (_#composite left (_#composite mid right)) + (_#composite (_#composite left mid) right))) + )))) diff --git a/stdlib/source/specification/lux/abstract/order.lux b/stdlib/source/specification/lux/abstract/order.lux index 1c77ffc3b..e6e85a1e8 100644 --- a/stdlib/source/specification/lux/abstract/order.lux +++ b/stdlib/source/specification/lux/abstract/order.lux @@ -12,47 +12,47 @@ (def: .public (spec (open "@//[0]") generator) (All (_ a) (-> (/.Order a) (Random a) Test)) (<| (_.for [/.Order]) - ($_ _.and - (do random.monad - [parameter generator - subject generator] - (_.test "Values are either ordered, or they are equal. All options(_ are mutually exclusive." - (cond (@//< parameter subject) - (not (or (@//< subject parameter) - (@//= parameter subject))) + (all _.and + (do random.monad + [parameter generator + subject generator] + (_.test "Values are either ordered, or they are equal. All options(_ are mutually exclusive." + (cond (@//< parameter subject) + (not (or (@//< subject parameter) + (@//= parameter subject))) - (@//< subject parameter) - (not (@//= parameter subject)) + (@//< subject parameter) + (not (@//= parameter subject)) - ... else - (@//= parameter subject)))) - (do random.monad - [parameter generator - subject (random.only (|>> (@//= parameter) not) - generator) - extra (random.only (function (_ value) - (not (or (@//= parameter value) - (@//= subject value)))) - generator)] - (_.test "Transitive property." - (if (@//< parameter subject) - (let [greater? (and (@//< subject extra) - (@//< parameter extra)) - lesser? (and (@//< extra parameter) - (@//< extra subject)) - in_between? (and (@//< parameter extra) - (@//< extra subject))] - (or greater? - lesser? - in_between?)) - ... (@//< subject parameter) - (let [greater? (and (@//< extra subject) - (@//< extra parameter)) - lesser? (and (@//< parameter extra) - (@//< subject extra)) - in_between? (and (@//< subject extra) - (@//< extra parameter))] - (or greater? - lesser? - in_between?))))) - ))) + ... else + (@//= parameter subject)))) + (do random.monad + [parameter generator + subject (random.only (|>> (@//= parameter) not) + generator) + extra (random.only (function (_ value) + (not (or (@//= parameter value) + (@//= subject value)))) + generator)] + (_.test "Transitive property." + (if (@//< parameter subject) + (let [greater? (and (@//< subject extra) + (@//< parameter extra)) + lesser? (and (@//< extra parameter) + (@//< extra subject)) + in_between? (and (@//< parameter extra) + (@//< extra subject))] + (or greater? + lesser? + in_between?)) + ... (@//< subject parameter) + (let [greater? (and (@//< extra subject) + (@//< extra parameter)) + lesser? (and (@//< parameter extra) + (@//< subject extra)) + in_between? (and (@//< subject extra) + (@//< extra parameter))] + (or greater? + lesser? + in_between?))))) + ))) diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux index 1e1d5f557..d4a0e591d 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -39,21 +39,21 @@ in (do async.monad [fs (async.future fs)] - ($_ _.and' - (_.cover' [/.rooted] - (let [path (/.rooted fs parent child)] - (and (text.starts_with? parent path) - (text.ends_with? child path)))) - (_.cover' [/.parent] - (|> (/.rooted fs parent child) - (/.parent fs) - (maybe#each (text#= parent)) - (maybe.else false))) - (_.cover' [/.name] - (|> (/.rooted fs parent child) - (/.name fs) - (text#= child))) - )))) + (all _.and' + (_.cover' [/.rooted] + (let [path (/.rooted fs parent child)] + (and (text.starts_with? parent path) + (text.ends_with? child path)))) + (_.cover' [/.parent] + (|> (/.rooted fs parent child) + (/.parent fs) + (maybe#each (text#= parent)) + (maybe.else false))) + (_.cover' [/.name] + (|> (/.rooted fs parent child) + (/.name fs) + (text#= child))) + )))) (def: (directory?&make_directory fs parent) (-> (/.System Async) /.Path (Async Bit)) @@ -226,31 +226,31 @@ cannot_make_directory!/0 (/.make_directories ! fs "") cannot_make_directory!/1 (/.make_directories ! fs (# fs separator))]) - ($_ _.and' - (_.cover' [/.make_directories] - (and (not pre_dir/0) - (not pre_dir/1) - (not pre_dir/2) - (case made? - {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 _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_directory error)) - (case cannot_make_directory!/1 - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_directory error)))) - ))) + (all _.and' + (_.cover' [/.make_directories] + (and (not pre_dir/0) + (not pre_dir/1) + (not pre_dir/2) + (case made? + {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 _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_directory error)) + (case cannot_make_directory!/1 + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_directory error)))) + ))) (def: (make_file&cannot_make_file fs) (-> (IO (/.System Async)) Test) @@ -261,26 +261,26 @@ [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)]) - ($_ _.and' - (_.cover' [/.make_file] - (case make_file!/0 - {try.#Success _} true - {try.#Failure error} false)) - (_.cover' [/.cannot_make_file] - (case make_file!/1 - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_file error))) - ))) + (all _.and' + (_.cover' [/.make_file] + (case make_file!/0 + {try.#Success _} true + {try.#Failure error} false)) + (_.cover' [/.cannot_make_file] + (case make_file!/1 + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_file error))) + ))) (def: (for_utilities fs) (-> (IO (/.System Async)) Test) - ($_ _.and - (..make_directories&cannot_make_directory fs) - (..make_file&cannot_make_file fs) - )) + (all _.and + (..make_directories&cannot_make_directory fs) + (..make_file&cannot_make_file fs) + )) (def: (exists? fs) (-> (IO (/.System Async)) Test) @@ -324,9 +324,9 @@ (def: .public (spec fs) (-> (IO (/.System Async)) Test) - ($_ _.and - (..for_path fs) - (..for_utilities fs) - (..for_system fs) - (..exists? fs) - )) + (all _.and + (..for_path fs) + (..for_utilities fs) + (..for_system fs) + (..exists? fs) + )) diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux index 9d18afee2..30c061ca3 100644 --- a/stdlib/source/specification/lux/world/shell.lux +++ b/stdlib/source/specification/lux/world/shell.lux @@ -80,12 +80,12 @@ (do ! [can_read! (..can_read! message echo) can_destroy! (..can_destroy! sleep)] - ($_ _.and' - (_.cover' - (and can_read! - can_destroy!)) - (..can_wait! echo) - )) + (all _.and' + (_.cover' + (and can_read! + can_destroy!)) + (..can_wait! echo) + )) _ (_.cover' -- cgit v1.2.3