aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/meta/target/ruby.lux
diff options
context:
space:
mode:
authorEduardo Julian2023-01-08 02:13:36 -0400
committerEduardo Julian2023-01-08 02:13:36 -0400
commit617069b3986e9271d6e73191b899aa914e430dd6 (patch)
tree7a4255a4eb1460a58b64161a8200486a756265bc /stdlib/source/test/lux/meta/target/ruby.lux
parentae2d5697d93a45dcbff768c32c4dc8fb291096cd (diff)
Moved compiler target machinery under meta/compiler.
Diffstat (limited to 'stdlib/source/test/lux/meta/target/ruby.lux')
-rw-r--r--stdlib/source/test/lux/meta/target/ruby.lux1062
1 files changed, 0 insertions, 1062 deletions
diff --git a/stdlib/source/test/lux/meta/target/ruby.lux b/stdlib/source/test/lux/meta/target/ruby.lux
deleted file mode 100644
index 900e630e7..000000000
--- a/stdlib/source/test/lux/meta/target/ruby.lux
+++ /dev/null
@@ -1,1062 +0,0 @@
-(.require
- [library
- [lux (.except)
- ["[0]" ffi]
- [abstract
- [monad (.only do)]
- ["[0]" predicate]
- ["[0]" equivalence
- ["[1]T" \\test]]]
- [control
- ["[0]" pipe]
- ["[0]" maybe (.use "[1]#[0]" functor)]
- ["[0]" try (.only Try) (.use "[1]#[0]" functor)]]
- [data
- ["[0]" bit (.use "[1]#[0]" equivalence)]
- ["[0]" text (.use "[1]#[0]" equivalence)
- ["%" \\format (.only format)]]
- [collection
- ["[0]" list (.use "[1]#[0]" functor)]
- ["[0]" set]]]
- [math
- ["[0]" random (.only Random) (.use "[1]#[0]" monad)]
- [number (.only hex)
- ["n" nat]
- ["i" int]
- ["f" frac]
- ["[0]" i64]]]
- [meta
- [compiler
- [meta
- ["[0]" packager
- ["[1]" ruby]]]]]
- [world
- ["[0]" file]]
- [test
- ["_" property (.only Test)]]]]
- [\\library
- ["[0]" / (.use "[1]#[0]" equivalence)]])
-
-(ffi.import (eval [Text] "try" "?" Any))
-
-(def (expression ??? it)
- (-> (-> Any Bit) /.Expression Bit)
- (|> it
- /.code
- ..eval
- (try#each (|>> (maybe#each ???)
- (maybe.else false)))
- (try.else false)))
-
-(def nil
- (-> /.Expression Bit)
- (|>> /.code
- ..eval
- (try#each (|>> (pipe.when
- {.#None} true
- {.#Some _} false)))
- (try.else false)))
-
-(def test|literal
- Test
- (do [! random.monad]
- [bool random.bit
- float random.frac
- int random.int
- string (random.upper_cased 5)]
- (all _.and
- (_.coverage [/.nil]
- (..nil /.nil))
- (_.coverage [/.bool]
- (expression (|>> (as Bit) (bit#= bool))
- (/.bool bool)))
- (_.coverage [/.int]
- (expression (|>> (as Int) (i.= int))
- (/.int int)))
- (_.coverage [/.float]
- (expression (|>> (as Frac) (f.= float))
- (/.float float)))
- (_.coverage [/.string]
- (expression (|>> (as Text) (text#= string))
- (/.string string)))
- (_.coverage [/.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]
- (`` (all _.and
- (,, (with_template [</> <lux>]
- [(_.coverage [</>]
- (let [expected (<lux> left right)]
- (expression (|>> (as Bit) (bit#= expected))
- (</> (/.bool left) (/.bool right)))))]
-
- [/.or .or]
- [/.and .and]
- ))
- (_.coverage [/.not]
- (expression (|>> (as Bit) (bit#= (not left)))
- (/.not (/.bool left))))
- ))))
-
-(def test|float
- Test
- (do [! random.monad]
- [parameter (random.only (|>> (f.= +0.0) not)
- random.safe_frac)
- subject random.safe_frac]
- (`` (all _.and
- (,, (with_template [</> <lux> <pre>]
- [(_.coverage [</>]
- (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]
- ))
- (,, (with_template [</> <lux>]
- [(_.coverage [</>]
- (let [expected (<lux> parameter subject)]
- (expression (|>> (as Bit) (bit#= expected))
- (</> (/.float parameter) (/.float subject)))))]
-
- [/.< f.<]
- [/.<= f.<=]
- [/.> f.>]
- [/.>= f.>=]
- [/.= f.=]
- ))
- ))))
-
-(def int_16
- (-> Int Int)
- (i64.and (-- (i64.left_shifted 15 1))))
-
-(def test|int
- Test
- (do [! random.monad]
- [left random.int
- right random.int
-
- i16 (of ! each ..int_16 random.int)
- shift (of ! each (n.% 16) random.nat)]
- (`` (all _.and
- (,, (with_template [</> <lux>]
- [(_.coverage [</>]
- (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]
- ))
- (_.coverage [/.bit_not]
- (expression (|>> (as Int) (i.= (i64.not left)))
- (/.bit_not (/.int left))))
- (_.coverage [/.opposite]
- (expression (|>> (as Int) (i.= (i.* -1 left)))
- (/.opposite (/.int left))))
- (_.coverage [/.bit_shl]
- (let [expected (i64.left_shifted shift i16)]
- (expression (|>> (as Frac) f.int (i.= expected))
- (/.bit_shl (/.int (.int shift))
- (/.int i16)))))
- (_.coverage [/.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
- (do [! random.monad]
- [size (of ! each (|>> (n.% 10) ++) random.nat)
- index (of ! each (n.% size) random.nat)
- items (random.list size random.safe_frac)
- .let [expected (|> items
- (list.item index)
- (maybe.else f.not_a_number))]
- from (of ! each (n.% size) random.nat)
- plus (of ! each (n.% (n.- from size)) random.nat)
- .let [to (/.int (.int (n.+ plus from)))
- from (/.int (.int from))]]
- (all _.and
- (_.coverage [/.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)))))
- (_.coverage [/.array_range]
- (expression (|>> (as Int) (i.= (.int (++ plus))))
- (|> (/.array (list#each /.float items))
- (/.array_range from to)
- (/.the "length"))))
- )))
-
-(def test|hash
- Test
- (do [! random.monad]
- [expected random.safe_frac
- field (random.upper_cased 5)
- dummy (random.only (|>> (text#= field) not)
- (random.upper_cased 5))
- .let [field (/.string field)
- dummy (/.string dummy)]]
- (all _.and
- (_.coverage [/.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
- (do [! random.monad]
- [size (of ! each (|>> (n.% 10) ++) random.nat)
- index (of ! each (n.% size) random.nat)
- items (random.list size random.safe_frac)
- $class (of ! each (|>> %.nat (format "class_") /.local)
- random.nat)
- $sub_class (of ! each (|>> %.nat (format "sub_class_") /.local)
- random.nat)
- $method/0 (of ! each (|>> %.nat (format "method_") /.local)
- random.nat)
- $method/1 (|> random.nat
- (of ! each (|>> %.nat (format "method_") /.local))
- (random.only (|>> (/#= $method/0) not)))
- $arg/0 (of ! each (|>> %.nat (format "arg_") /.local)
- random.nat)
- $state (of ! each (|>> %.nat (format "instance_") /.instance)
- random.nat)
- single random.safe_frac
- .let [double (/.function $method/0 (list $arg/0)
- (/.return (/.+ $arg/0 $arg/0)))]]
- (all _.and
- (_.coverage [/.the]
- (expression (|>> (as Int) (i.= (.int size)))
- (|> (/.array (list#each /.float items))
- (/.the "length"))))
- (_.coverage [/.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}))))
- (_.coverage [/.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)))))
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (<| (do [! random.monad]
- [left (random.upper_cased 5)
- right (random.upper_cased 5)
- $old (of ! each /.local (random.upper_cased 1))
- $new (of ! each /.local (random.upper_cased 2))
- $it (of ! each /.local (random.upper_cased 3))
- .let [expected (format left right)]])
- (all _.and
- (_.for [/.stdout]
- (all _.and
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (_.coverage [/.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)))))
- (_.coverage [/.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)))))
- (_.coverage [/.last_line_number_read]
- (expression (|>> (as Nat) (n.= 2))
- /.last_line_number_read))
- ))
- )))
-
-(def test|computation
- Test
- (do [! random.monad]
- [test random.bit
- then random.safe_frac
- else random.safe_frac
-
- bool random.bit
- float random.frac
- string (random.upper_cased 5)
-
- comment (random.upper_cased 10)]
- (all _.and
- ..test|bool
- ..test|float
- ..test|int
- ..test|array
- ..test|hash
- ..test|object
- ..test|io
- (_.coverage [/.?]
- (let [expected (if test then else)]
- (expression (|>> (as Frac) (f.= expected))
- (/.? (/.bool test)
- (/.float then)
- (/.float else)))))
- (_.coverage [/.comment]
- (expression (|>> (as Frac) (f.= then))
- (/.comment comment
- (/.float then))))
- )))
-
-(def test|global
- Test
- (do [! random.monad]
- [float/0 random.safe_frac
- $global (of ! each /.global (random.lower_cased 10))
- pattern (of ! each /.string (random.lower_cased 11))]
- (all _.and
- (_.coverage [/.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)))))
- (_.coverage [/.script_name]
- (expression (let [file (format (of file.default separator) packager.main_file)]
- (|>> (as Text)
- (text.ends_with? file)))
- /.script_name))
- (_.coverage [/.input_record_separator]
- (expression (|>> (as Text)
- (text#= text.\n))
- /.input_record_separator))
- (_.coverage [/.output_record_separator]
- (..nil /.output_record_separator))
- (_.coverage [/.process_id]
- (expression (|>> (as Nat) (n.= 0) not)
- /.process_id))
- (_.coverage [/.case_insensitivity_flag]
- (expression (|>> (as Bit) (bit#= false))
- /.case_insensitivity_flag))
- (_.coverage [/.command_line_arguments]
- (expression (|>> (as Int) (i.= +0))
- (/.the "length" /.command_line_arguments)))
- (_.coverage [/.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)))))
- (_.coverage [/.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 (of ! each /.local (random.lower_cased 10))]
- (all _.and
- (_.coverage [/.local]
- (expression (|>> (as Frac) (f.= (f.+ float/0 float/0)))
- (|> (/.return (/.+ $foreign $foreign))
- [(list $foreign)] (/.lambda {.#None})
- (/.apply_lambda (list (/.float float/0))))))
- (_.coverage [/.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
- (do [! random.monad]
- [float/0 random.safe_frac
- instance (of ! each (|>> %.nat (format "instance_"))
- random.nat)
- .let [$instance (/.instance instance)]
- $method (of ! each (|>> %.nat (format "method_") /.local)
- random.nat)
- $class (of ! each (|>> %.nat (format "class_") /.local)
- random.nat)
- $object (of ! each (|>> %.nat (format "object_") /.local)
- random.nat)]
- (all _.and
- (_.coverage [/.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)))))
- (_.coverage [/.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)))))
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (do [! random.monad]
- [int/0 (of ! each (|>> (n.% 10) ++ .int)
- random.nat)
- $static (of ! each (|>> %.nat (format "static_") /.static)
- random.nat)
- $arg (of ! each (|>> %.nat /.local)
- random.nat)
- $method (of ! each (|>> %.nat (format "method_") /.local)
- random.nat)
- $class (of ! each (|>> %.nat (format "class_") /.local)
- random.nat)]
- (all _.and
- (_.coverage [/.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
- (do [! random.monad]
- [$inputs (of ! each /.local (random.lower_cased 10))
- arity (of ! each (n.% 10) random.nat)
- vals (|> random.int
- (of ! each /.int)
- (random.list arity))
- keys (|> (random.lower_cased 1)
- (random.set text.hash arity)
- (of ! each (|>> set.list (list#each /.string))))]
- (all _.and
- (<| (_.for [/.LVar*])
- (all _.and
- (_.coverage [/.variadic]
- (expression (|>> (as Int) .nat (n.= arity))
- (|> (/.return (/.the "length" $inputs))
- [(list (/.variadic $inputs))] (/.lambda {.#None})
- (/.apply_lambda vals))))
- (_.coverage [/.splat]
- (expression (|>> (as Int) .nat (n.= arity))
- (|> (/.return (/.the "length" (/.array (list (/.splat $inputs)))))
- [(list (/.variadic $inputs))] (/.lambda {.#None})
- (/.apply_lambda vals))))))
- (<| (_.for [/.LVar**])
- (_.coverage [/.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
- (do [! random.monad]
- [float/0 random.safe_frac
- $foreign (of ! each /.local (random.lower_cased 10))
-
- $constant (of ! each /.constant (random.lower_cased 10))]
- (all _.and
- (_.coverage [/.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]
- (_.coverage [/.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
- (do [! random.monad]
- [float/0 random.safe_frac
- $foreign (of ! each /.local (random.lower_cased 10))
- field (of ! each /.string (random.upper_cased 10))]
- (all _.and
- (<| (_.for [/.Var])
- ..test|var)
- (_.coverage [/.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]
- (`` (all _.and
- (_.for [/.Literal]
- ..test|literal)
- (_.for [/.Computation]
- ..test|computation)
- (_.for [/.Location]
- ..test|location)
- ))))
-
-(def test|label
- Test
- (do [! random.monad]
- [input (of ! each ..int_16 random.int)
-
- full_inner_iterations (of ! each (|>> (n.% 20) ++) random.nat)
- expected_inner_iterations (of ! each (n.% full_inner_iterations) random.nat)
-
- full_outer_iterations (of ! each (|>> (n.% 10) ++) random.nat)
- expected_outer_iterations (of ! each (n.% full_outer_iterations) random.nat)
-
- .let [$input (/.local "input")
- $output (/.local "output")
- $inner_index (/.local "inner_index")
- $outer_index (/.local "outer_index")]]
- (all _.and
- (_.coverage [/.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)))))))
- (_.coverage [/.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)))))))
- (_.coverage [/.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
- (do [! random.monad]
- [input (of ! each (i.right_shifted 32) random.int)
- iterations (of ! each (n.% 10) random.nat)
- .let [$input (/.local "input")
- $output (/.local "output")
- $index (/.local "index")
- expected (i.* (.int iterations) input)]]
- (all _.and
- (_.coverage [/.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))))))
- (_.coverage [/.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)
- (random#each (i64.and (hex "FF,FF,FF,FF"))
- random.int))
-
-(def test|exception
- Test
- (do [! random.monad]
- [expected random.safe_frac
- dummy (random.only (|>> (f.= expected) not)
- random.safe_frac)
- error (random.lower_cased 10)
- $ex (of ! each /.local (random.lower_cased 10))
-
- expected_tag ..random_tag
- dummy_tag (random.only (|>> (i.= expected_tag) not)
- ..random_tag)
- .let [expected_tag (/.int expected_tag)
- dummy_tag (/.int dummy_tag)]]
- (all _.and
- (_.coverage [/.begin]
- (expression (|>> (as Frac) (f.= expected))
- (|> (/.begin (/.return (/.float expected))
- (list [(list) $ex (/.return (/.float dummy))]))
- [(list)] (/.lambda {.#None})
- (/.apply_lambda (list)))))
- (_.coverage [/.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)))))
- (_.coverage [/.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)))))
- (_.coverage [/.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))))))
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (do [! random.monad]
- [iterations (of ! each (n.% 10) random.nat)
- $self (of ! each /.local (random.lower_cased 1))
- field (random.lower_cased 3)
- $class (of ! each /.local (random.upper_cased 4))
-
- float/0 random.safe_frac
- float/1 random.safe_frac
- float/2 random.safe_frac
- $arg/0 (of ! each /.local (random.lower_cased 10))
- $arg/1 (of ! each /.local (random.lower_cased 11))
- $arg/2 (of ! each /.local (random.lower_cased 12))]
- (all _.and
- (_.coverage [/.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)))))))
- (_.coverage [/.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))))))
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (do [! random.monad]
- [float/0 random.safe_frac
- float/1 random.safe_frac
- float/2 random.safe_frac
- arg/0 (random.lower_cased 10)
- arg/1 (random.only (|>> (text#= arg/0) not)
- (random.lower_cased 10))
- arg/2 (random.only (predicate.and (|>> (text#= arg/0) not)
- (|>> (text#= arg/1) not))
- (random.lower_cased 10))
- .let [$arg/0 (/.local arg/0)
- $arg/1 (/.local arg/1)
- $arg/2 (/.local arg/2)]
- ??? random.bit]
- (all _.and
- (_.coverage [/.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)))))
- (_.coverage [/.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
- (do [! random.monad]
- [float/0 random.safe_frac
- float/1 random.safe_frac
- float/2 random.safe_frac
- $arg/0 (of ! each /.local (random.lower_cased 10))
- $arg/1 (of ! each /.local (random.lower_cased 11))
- $arg/2 (of ! each /.local (random.lower_cased 12))
- expected (of ! each (|>> %.int (text.replaced "+" ""))
- random.int)]
- (all _.and
- (_.coverage [/.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))))))
- (_.coverage [/.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))))))
- (_.coverage [/.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)
- (all random.either
- (random#each /.bool random.bit)
- (random#each /.float random.frac)
- (random#each /.int random.int)
- (random#each /.string (random.lower_cased 5))
- ))]
- (all random.either
- literal
- )))
-
-(def .public test
- Test
- (do [! random.monad]
- [expected ..random_expression]
- (<| (_.covering /._)
- (_.for [/.Code])
- (all _.and
- (_.for [/.equivalence]
- (equivalenceT.spec /.equivalence ..random_expression))
-
- (_.coverage [/.code /.manual]
- (|> (/.manual (/.code expected))
- (is /.Expression)
- (/#= expected)))
- (_.for [/.Expression]
- ..test|expression)
- (_.for [/.Statement]
- ..test|statement)
- ))))