diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/test/lux/target/ruby.lux | 1442 |
1 files changed, 721 insertions, 721 deletions
diff --git a/stdlib/source/test/lux/target/ruby.lux b/stdlib/source/test/lux/target/ruby.lux index 22dee2512..b3324189d 100644 --- a/stdlib/source/test/lux/target/ruby.lux +++ b/stdlib/source/test/lux/target/ruby.lux @@ -64,45 +64,45 @@ float random.frac int random.int string (random.ascii/upper 5)] - ($_ _.and - (_.cover [/.nil] - (..nil /.nil)) - (_.cover [/.bool] - (expression (|>> (as Bit) (bit#= bool)) - (/.bool bool))) - (_.cover [/.int] - (expression (|>> (as Int) (i.= int)) - (/.int int))) - (_.cover [/.float] - (expression (|>> (as Frac) (f.= float)) - (/.float float))) - (_.cover [/.string] - (expression (|>> (as Text) (text#= string)) - (/.string string))) - (_.cover [/.symbol] - (expression (|>> (as Text) (text#= string)) - (/.do "id2name" (list) {.#None} (/.symbol string)))) - ))) + (all _.and + (_.cover [/.nil] + (..nil /.nil)) + (_.cover [/.bool] + (expression (|>> (as Bit) (bit#= bool)) + (/.bool bool))) + (_.cover [/.int] + (expression (|>> (as Int) (i.= int)) + (/.int int))) + (_.cover [/.float] + (expression (|>> (as Frac) (f.= float)) + (/.float float))) + (_.cover [/.string] + (expression (|>> (as Text) (text#= string)) + (/.string string))) + (_.cover [/.symbol] + (expression (|>> (as Text) (text#= string)) + (/.do "id2name" (list) {.#None} (/.symbol string)))) + ))) (def: test|bool Test (do [! random.monad] [left random.bit right random.bit] - (`` ($_ _.and - (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.bool left) (/.bool right)))))] + (`` (all _.and + (~~ (template [</> <lux>] + [(_.cover [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.bool left) (/.bool right)))))] - [/.or .or] - [/.and .and] - )) - (_.cover [/.not] - (expression (|>> (as Bit) (bit#= (not left))) - (/.not (/.bool left)))) - )))) + [/.or .or] + [/.and .and] + )) + (_.cover [/.not] + (expression (|>> (as Bit) (bit#= (not left))) + (/.not (/.bool left)))) + )))) (def: test|float Test @@ -110,33 +110,33 @@ [parameter (random.only (|>> (f.= +0.0) not) random.safe_frac) subject random.safe_frac] - (`` ($_ _.and - (~~ (template [</> <lux> <pre>] - [(_.cover [</>] - (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (as Frac) (f.= expected)) - (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] + (`` (all _.and + (~~ (template [</> <lux> <pre>] + [(_.cover [</>] + (let [expected (<lux> (<pre> parameter) (<pre> subject))] + (expression (|>> (as Frac) (f.= expected)) + (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] - [/.+ f.+ |>] - [/.- f.- |>] - [/.* f.* |>] - [/./ f./ |>] - [/.% f.mod |>] - [/.pow f.pow f.abs] - )) - (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.float parameter) (/.float subject)))))] + [/.+ f.+ |>] + [/.- f.- |>] + [/.* f.* |>] + [/./ f./ |>] + [/.% f.mod |>] + [/.pow f.pow f.abs] + )) + (~~ (template [</> <lux>] + [(_.cover [</>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.float parameter) (/.float subject)))))] - [/.< f.<] - [/.<= f.<=] - [/.> f.>] - [/.>= f.>=] - [/.= f.=] - )) - )))) + [/.< f.<] + [/.<= f.<=] + [/.> f.>] + [/.>= f.>=] + [/.= f.=] + )) + )))) (def: int_16 (-> Int Int) @@ -150,34 +150,34 @@ i16 (# ! each ..int_16 random.int) shift (# ! each (n.% 16) random.nat)] - (`` ($_ _.and - (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Frac) f.int (i.= expected)) - (</> (/.int left) (/.int right)))))] + (`` (all _.and + (~~ (template [</> <lux>] + [(_.cover [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Frac) f.int (i.= expected)) + (</> (/.int left) (/.int right)))))] - [/.bit_or i64.or] - [/.bit_xor i64.xor] - [/.bit_and i64.and] - )) - (_.cover [/.bit_not] - (expression (|>> (as Int) (i.= (i64.not left))) - (/.bit_not (/.int left)))) - (_.cover [/.opposite] - (expression (|>> (as Int) (i.= (i.* -1 left))) - (/.opposite (/.int left)))) - (_.cover [/.bit_shl] - (let [expected (i64.left_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shl (/.int (.int shift)) - (/.int i16))))) - (_.cover [/.bit_shr] - (let [expected (i.right_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shr (/.int (.int shift)) - (/.int i16))))) - )))) + [/.bit_or i64.or] + [/.bit_xor i64.xor] + [/.bit_and i64.and] + )) + (_.cover [/.bit_not] + (expression (|>> (as Int) (i.= (i64.not left))) + (/.bit_not (/.int left)))) + (_.cover [/.opposite] + (expression (|>> (as Int) (i.= (i.* -1 left))) + (/.opposite (/.int left)))) + (_.cover [/.bit_shl] + (let [expected (i64.left_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shl (/.int (.int shift)) + (/.int i16))))) + (_.cover [/.bit_shr] + (let [expected (i.right_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shr (/.int (.int shift)) + (/.int i16))))) + )))) (def: test|array Test @@ -192,21 +192,21 @@ plus (# ! each (n.% (n.- from size)) random.nat) .let [to (/.int (.int (n.+ plus from))) from (/.int (.int from))]] - ($_ _.and - (_.cover [/.array /.item] - (and (expression (|>> (as Frac) (f.= expected)) - (/.item (/.int (.int index)) - (/.array (list#each /.float items)))) - (expression (|>> (as Bit)) - (|> (/.array (list#each /.float items)) - (/.item (/.int (.int size))) - (/.= /.nil))))) - (_.cover [/.array_range] - (expression (|>> (as Int) (i.= (.int (++ plus)))) - (|> (/.array (list#each /.float items)) - (/.array_range from to) - (/.the "length")))) - ))) + (all _.and + (_.cover [/.array /.item] + (and (expression (|>> (as Frac) (f.= expected)) + (/.item (/.int (.int index)) + (/.array (list#each /.float items)))) + (expression (|>> (as Bit)) + (|> (/.array (list#each /.float items)) + (/.item (/.int (.int size))) + (/.= /.nil))))) + (_.cover [/.array_range] + (expression (|>> (as Int) (i.= (.int (++ plus)))) + (|> (/.array (list#each /.float items)) + (/.array_range from to) + (/.the "length")))) + ))) (def: test|hash Test @@ -217,15 +217,15 @@ (random.ascii/upper 5)) .let [field (/.string field) dummy (/.string dummy)]] - ($_ _.and - (_.cover [/.hash] - (and (expression (|>> (as Frac) (f.= expected)) - (/.item field (/.hash (list [field (/.float expected)])))) - (expression (|>> (as Bit)) - (|> (/.hash (list [field (/.float expected)])) - (/.item dummy) - (/.= /.nil))))) - ))) + (all _.and + (_.cover [/.hash] + (and (expression (|>> (as Frac) (f.= expected)) + (/.item field (/.hash (list [field (/.float expected)])))) + (expression (|>> (as Bit)) + (|> (/.hash (list [field (/.float expected)])) + (/.item dummy) + (/.= /.nil))))) + ))) (def: test|object Test @@ -249,83 +249,83 @@ single random.safe_frac .let [double (/.function $method/0 (list $arg/0) (/.return (/.+ $arg/0 $arg/0)))]] - ($_ _.and - (_.cover [/.the] - (expression (|>> (as Int) (i.= (.int size))) - (|> (/.array (list#each /.float items)) - (/.the "length")))) - (_.cover [/.do] - (expression (let [expected (|> items - (list.item index) - (maybe.else f.not_a_number))] - (|>> (as Frac) (f.= expected))) - (|> (/.array (list#each /.float items)) - (/.do "at" (list (/.int (.int index))) {.#None})))) - (_.cover [/.class] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body double])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.new /.initialize] - (expression (|>> (as Frac) (f.= single)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body ($_ /.then - (/.function /.initialize (list $arg/0) - (/.set (list $state) $arg/0)) - (/.function $method/0 (list) - (/.return $state)) - )])) - (/.return (|> $class - (/.new (list (/.float single)) {.#None}) - (/.do (/.code $method/0) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.alias_method/2] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body ($_ /.then - double - (/.statement (/.alias_method/2 (/.string (/.code $method/1)) - (/.string (/.code $method/0)))))])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method/1) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.for [/.module] - ($_ _.and - (_.cover [/.include/1] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> ($_ /.then - (/.set (list $class) (/.module [/.#parameters (list) - /.#body double])) - (/.set (list $sub_class) (/.class [/.#parameters (list) - /.#body (/.statement (/.include/1 $class))])) - (/.return (|> $sub_class - (/.new (list) {.#None}) - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.extend/1] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> ($_ /.then - (/.set (list $class) (/.module [/.#parameters (list) - /.#body double])) - (/.set (list $sub_class) (/.class [/.#parameters (list) - /.#body (/.statement (/.extend/1 $class))])) - (/.return (|> $sub_class - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - )) - ))) + (all _.and + (_.cover [/.the] + (expression (|>> (as Int) (i.= (.int size))) + (|> (/.array (list#each /.float items)) + (/.the "length")))) + (_.cover [/.do] + (expression (let [expected (|> items + (list.item index) + (maybe.else f.not_a_number))] + (|>> (as Frac) (f.= expected))) + (|> (/.array (list#each /.float items)) + (/.do "at" (list (/.int (.int index))) {.#None})))) + (_.cover [/.class] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body double])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.new /.initialize] + (expression (|>> (as Frac) (f.= single)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.function /.initialize (list $arg/0) + (/.set (list $state) $arg/0)) + (/.function $method/0 (list) + (/.return $state)) + )])) + (/.return (|> $class + (/.new (list (/.float single)) {.#None}) + (/.do (/.code $method/0) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.alias_method/2] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + double + (/.statement (/.alias_method/2 (/.string (/.code $method/1)) + (/.string (/.code $method/0)))))])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method/1) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.for [/.module] + (all _.and + (_.cover [/.include/1] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.module [/.#parameters (list) + /.#body double])) + (/.set (list $sub_class) (/.class [/.#parameters (list) + /.#body (/.statement (/.include/1 $class))])) + (/.return (|> $sub_class + (/.new (list) {.#None}) + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.extend/1] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.module [/.#parameters (list) + /.#body double])) + (/.set (list $sub_class) (/.class [/.#parameters (list) + /.#body (/.statement (/.extend/1 $class))])) + (/.return (|> $sub_class + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + )) + ))) (def: test|io Test @@ -336,66 +336,66 @@ $new (# ! each /.local (random.ascii/upper 2)) $it (# ! each /.local (random.ascii/upper 3)) .let [expected (format left right)]]) - ($_ _.and - (_.for [/.stdout] - ($_ _.and - (_.cover [/.print/1] - (expression (|>> (as Text) (text#= expected)) - (|> ($_ /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdout) - (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) - (/.set (list /.stdout) $new) - (/.statement (/.print/1 (/.string left))) - (/.statement (/.print/1 (/.string right))) - (/.set (list /.stdout) $old) - (/.return (/.the "string" $new))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.print/2] - (expression (|>> (as Text) (text#= expected)) - (|> ($_ /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdout) - (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) - (/.set (list /.stdout) $new) - (/.statement (/.print/2 (/.string left) (/.string right))) - (/.set (list /.stdout) $old) - (/.return (/.the "string" $new))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - )) - (_.for [/.stdin] - ($_ _.and - (_.cover [/.gets/0] - (expression (|>> (as Text) (text#= (format left text.\n))) - (|> ($_ /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdin) - (/.set (list /.stdin) (/.new (list (/.string (format left text.\n))) {.#None} - (/.manual "StringIO"))) - (/.set (list $it) /.gets/0) - (/.set (list /.stdin) $old) - (/.return $it)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_string_read] - (expression (|>> (as Text) (text#= (format right text.\n))) - (|> ($_ /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdin) - (/.set (list /.stdin) (/.new (list (/.string (format right text.\n))) {.#None} - (/.manual "StringIO"))) - (/.set (list $it) /.gets/0) - (/.set (list /.stdin) $old) - (/.return /.last_string_read)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_line_number_read] - (expression (|>> (as Nat) (n.= 2)) - /.last_line_number_read)) - )) - ))) + (all _.and + (_.for [/.stdout] + (all _.and + (_.cover [/.print/1] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdout) + (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) + (/.set (list /.stdout) $new) + (/.statement (/.print/1 (/.string left))) + (/.statement (/.print/1 (/.string right))) + (/.set (list /.stdout) $old) + (/.return (/.the "string" $new))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.print/2] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdout) + (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) + (/.set (list /.stdout) $new) + (/.statement (/.print/2 (/.string left) (/.string right))) + (/.set (list /.stdout) $old) + (/.return (/.the "string" $new))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + )) + (_.for [/.stdin] + (all _.and + (_.cover [/.gets/0] + (expression (|>> (as Text) (text#= (format left text.\n))) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdin) + (/.set (list /.stdin) (/.new (list (/.string (format left text.\n))) {.#None} + (/.manual "StringIO"))) + (/.set (list $it) /.gets/0) + (/.set (list /.stdin) $old) + (/.return $it)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.last_string_read] + (expression (|>> (as Text) (text#= (format right text.\n))) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdin) + (/.set (list /.stdin) (/.new (list (/.string (format right text.\n))) {.#None} + (/.manual "StringIO"))) + (/.set (list $it) /.gets/0) + (/.set (list /.stdin) $old) + (/.return /.last_string_read)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.last_line_number_read] + (expression (|>> (as Nat) (n.= 2)) + /.last_line_number_read)) + )) + ))) (def: test|computation Test @@ -409,25 +409,25 @@ string (random.ascii/upper 5) comment (random.ascii/upper 10)] - ($_ _.and - ..test|bool - ..test|float - ..test|int - ..test|array - ..test|hash - ..test|object - ..test|io - (_.cover [/.?] - (let [expected (if test then else)] - (expression (|>> (as Frac) (f.= expected)) - (/.? (/.bool test) - (/.float then) - (/.float else))))) - (_.cover [/.comment] - (expression (|>> (as Frac) (f.= then)) - (/.comment comment - (/.float then)))) - ))) + (all _.and + ..test|bool + ..test|float + ..test|int + ..test|array + ..test|hash + ..test|object + ..test|io + (_.cover [/.?] + (let [expected (if test then else)] + (expression (|>> (as Frac) (f.= expected)) + (/.? (/.bool test) + (/.float then) + (/.float else))))) + (_.cover [/.comment] + (expression (|>> (as Frac) (f.= then)) + (/.comment comment + (/.float then)))) + ))) (def: test|global Test @@ -435,73 +435,73 @@ [float/0 random.safe_frac $global (# ! each /.global (random.ascii/lower 10)) pattern (# ! each /.string (random.ascii/lower 11))] - ($_ _.and - (_.cover [/.global] - (expression (|>> (as Text) (text#= "global-variable")) - (|> ($_ /.then - (/.set (list $global) (/.float float/0)) - (/.return (/.defined?/1 $global))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.script_name] - (expression (let [file (format (# file.default separator) packager.main_file)] - (|>> (as Text) - (text.ends_with? file))) - /.script_name)) - (_.cover [/.input_record_separator] - (expression (|>> (as Text) - (text#= text.\n)) - /.input_record_separator)) - (_.cover [/.output_record_separator] - (..nil /.output_record_separator)) - (_.cover [/.process_id] - (expression (|>> (as Nat) (n.= 0) not) - /.process_id)) - (_.cover [/.case_insensitivity_flag] - (expression (|>> (as Bit) (bit#= false)) - /.case_insensitivity_flag)) - (_.cover [/.command_line_arguments] - (expression (|>> (as Int) (i.= +0)) - (/.the "length" /.command_line_arguments))) - (_.cover [/.last_string_matched] - (expression (|>> (as Bit)) - (|> ($_ /.then - (/.statement - (|> (/.manual "Regexp") - (/.new (list pattern) {.#None}) - (/.do "match" (list pattern) {.#None}))) - (/.return (/.= pattern /.last_string_matched))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_regexp_match] - (expression (|>> (as Bit)) - (|> (/.return (|> (/.manual "Regexp") - (/.new (list pattern) {.#None}) - (/.do "match" (list pattern) {.#None}) - (/.= /.last_regexp_match))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.global] + (expression (|>> (as Text) (text#= "global-variable")) + (|> (all /.then + (/.set (list $global) (/.float float/0)) + (/.return (/.defined?/1 $global))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.script_name] + (expression (let [file (format (# file.default separator) packager.main_file)] + (|>> (as Text) + (text.ends_with? file))) + /.script_name)) + (_.cover [/.input_record_separator] + (expression (|>> (as Text) + (text#= text.\n)) + /.input_record_separator)) + (_.cover [/.output_record_separator] + (..nil /.output_record_separator)) + (_.cover [/.process_id] + (expression (|>> (as Nat) (n.= 0) not) + /.process_id)) + (_.cover [/.case_insensitivity_flag] + (expression (|>> (as Bit) (bit#= false)) + /.case_insensitivity_flag)) + (_.cover [/.command_line_arguments] + (expression (|>> (as Int) (i.= +0)) + (/.the "length" /.command_line_arguments))) + (_.cover [/.last_string_matched] + (expression (|>> (as Bit)) + (|> (all /.then + (/.statement + (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}))) + (/.return (/.= pattern /.last_string_matched))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.last_regexp_match] + (expression (|>> (as Bit)) + (|> (/.return (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}) + (/.= /.last_regexp_match))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|local_var Test (do [! random.monad] [float/0 random.safe_frac $foreign (# ! each /.local (random.ascii/lower 10))] - ($_ _.and - (_.cover [/.local] - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (|> (/.return (/.+ $foreign $foreign)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (_.cover [/.set] - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (|> ($_ /.then - (/.set (list $foreign) (/.float float/0)) - (/.return (/.+ $foreign $foreign))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.local] + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (|> (/.return (/.+ $foreign $foreign)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (_.cover [/.set] + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (|> (all /.then + (/.set (list $foreign) (/.float float/0)) + (/.return (/.+ $foreign $foreign))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|instance_var Test @@ -516,64 +516,64 @@ random.nat) $object (# ! each (|>> %.nat (format "object_") /.local) random.nat)] - ($_ _.and - (_.cover [/.instance] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body ($_ /.then - (/.function /.initialize (list) - (/.set (list $instance) (/.float float/0))) - (/.function $method (list) - (/.return $instance)) - )])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_reader/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body ($_ /.then - (/.attr_reader/* (list instance)) - (/.function /.initialize (list) - (/.set (list $instance) (/.float float/0))) - )])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.the instance)))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_writer/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body ($_ /.then - (/.attr_writer/* (list instance)) - (/.function $method (list) - (/.return $instance)) - )])) - (/.set (list $object) (|> $class - (/.new (list) {.#None}))) - (/.set (list (/.the instance $object)) (/.float float/0)) - (/.return (|> $object - (/.do (/.code $method) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_accessor/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (/.attr_accessor/* (list instance))])) - (/.set (list $object) (|> $class - (/.new (list) {.#None}))) - (/.set (list (/.the instance $object)) (/.float float/0)) - (/.return (/.the instance $object))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.instance] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.function /.initialize (list) + (/.set (list $instance) (/.float float/0))) + (/.function $method (list) + (/.return $instance)) + )])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.attr_reader/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.attr_reader/* (list instance)) + (/.function /.initialize (list) + (/.set (list $instance) (/.float float/0))) + )])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.the instance)))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.attr_writer/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.attr_writer/* (list instance)) + (/.function $method (list) + (/.return $instance)) + )])) + (/.set (list $object) (|> $class + (/.new (list) {.#None}))) + (/.set (list (/.the instance $object)) (/.float float/0)) + (/.return (|> $object + (/.do (/.code $method) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.attr_accessor/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (/.attr_accessor/* (list instance))])) + (/.set (list $object) (|> $class + (/.new (list) {.#None}))) + (/.set (list (/.the instance $object)) (/.float float/0)) + (/.return (/.the instance $object))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|static_var Test @@ -588,18 +588,18 @@ random.nat) $class (# ! each (|>> %.nat (format "class_") /.local) random.nat)] - ($_ _.and - (_.cover [/.static /.class_variable_set /.class_variable_get] - (expression (|>> (as Int) (i.= int/0)) - (|> ($_ /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (/.function $method (list) - (/.return (/.int +0)))])) - (/.statement (/.class_variable_set $static (/.int int/0) $class)) - (/.return (/.class_variable_get $static $class))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.static /.class_variable_set /.class_variable_get] + (expression (|>> (as Int) (i.= int/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (/.function $method (list) + (/.return (/.int +0)))])) + (/.statement (/.class_variable_set $static (/.int int/0) $class)) + (/.return (/.class_variable_get $static $class))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|variadic Test @@ -612,26 +612,26 @@ keys (|> (random.ascii/lower 1) (random.set text.hash arity) (# ! each (|>> set.list (list#each /.string))))] - ($_ _.and - (<| (_.for [/.LVar*]) - ($_ _.and - (_.cover [/.variadic] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" $inputs)) - [(list (/.variadic $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* vals)))) - (_.cover [/.splat] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" (/.array (list (/.splat $inputs))))) - [(list (/.variadic $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* vals)))))) - (<| (_.for [/.LVar**]) - (_.cover [/.variadic_kv /.double_splat] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" $inputs)) - [(list (/.variadic_kv $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.double_splat (/.hash (list.zipped_2 keys vals))))))))) - ))) + (all _.and + (<| (_.for [/.LVar*]) + (all _.and + (_.cover [/.variadic] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" $inputs)) + [(list (/.variadic $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* vals)))) + (_.cover [/.splat] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" (/.array (list (/.splat $inputs))))) + [(list (/.variadic $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* vals)))))) + (<| (_.for [/.LVar**]) + (_.cover [/.variadic_kv /.double_splat] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" $inputs)) + [(list (/.variadic_kv $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.double_splat (/.hash (list.zipped_2 keys vals))))))))) + ))) (def: test|var Test @@ -640,35 +640,35 @@ $foreign (# ! each /.local (random.ascii/lower 10)) $constant (# ! each /.constant (random.ascii/lower 10))] - ($_ _.and - (_.cover [/.defined?/1] - (and (expression (|>> (as Bit)) - (|> (/.defined?/1 $foreign) - (/.= /.nil))) - (expression (|>> (as Text) (text#= "local-variable")) - (|> ($_ /.then - (/.set (list $foreign) (/.float float/0)) - (/.return (/.defined?/1 $foreign))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) - (_.for [/.CVar] - (_.cover [/.constant] - (expression (|>> (as Text) (text#= "constant")) - (|> ($_ /.then - (/.set (list $constant) (/.float float/0)) - (/.return (/.defined?/1 $constant))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) - (_.for [/.GVar] - ..test|global) - (_.for [/.LVar] - ..test|local_var) - (_.for [/.IVar] - ..test|instance_var) - (_.for [/.SVar] - ..test|static_var) - ..test|variadic - ))) + (all _.and + (_.cover [/.defined?/1] + (and (expression (|>> (as Bit)) + (|> (/.defined?/1 $foreign) + (/.= /.nil))) + (expression (|>> (as Text) (text#= "local-variable")) + (|> (all /.then + (/.set (list $foreign) (/.float float/0)) + (/.return (/.defined?/1 $foreign))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) + (_.for [/.CVar] + (_.cover [/.constant] + (expression (|>> (as Text) (text#= "constant")) + (|> (all /.then + (/.set (list $constant) (/.float float/0)) + (/.return (/.defined?/1 $constant))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) + (_.for [/.GVar] + ..test|global) + (_.for [/.LVar] + ..test|local_var) + (_.for [/.IVar] + ..test|instance_var) + (_.for [/.SVar] + ..test|static_var) + ..test|variadic + ))) (def: test|location Test @@ -676,42 +676,42 @@ [float/0 random.safe_frac $foreign (# ! each /.local (random.ascii/lower 10)) field (# ! each /.string (random.ascii/upper 10))] - ($_ _.and - (<| (_.for [/.Var]) - ..test|var) - (_.cover [/.Access] - (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.item (/.int +0) $foreign)] - (|> ($_ /.then - (/.set (list $foreign) (/.array (list $foreign))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.item field $foreign)] - (|> ($_ /.then - (/.set (list $foreign) (/.hash (list [field $foreign]))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - )) - ))) + (all _.and + (<| (_.for [/.Var]) + ..test|var) + (_.cover [/.Access] + (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.item (/.int +0) $foreign)] + (|> (all /.then + (/.set (list $foreign) (/.array (list $foreign))) + (/.set (list @) (/.+ @ @)) + (/.return @)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.item field $foreign)] + (|> (all /.then + (/.set (list $foreign) (/.hash (list [field $foreign]))) + (/.set (list @) (/.+ @ @)) + (/.return @)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + )) + ))) (def: test|expression Test (do [! random.monad] [dummy random.safe_frac expected random.safe_frac] - (`` ($_ _.and - (_.for [/.Literal] - ..test|literal) - (_.for [/.Computation] - ..test|computation) - (_.for [/.Location] - ..test|location) - )))) + (`` (all _.and + (_.for [/.Literal] + ..test|literal) + (_.for [/.Computation] + ..test|computation) + (_.for [/.Location] + ..test|location) + )))) (def: test|label Test @@ -728,56 +728,56 @@ $output (/.local "output") $inner_index (/.local "inner_index") $outer_index (/.local "outer_index")]] - ($_ _.and - (_.cover [/.break] - (let [expected (i.* (.int expected_inner_iterations) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> ($_ /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - ($_ /.then - (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) - /.break) - (/.set (list $output) (/.+ $input $output)) - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) - (_.cover [/.next] - (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> ($_ /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - ($_ /.then - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.next) - (/.set (list $output) (/.+ $input $output)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) - (_.cover [/.redo] - (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> ($_ /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - ($_ /.then - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.redo) - (/.set (list $output) (/.+ $input $output)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) - ))) + (all _.and + (_.cover [/.break] + (let [expected (i.* (.int expected_inner_iterations) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) + /.break) + (/.set (list $output) (/.+ $input $output)) + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) + (_.cover [/.next] + (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.next) + (/.set (list $output) (/.+ $input $output)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) + (_.cover [/.redo] + (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.redo) + (/.set (list $output) (/.+ $input $output)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) + ))) (def: test|loop Test @@ -788,31 +788,31 @@ $output (/.local "output") $index (/.local "index") expected (i.* (.int iterations) input)]] - ($_ _.and - (_.cover [/.while] - (expression (|>> (as Int) (i.= expected)) - (|> ($_ /.then - (/.set (list $index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int iterations)) $index) - ($_ /.then - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input)))))) - (_.cover [/.for_in] - (expression (|>> (as Int) (i.= expected)) - (|> ($_ /.then - (/.set (list $output) (/.int +0)) - (/.for_in $index (/.array (list.repeated iterations (/.int input))) - (/.set (list $output) (/.+ $index $output))) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input)))))) - ..test|label - ))) + (all _.and + (_.cover [/.while] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.set (list $index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int iterations)) $index) + (all /.then + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input)))))) + (_.cover [/.for_in] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.set (list $output) (/.int +0)) + (/.for_in $index (/.array (list.repeated iterations (/.int input))) + (/.set (list $output) (/.+ $index $output))) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input)))))) + ..test|label + ))) (def: random_tag (Random Int) @@ -833,73 +833,73 @@ ..random_tag) .let [expected_tag (/.int expected_tag) dummy_tag (/.int dummy_tag)]] - ($_ _.and - (_.cover [/.begin] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin (/.return (/.float expected)) - (list [(list) $ex (/.return (/.float dummy))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.Rescue /.throw/1] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin ($_ /.then - (/.throw/1 (/.string error)) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.float expected))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.raise] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin ($_ /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.float expected))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.catch /.throw/2] - (and (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch expected_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch expected_tag) [(list)] - /.statement (/.catch dummy_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch dummy_tag) [(list)] - /.statement (/.catch expected_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))))) - (_.cover [/.latest_error_message] - (expression (|>> (as Text) (text#= error)) - (|> (/.begin ($_ /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.the "message" /.latest_error_message))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.latest_error_location] - (and (|> (/.return /.latest_error_location) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)) - ..nil) - (expression (|>> (as Bit) (bit#= true)) - (|> (/.begin ($_ /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return ($_ /.and - (/.do "kind_of?" (list (is /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) - (/.> (/.int +0) (/.the "length" /.latest_error_location))))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) - ))) + (all _.and + (_.cover [/.begin] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (/.return (/.float expected)) + (list [(list) $ex (/.return (/.float dummy))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.Rescue /.throw/1] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (all /.then + (/.throw/1 (/.string error)) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.float expected))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.raise] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.float expected))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.catch /.throw/2] + (and (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch expected_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))) + (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch expected_tag) [(list)] + /.statement (/.catch dummy_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))) + (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch dummy_tag) [(list)] + /.statement (/.catch expected_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))))) + (_.cover [/.latest_error_message] + (expression (|>> (as Text) (text#= error)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.the "message" /.latest_error_message))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.latest_error_location] + (and (|> (/.return /.latest_error_location) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)) + ..nil) + (expression (|>> (as Bit) (bit#= true)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (all /.and + (/.do "kind_of?" (list (is /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) + (/.> (/.int +0) (/.the "length" /.latest_error_location))))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) + ))) (def: test|function Test @@ -915,42 +915,42 @@ $arg/0 (# ! each /.local (random.ascii/lower 10)) $arg/1 (# ! each /.local (random.ascii/lower 11)) $arg/2 (# ! each /.local (random.ascii/lower 12))] - ($_ _.and - (_.cover [/.lambda /.return] - (and (expression (|>> (as Frac) (f.= float/0)) - (|> (/.return (/.float float/0)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))) - (expression (|>> (as Frac) f.nat (n.= iterations)) - (|> (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self) - $arg/0)) - [(list $arg/0)] (/.lambda {.#Some $self}) - (/.apply_lambda/* (list (/.int +0))))))) - (_.cover [/.apply_lambda/*] - (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) - (|> (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)) - [(list $arg/0 $arg/1 $arg/2)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2)))))) - (_.cover [/.function] - (expression (|>> (as Frac) f.nat (n.= iterations)) - (|> ($_ /.then - (/.function $self (list $arg/0) - (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply/* (list (/.+ (/.int +1) $arg/0)) {.#None} $self) - $arg/0))) - (/.return (/.apply/* (list (/.int +0)) {.#None} $self))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.apply/*] - (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) - (|> ($_ /.then - (/.function $self (list $arg/0 $arg/1 $arg/2) - (/.return ($_ /.+ $arg/0 $arg/1 $arg/2))) - (/.return (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) {.#None} $self))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.lambda /.return] + (and (expression (|>> (as Frac) (f.= float/0)) + (|> (/.return (/.float float/0)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))) + (expression (|>> (as Frac) f.nat (n.= iterations)) + (|> (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self) + $arg/0)) + [(list $arg/0)] (/.lambda {.#Some $self}) + (/.apply_lambda/* (list (/.int +0))))))) + (_.cover [/.apply_lambda/*] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (|> (/.return (all /.+ $arg/0 $arg/1 $arg/2)) + [(list $arg/0 $arg/1 $arg/2)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2)))))) + (_.cover [/.function] + (expression (|>> (as Frac) f.nat (n.= iterations)) + (|> (all /.then + (/.function $self (list $arg/0) + (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply/* (list (/.+ (/.int +1) $arg/0)) {.#None} $self) + $arg/0))) + (/.return (/.apply/* (list (/.int +0)) {.#None} $self))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.apply/*] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (|> (all /.then + (/.function $self (list $arg/0 $arg/1 $arg/2) + (/.return (all /.+ $arg/0 $arg/1 $arg/2))) + (/.return (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) {.#None} $self))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|branching Test @@ -968,23 +968,23 @@ $arg/1 (/.local arg/1) $arg/2 (/.local arg/2)] ??? random.bit] - ($_ _.and - (_.cover [/.if] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> (/.if (/.bool ???) - (/.return (/.float float/0)) - (/.return (/.float float/1))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.when] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> ($_ /.then - (/.when (/.bool ???) - (/.return (/.float float/0))) - (/.return (/.float float/1))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - ))) + (all _.and + (_.cover [/.if] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (/.if (/.bool ???) + (/.return (/.float float/0)) + (/.return (/.float float/1))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.when] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (all /.then + (/.when (/.bool ???) + (/.return (/.float float/0))) + (/.return (/.float float/1))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + ))) (def: test|statement Test @@ -997,49 +997,49 @@ $arg/2 (# ! each /.local (random.ascii/lower 12)) expected (# ! each (|>> %.int (text.replaced "+" "")) random.int)] - ($_ _.and - (_.cover [/.statement] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.statement (/.+ $arg/0 $arg/0)) - (/.return $arg/0)) - [(list $arg/0)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (_.cover [/.then] - (expression (|>> (as Frac) (f.= float/0)) - (|> ($_ /.then - (/.return $arg/0) - (/.return $arg/1)) - [(list $arg/0 $arg/1)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0) (/.float float/1)))))) - (_.cover [/.require/1] - (let [$JSON (is /.CVar (/.manual "JSON"))] - (expression (|>> (as Text) (text#= expected)) - (|> ($_ /.then - (/.statement (/.require/1 (/.string "json"))) - (/.return (let [json (/.do "parse" (list $arg/0) {.#None} $JSON)] - (/.do "generate" (list json) {.#None} $JSON)))) - [(list $arg/0)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.string expected))))))) - ..test|exception - ..test|branching - ..test|loop - (_.for [/.Block] - ..test|function) - ))) + (all _.and + (_.cover [/.statement] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.statement (/.+ $arg/0 $arg/0)) + (/.return $arg/0)) + [(list $arg/0)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (_.cover [/.then] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.return $arg/0) + (/.return $arg/1)) + [(list $arg/0 $arg/1)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0) (/.float float/1)))))) + (_.cover [/.require/1] + (let [$JSON (is /.CVar (/.manual "JSON"))] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "json"))) + (/.return (let [json (/.do "parse" (list $arg/0) {.#None} $JSON)] + (/.do "generate" (list json) {.#None} $JSON)))) + [(list $arg/0)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.string expected))))))) + ..test|exception + ..test|branching + ..test|loop + (_.for [/.Block] + ..test|function) + ))) (def: random_expression (Random /.Expression) (let [literal (is (Random /.Literal) - ($_ random.either - (random#each /.bool random.bit) - (random#each /.float random.frac) - (random#each /.int random.int) - (random#each /.string (random.ascii/lower 5)) - ))] - ($_ random.either - literal - ))) + (all random.either + (random#each /.bool random.bit) + (random#each /.float random.frac) + (random#each /.int random.int) + (random#each /.string (random.ascii/lower 5)) + ))] + (all random.either + literal + ))) (def: .public test Test @@ -1047,16 +1047,16 @@ [expected ..random_expression] (<| (_.covering /._) (_.for [/.Code]) - ($_ _.and - (_.for [/.equivalence] - ($equivalence.spec /.equivalence ..random_expression)) - - (_.cover [/.code /.manual] - (|> (/.manual (/.code expected)) - (is /.Expression) - (/#= expected))) - (_.for [/.Expression] - ..test|expression) - (_.for [/.Statement] - ..test|statement) - )))) + (all _.and + (_.for [/.equivalence] + ($equivalence.spec /.equivalence ..random_expression)) + + (_.cover [/.code /.manual] + (|> (/.manual (/.code expected)) + (is /.Expression) + (/#= expected))) + (_.for [/.Expression] + ..test|expression) + (_.for [/.Statement] + ..test|statement) + )))) |