From 04c7f49a732380a2b9f72b1b937171b341c24323 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 9 Apr 2022 03:03:46 -0400 Subject: Better names for testing macros (plus better indentation). --- .../specification/compositor/analysis/type.lux | 8 +- .../specification/compositor/generation/case.lux | 110 +++--- .../specification/compositor/generation/common.lux | 412 ++++++++++----------- .../compositor/generation/function.lux | 70 ++-- .../compositor/generation/primitive.lux | 14 +- .../compositor/generation/reference.lux | 34 +- .../compositor/generation/structure.lux | 76 ++-- 7 files changed, 362 insertions(+), 362 deletions(-) (limited to 'stdlib/source/specification/compositor') diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux index 5f2820ba2..2cbc93cea 100644 --- a/stdlib/source/specification/compositor/analysis/type.lux +++ b/stdlib/source/specification/compositor/analysis/type.lux @@ -57,8 +57,8 @@ [[typeC exprT exprC] ..check [other_typeC other_exprT other_exprC] ..check] (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)) + (_.property "lux check" + (check_success+ expander state "lux check" (list typeC exprC) exprT)) + (_.property "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 12fa81a14..1e5502e17 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -101,12 +101,12 @@ (-> Runner Test) (do r.monad [value r.safe_frac] - (_.test (%.symbol (symbol synthesis.branch/let)) - (|> (synthesis.branch/let [(synthesis.f64 value) - 0 - (synthesis.variable/local 0)]) - (run "let_spec") - (verify value))))) + (_.property (%.symbol (symbol synthesis.branch/let)) + (|> (synthesis.branch/let [(synthesis.f64 value) + 0 + (synthesis.variable/local 0)]) + (run "let_spec") + (verify value))))) (def: (if_spec run) (-> Runner Test) @@ -114,12 +114,12 @@ [on_true r.safe_frac on_false (|> r.safe_frac (r.only (|>> (f.= on_true) not))) verdict r.bit] - (_.test (%.symbol (symbol synthesis.branch/if)) - (|> (synthesis.branch/if [(synthesis.bit verdict) - (synthesis.f64 on_true) - (synthesis.f64 on_false)]) - (run "if_spec") - (verify (if verdict on_true on_false)))))) + (_.property (%.symbol (symbol synthesis.branch/if)) + (|> (synthesis.branch/if [(synthesis.bit verdict) + (synthesis.f64 on_true) + (synthesis.f64 on_false)]) + (run "if_spec") + (verify (if verdict on_true on_false)))))) (def: (case_spec run) (-> Runner Test) @@ -127,16 +127,16 @@ [[inputS pathS] ..case on_success r.safe_frac on_failure (|> r.safe_frac (r.only (|>> (f.= on_success) not)))] - (_.test (%.symbol (symbol synthesis.branch/case)) - (|> (synthesis.branch/case - [inputS - (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))))) + (_.property (%.symbol (symbol synthesis.branch/case)) + (|> (synthesis.branch/case + [inputS + (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))))) (def: special_input Synthesis @@ -243,39 +243,39 @@ (def: (special_spec run) (-> Runner Test) (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))) + (_.property "===" + (and (text#= (synthesis.%path special_path) + (synthesis.%path special_pattern_path)) + (# synthesis.path_equivalence = special_path special_pattern_path))) + (_.property "CODE" + (|> special_input + (run "special_input") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.property "PATTERN_MATCHING 0" + (|> (synthesis.branch/case [special_input + special_path]) + (run "special_path") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.property "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) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 77854d953..e93a46c29 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -40,17 +40,17 @@ [param r.i64 subject r.i64] (with_expansions [ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueT} - (n.= ( param subject) (as Nat valueT)) - - {try.#Failure _} - false) - (let [param ])))] + [(_.property + (|> {synthesis.#Extension (list (synthesis.i64 param) + (synthesis.i64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueT} + (n.= ( param subject) (as Nat valueT)) + + {try.#Failure _} + false) + (let [param ])))] ["lux i64 and" i64.and param] ["lux i64 or" i64.or param] @@ -60,20 +60,20 @@ )] (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)]))) + (_.property "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) @@ -83,16 +83,16 @@ subject r.i64] (`` (all _.and (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.i64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueT} - ( ( subject) (as valueT)) + [(_.property + (|> {synthesis.#Extension (list (synthesis.i64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueT} + ( ( subject) (as valueT)) - {try.#Failure _} - false) - (let [subject ])))] + {try.#Failure _} + false) + (let [subject ])))] ["lux i64 f64" Frac i.frac f.= subject] ["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject @@ -101,16 +101,16 @@ (as Int))] )) (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe )) - (pipe.case - {try.#Success valueT} - ( ( param subject) (as valueT)) + [(_.property + (|> {synthesis.#Extension (list (synthesis.i64 param) + (synthesis.i64 subject))} + (run (..safe )) + (pipe.case + {try.#Success valueT} + ( ( param subject) (as valueT)) - {try.#Failure _} - false)))] + {try.#Failure _} + false)))] ["lux i64 +" i.+ Int i.=] ["lux i64 -" i.- Int i.=] @@ -133,11 +133,11 @@ subject ..simple_frac] (`` (all _.and (~~ (template [ ] - [(_.test - (|> {synthesis.#Extension (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe )) - (//case.verify ( param subject))))] + [(_.property + (|> {synthesis.#Extension (list (synthesis.f64 param) + (synthesis.f64 subject))} + (run (..safe )) + (//case.verify ( param subject))))] ["lux f64 +" f.+ f.=] ["lux f64 -" f.- f.=] @@ -146,37 +146,37 @@ ["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)))] + [(_.property + (|> {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 )))] + [(_.property + (|> {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))) + (_.property "'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) @@ -197,75 +197,75 @@ 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))]] (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)))) + (_.property "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)))) + (_.property "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))) + (_.property "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))) + (_.property "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))) + (_.property "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" @@ -281,23 +281,23 @@ _ 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))) + (_.property "Can clip text to extract sub-text." + (and (test_clip 0 sample_size sample_lower) + (test_clip sample_size sample_size sample_upper)))) + (_.property "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) @@ -305,57 +305,57 @@ (do r.monad [message (r.alphabetic 5)] (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))) + (_.property "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))) + (_.property "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)))) + (_.property "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) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index 6cc0d14b5..33db49436 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -55,40 +55,40 @@ .let [expectation (maybe.trusted (list.item (-- local) inputs)) inputsS (list#each (|>> synthesis.f64) inputs)]] (all _.and - (_.test "Can read arguments." - (|> (synthesis.function/apply [synthesis.#function functionS + (_.property "Can read arguments." + (|> (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments inputsS]) + (run "with_local") + (//case.verify expectation))) + (_.property "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))))) + (_.property "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_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))))) + (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 46ba10d00..d79b226c3 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -32,14 +32,14 @@ (~~ (template [ ] [(do r.monad [expected ] - (_.test (%.symbol (symbol )) - (|> (run ( expected)) - (pipe.case - {try.#Success actual} - ( expected (as_expected actual)) + (_.property (%.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 ="] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index df9482058..f0893573f 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -29,31 +29,31 @@ (do r.monad [name ..symbol expected r.safe_frac] - (_.test "Definitions." - (|> (define name (synthesis.f64 expected)) - (pipe.case - {try.#Success actual} - (f.= expected (as Frac actual)) + (_.property "Definitions." + (|> (define name (synthesis.f64 expected)) + (pipe.case + {try.#Success actual} + (f.= expected (as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (variable run) (-> Runner Test) (do [! r.monad] [register (|> r.nat (# ! each (n.% 100))) expected r.safe_frac] - (_.test "Local variables." - (|> (synthesis.branch/let [(synthesis.f64 expected) - register - (synthesis.variable/local register)]) - (run "variable") - (pipe.case - {try.#Success actual} - (f.= expected (as Frac actual)) + (_.property "Local variables." + (|> (synthesis.branch/let [(synthesis.f64 expected) + register + (synthesis.variable/local register)]) + (run "variable") + (pipe.case + {try.#Success actual} + (f.= expected (as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner definer) (-> Runner Definer Test) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index 4423a85bf..3080f6abd 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -35,53 +35,53 @@ tag_in (|> r.nat (# ! each (n.% num_tags))) .let [last?_in (|> num_tags -- (n.= tag_in))] value_in r.i64] - (_.test (%.symbol (symbol synthesis.variant)) - (|> (synthesis.variant [analysis.#lefts (if last?_in - (-- tag_in) - tag_in) - analysis.#right? last?_in - analysis.#value (synthesis.i64 value_in)]) - (run "variant") - (pipe.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))) - last?_out (array.read! 1 valueT) - 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'} - (and last?_in (text#= "" (as Text last?_out'))) + (_.property (%.symbol (symbol synthesis.variant)) + (|> (synthesis.variant [analysis.#lefts (if last?_in + (-- tag_in) + tag_in) + analysis.#right? last?_in + analysis.#value (synthesis.i64 value_in)]) + (run "variant") + (pipe.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))) + last?_out (array.read! 1 valueT) + 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'} + (and last?_in (text#= "" (as Text last?_out'))) - {.#None} - (not last?_in)) - same_value? (|> value_out (as Int) (i.= value_in))] - (and same_tag? - same_flag? - same_value?)))) + {.#None} + (not last?_in)) + same_value? (|> value_out (as Int) (i.= value_in))] + (and same_tag? + same_flag? + same_value?)))) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (tuple run) (-> Runner Test) (do [! r.monad] [size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) tuple_in (r.list size r.i64)] - (_.test (%.symbol (symbol synthesis.tuple)) - (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) - (run "tuple") - (pipe.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))))) + (_.property (%.symbol (symbol synthesis.tuple)) + (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) + (run "tuple") + (pipe.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 _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner) (-> Runner Test) -- cgit v1.2.3