aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux.lux151
-rw-r--r--stdlib/source/test/lux/math/number/int.lux63
-rw-r--r--stdlib/source/test/lux/target/js.lux845
3 files changed, 957 insertions, 102 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index 7026c0a48..c200a0316 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -1,72 +1,71 @@
-(.with_expansions [<target>' (.for ["{old}" (.as_is ["[1]/[0]" jvm])
- "JVM" (.as_is ["[1]/[0]" jvm])]
- (.as_is))
- <target> <target>']
- (.using
- [library
- ["/" lux "*"
- [program {"+" program:}]
- ["_" test {"+" Test}]
- ["@" target]
- [abstract
- [monad {"+" do}]]
- [control
- ["[0]" io]
- ["[0]" maybe ("[1]#[0]" functor)]
- [concurrency
- ["[0]" atom {"+" Atom}]]
- [parser
- ["<[0]>" code]]]
- [data
- ["[0]" product]
- ["[0]" bit ("[1]#[0]" equivalence)]
- ["[0]" text ("[1]#[0]" equivalence)
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]
- ["[0]" set {"+" Set} ("[1]#[0]" equivalence)]
- [dictionary
- ["[0]" plist]]]]
- ["[0]" macro
- [syntax {"+" syntax:}]
- ["[0]" code ("[1]#[0]" equivalence)]
- ["[0]" template]]
- ["[0]" math
- ["[0]" random ("[1]#[0]" functor)]
- [number
- [i8 {"+"}]
- [i16 {"+"}]
- ["n" nat]
- ["i" int]
- ["r" rev]
- ["f" frac]
- ["[0]" i64]]]
- ["[0]" meta
- ["[0]" location ("[1]#[0]" equivalence)]]]]
- ... TODO: Must have 100% coverage on tests.
- ["[0]" / "_"
- ["[1][0]" abstract]
- ["[1][0]" control]
- ["[1][0]" data]
- ["[1][0]" debug]
- ["[1][0]" documentation]
- ["[1][0]" locale]
- ["[1][0]" macro
- ["[1]/[0]" code]]
- ["[1][0]" math]
- ["[1][0]" meta]
- ["[1][0]" program]
- ["[1][0]" static]
- ["[1][0]" target]
- ["[1][0]" test]
- ["[1][0]" time]
- ... ["[1][0]" tool] ... TODO: Update & expand tests for this
- ["[1][0]" type]
- ["[1][0]" world]
- ["[1][0]" ffi]
- ["[1][0]" extension]
- ["[1][0]" target "_"
- <target>]]))
+(.`` (.`` (.using
+ [library
+ ["/" lux "*"
+ [program {"+" program:}]
+ ["_" test {"+" Test}]
+ ["@" target]
+ [abstract
+ [monad {"+" do}]]
+ [control
+ ["[0]" io]
+ ["[0]" maybe ("[1]#[0]" functor)]
+ [concurrency
+ ["[0]" atom {"+" Atom}]]
+ [parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" product]
+ ["[0]" bit ("[1]#[0]" equivalence)]
+ ["[0]" text ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]
+ ["[0]" set {"+" Set} ("[1]#[0]" equivalence)]
+ [dictionary
+ ["[0]" plist]]]]
+ ["[0]" macro
+ [syntax {"+" syntax:}]
+ ["[0]" code ("[1]#[0]" equivalence)]
+ ["[0]" template]]
+ ["[0]" math
+ ["[0]" random ("[1]#[0]" functor)]
+ [number
+ [i8 {"+"}]
+ [i16 {"+"}]
+ ["n" nat]
+ ["i" int]
+ ["r" rev]
+ ["f" frac]
+ ["[0]" i64]]]
+ ["[0]" meta
+ ["[0]" location ("[1]#[0]" equivalence)]]]]
+ ... TODO: Must have 100% coverage on tests.
+ ["[0]" / "_"
+ ["[1][0]" abstract]
+ ["[1][0]" control]
+ ["[1][0]" data]
+ ["[1][0]" debug]
+ ["[1][0]" documentation]
+ ["[1][0]" locale]
+ ["[1][0]" macro
+ ["[1]/[0]" code]]
+ ["[1][0]" math]
+ ["[1][0]" meta]
+ ["[1][0]" program]
+ ["[1][0]" static]
+ ["[1][0]" target]
+ ["[1][0]" test]
+ ["[1][0]" time]
+ ... ["[1][0]" tool] ... TODO: Update & expand tests for this
+ ["[1][0]" type]
+ ["[1][0]" world]
+ ["[1][0]" ffi]
+ ["[1][0]" extension]
+ ["[1][0]" target "_"
+ (~~ (.for ["{old}" (~~ (.as_is ["[1]/[0]" jvm]))
+ "JVM" (~~ (.as_is ["[1]/[0]" jvm]))
+ "JavaScript" (~~ (.as_is ["[1]/[0]" js]))]
+ (~~ (.as_is))))]])))
... TODO: Get rid of this ASAP
(template: (!bundle body)
@@ -79,7 +78,8 @@
Test
(with_expansions [... TODO: Update & expand tests for this
<target> (for [@.jvm (~~ (as_is /target/jvm.test))
- @.old (~~ (as_is /target/jvm.test))]
+ @.old (~~ (as_is /target/jvm.test))
+ @.js (~~ (as_is /target/js.test))]
(~~ (as_is)))
<extension> (for [@.old (~~ (as_is))]
(~~ (as_is /extension.test)))]
@@ -865,12 +865,11 @@
(hide left))
true)))))
(_.cover [/.same?]
- (let [not_left (|> left ++ -- %.nat)
- left (%.nat left)]
- (and (and (/.same? left left)
- (/.same? not_left not_left))
- (and (text#= left not_left)
- (not (/.same? left not_left))))))
+ (let [not_left (atom.atom left)
+ left (atom.atom left)]
+ (and (/.same? left left)
+ (/.same? not_left not_left)
+ (not (/.same? left not_left)))))
(_.cover [/.Rec]
(let [list (: (/.Rec NList
(Maybe [Nat NList]))
diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux
index d67d0d853..394c34c15 100644
--- a/stdlib/source/test/lux/math/number/int.lux
+++ b/stdlib/source/test/lux/math/number/int.lux
@@ -1,27 +1,27 @@
(.using
- [library
- [lux "*"
- ["_" test {"+" Test}]
- [abstract
- [monad {"+" do}]
- [\\specification
- ["$[0]" equivalence]
- ["$[0]" hash]
- ["$[0]" order]
- ["$[0]" enum]
- ["$[0]" interval]
- ["$[0]" monoid]
- ["$[0]" codec]]]
- [data
- ["[0]" bit ("[1]#[0]" equivalence)]]
- [math
- ["[0]" random {"+" Random}]]]]
- [\\library
- ["[0]" /
- [//
- ["n" nat]
- ["f" frac]
- ["[0]" i64]]]])
+ [library
+ [lux "*"
+ ["_" test {"+" Test}]
+ [abstract
+ [monad {"+" do}]
+ [\\specification
+ ["$[0]" equivalence]
+ ["$[0]" hash]
+ ["$[0]" order]
+ ["$[0]" enum]
+ ["$[0]" interval]
+ ["$[0]" monoid]
+ ["$[0]" codec]]]
+ [data
+ ["[0]" bit ("[1]#[0]" equivalence)]]
+ [math
+ ["[0]" random {"+" Random}]]]]
+ [\\library
+ ["[0]" /
+ [//
+ ["n" nat]
+ ["f" frac]
+ ["[0]" i64]]]])
(def: signature
Test
@@ -193,7 +193,8 @@
(/.= pattern (/.right_shifted i64.width pattern))
sign_mask (i64.left_shifted (-- i64.width) 1)
- mantissa_mask (i64.not sign_mask)
+ mantissa_mask (-- (i64.left_shifted (n.- idx i64.width) 1))
+ co_mantissa_mask (i64.not mantissa_mask)
sign_preservation!
(/.= (i64.and sign_mask pattern)
@@ -201,11 +202,21 @@
mantissa_parity!
(/.= (i64.and mantissa_mask (i64.right_shifted idx pattern))
- (i64.and mantissa_mask (/.right_shifted idx pattern)))]
+ (i64.and mantissa_mask (/.right_shifted idx pattern)))
+
+ co_mantissa_disparity!
+ (or (n.= 0 idx)
+ (and (/.= +0 (i64.and co_mantissa_mask (i64.right_shifted idx pattern)))
+ (/.= (if (/.< +0 pattern)
+ (.int co_mantissa_mask)
+ +0)
+ (i64.and co_mantissa_mask (/.right_shifted idx pattern)))))]
(and nullity!
idempotency!
sign_preservation!
- mantissa_parity!))))
+ mantissa_parity!
+ co_mantissa_disparity!
+ ))))
..predicate
..signature
diff --git a/stdlib/source/test/lux/target/js.lux b/stdlib/source/test/lux/target/js.lux
new file mode 100644
index 000000000..cc60dd896
--- /dev/null
+++ b/stdlib/source/test/lux/target/js.lux
@@ -0,0 +1,845 @@
+(.using
+ [library
+ [lux "*"
+ ["_" test {"+" Test}]
+ ["[0]" static]
+ [abstract
+ [monad {"+" do}]
+ ["[0]" predicate]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" function]
+ ["[0]" maybe ("[1]#[0]" functor)]
+ ["[0]" try {"+" Try} ("[1]#[0]" functor)]]
+ [data
+ ["[0]" bit ("[1]#[0]" equivalence)]
+ ["[0]" text {"+" \n} ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [macro
+ ["[0]" template]]
+ [math
+ ["[0]" random {"+" Random} ("[1]#[0]" monad)]
+ [number
+ ["n" nat]
+ ["i" int]
+ ["f" frac]
+ ["[0]" i64]]]]]
+ [\\library
+ ["[0]" /]])
+
+(def: (eval code)
+ (-> /.Expression (Try (Maybe Any)))
+ ... Note: I have to call "eval" this way
+ ... in order to avoid a quirk of calling eval in Node
+ ... when the code is running under "use strict";.
+ (try (let [return ("js apply" (function.identity ("js constant" "eval")) (/.code code))]
+ (if ("js object null?" return)
+ {.#None}
+ {.#Some return}))))
+
+(def: (expression ??? it)
+ (-> (-> Any Bit) /.Expression Bit)
+ (|> it
+ ..eval
+ (try#each (|>> (maybe#each ???)
+ (maybe.else false)))
+ (try.else false)))
+
+(template [<range>]
+ [(`` (def: (~~ (template.symbol ["as_int/" <range>]))
+ (-> Int Int)
+ (|>> (i64.and (static.nat (-- (i64.left_shifted <range> 1)))))))
+ (`` (def: (~~ (template.symbol ["int/" <range>]))
+ (Random Int)
+ (do [! random.monad]
+ [negative? random.bit
+ mantissa (# ! each (|>> (i64.and (static.nat (-- (i64.left_shifted (-- <range>) 1))))
+ .int)
+ random.nat)]
+ (in (if negative?
+ (i.* -1 mantissa)
+ mantissa)))))]
+
+ [16]
+ [32]
+ )
+
+(def: test|literal
+ Test
+ (do [! random.monad]
+ [boolean random.bit
+ number random.frac
+ int ..int/32
+ string (random.ascii/upper 5)]
+ ($_ _.and
+ (_.cover [/.null]
+ (|> /.null
+ ..eval
+ (try#each (function (_ it)
+ (case it
+ {.#None} true
+ {.#Some _} true)))
+ (try.else false)))
+ (_.cover [/.boolean]
+ (expression (|>> (:as Bit) (bit#= boolean))
+ (/.boolean boolean)))
+ (_.cover [/.number]
+ (expression (|>> (:as Frac) (f.= number))
+ (/.number number)))
+ (_.cover [/.int]
+ (expression (|>> (:as Frac) f.int (i.= int))
+ (/.int int)))
+ (_.cover [/.string]
+ (expression (|>> (:as Text) (text#= string))
+ (/.string string)))
+ )))
+
+(def: test|boolean
+ Test
+ (do [! random.monad]
+ [left random.bit
+ right random.bit]
+ (`` ($_ _.and
+ (~~ (template [<js> <lux>]
+ [(_.cover [<js>]
+ (let [expected (<lux> left right)]
+ (expression (|>> (:as Bit) (bit#= expected))
+ (<js> (/.boolean left) (/.boolean right)))))]
+
+ [/.or .or]
+ [/.and .and]
+ ))
+ (_.cover [/.not]
+ (expression (|>> (:as Bit) (bit#= (not left)))
+ (/.not (/.boolean left))))
+ ))))
+
+(def: test|number
+ Test
+ (do [! random.monad]
+ [parameter (random.only (|>> (f.= +0.0) not)
+ random.safe_frac)
+ subject random.safe_frac]
+ (`` ($_ _.and
+ (~~ (template [<js> <lux>]
+ [(_.cover [<js>]
+ (let [expected (<lux> parameter subject)]
+ (expression (|>> (:as Frac) (f.= expected))
+ (<js> (/.number parameter) (/.number subject)))))]
+
+ [/.+ f.+]
+ [/.- f.-]
+ [/.* f.*]
+ [/./ f./]
+ [/.% f.%]
+ ))
+ (~~ (template [<js> <lux>]
+ [(_.cover [<js>]
+ (let [expected (<lux> parameter subject)]
+ (expression (|>> (:as Bit) (bit#= expected))
+ (<js> (/.number parameter) (/.number subject)))))]
+
+ [/.< f.<]
+ [/.<= f.<=]
+ [/.> f.>]
+ [/.>= f.>=]
+ [/.= f.=]
+ ))
+ ))))
+
+(def: test|i32
+ Test
+ (do [! random.monad]
+ [left ..int/32
+ right ..int/32
+
+ i32 ..int/32
+ i16 ..int/16
+ shift (# ! each (n.% 16) random.nat)]
+ (`` ($_ _.and
+ (~~ (template [<js> <lux>]
+ [(_.cover [<js>]
+ (let [expected (<lux> left right)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (<js> (/.int left) (/.int right)))))]
+
+ [/.bit_or i64.or]
+ [/.bit_xor i64.xor]
+ [/.bit_and i64.and]
+ ))
+ (_.cover [/.opposite]
+ (expression (|>> (:as Frac) f.int (i.= (i.* -1 i32)))
+ (/.opposite (/.i32 i32))))
+
+ (_.cover [/.i32]
+ (expression (|>> (:as Frac) f.int (i.= i32))
+ (/.i32 i32)))
+ (_.cover [/.to_i32]
+ (expression (|>> (:as Frac) f.int (i.= i32))
+ (/.to_i32 (/.int i32))))
+ (_.cover [/.left_shift]
+ (let [expected (i64.left_shifted shift i16)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.left_shift (/.int (.int shift))
+ (/.i32 i16)))))
+ (_.cover [/.logic_right_shift]
+ (let [expected (i64.right_shifted shift (as_int/32 i16))]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.logic_right_shift (/.int (.int shift))
+ (/.i32 i16)))))
+ (_.cover [/.arithmetic_right_shift]
+ (let [expected (i.right_shifted shift i16)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.arithmetic_right_shift (/.int (.int shift))
+ (/.i32 i16)))))
+ (_.cover [/.bit_not]
+ (let [expected (if (i.< +0 i32)
+ (as_int/32 (i64.not i32))
+ (i64.not (as_int/32 i32)))]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.bit_not (/.i32 i32)))))
+ ))))
+
+(def: test|array
+ Test
+ (do [! random.monad]
+ [size (# ! each (|>> (n.% 10) ++) random.nat)
+ index (# ! each (n.% size) random.nat)
+ items (random.list size random.safe_frac)
+ .let [expected (|> items
+ (list.item index)
+ (maybe.else f.not_a_number))]]
+ ($_ _.and
+ (_.cover [/.array /.at]
+ (and (expression (|>> (:as Frac) (f.= expected))
+ (/.at (/.int (.int index))
+ (/.array (list#each /.number items))))
+ (expression (|>> (:as Bit))
+ (|> (/.array (list#each /.number items))
+ (/.at (/.int (.int size)))
+ (/.= /.undefined)))))
+ )))
+
+(def: test|object
+ Test
+ (do [! random.monad]
+ [expected random.safe_frac
+ field (random.ascii/upper 5)
+ dummy (random.only (|>> (text#= field) not)
+ (random.ascii/upper 5))
+
+ size (# ! each (|>> (n.% 10) ++) random.nat)
+ index (# ! each (n.% size) random.nat)
+ items (random.list size random.safe_frac)]
+ ($_ _.and
+ (_.cover [/.object /.the]
+ (expression (|>> (:as Frac) (f.= expected))
+ (/.the field (/.object (list [field (/.number expected)])))))
+ (let [expected (|> items
+ (list.item index)
+ (maybe.else f.not_a_number))]
+ (_.cover [/.do]
+ (expression (|>> (:as Frac) f.int (i.= (.int index)))
+ (|> (/.array (list#each /.number items))
+ (/.do "lastIndexOf" (list (/.number expected)))))))
+ (_.cover [/.undefined]
+ (expression (|>> (:as Bit))
+ (|> (/.object (list [field (/.number expected)]))
+ (/.the dummy)
+ (/.= /.undefined))))
+ )))
+
+(def: test|computation
+ Test
+ (do [! random.monad]
+ [test random.bit
+ then random.safe_frac
+ else random.safe_frac
+
+ boolean random.bit
+ number random.frac
+ string (random.ascii/upper 5)
+
+ comment (random.ascii/upper 10)]
+ ($_ _.and
+ ..test|boolean
+ ..test|number
+ ..test|i32
+ ..test|array
+ ..test|object
+ (_.cover [/.?]
+ (let [expected (if test then else)]
+ (expression (|>> (:as Frac) (f.= expected))
+ (/.? (/.boolean test)
+ (/.number then)
+ (/.number else)))))
+ (_.cover [/.not_a_number?]
+ (and (expression (|>> (:as Bit))
+ (/.not_a_number? (/.number f.not_a_number)))
+ (expression (|>> (:as Bit) not)
+ (/.not_a_number? (/.number then)))))
+ (_.cover [/.type_of]
+ (and (expression (|>> (:as Text) (text#= "boolean"))
+ (/.type_of (/.boolean boolean)))
+ (expression (|>> (:as Text) (text#= "number"))
+ (/.type_of (/.number number)))
+ (expression (|>> (:as Text) (text#= "string"))
+ (/.type_of (/.string string)))
+ (expression (|>> (:as Text) (text#= "object"))
+ (/.type_of /.null))
+ (expression (|>> (:as Text) (text#= "object"))
+ (/.type_of (/.object (list [string (/.number number)]))))
+ (expression (|>> (:as Text) (text#= "object"))
+ (/.type_of (/.array (list (/.boolean boolean)
+ (/.number number)
+ (/.string string)))))
+ (expression (|>> (:as Text) (text#= "undefined"))
+ (/.type_of /.undefined))))
+ (_.cover [/.comment]
+ (expression (|>> (:as Frac) (f.= then))
+ (/.comment comment
+ (/.number then))))
+ )))
+
+(def: test|expression
+ Test
+ (do [! random.monad]
+ [dummy random.safe_frac
+ expected random.safe_frac]
+ (`` ($_ _.and
+ (_.for [/.Literal]
+ ..test|literal)
+ (_.for [/.Computation]
+ ..test|computation)
+ (_.cover [/.,]
+ (expression (|>> (:as Frac) (f.= expected))
+ (/., (/.number dummy) (/.number expected))))
+ ))))
+
+(def: test/var
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ number/1 random.safe_frac
+ number/2 random.safe_frac
+ foreign (random.ascii/lower 10)
+ local (random.only (|>> (text#= foreign) not)
+ (random.ascii/lower 10))
+ .let [$foreign (/.var foreign)
+ $local (/.var local)]]
+ ($_ _.and
+ (_.cover [/.var]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/* (/.closure (list $foreign) (/.return $foreign))
+ (list (/.number number/0)))))
+ (_.cover [/.define]
+ (expression (|>> (:as Frac) (f.= number/1))
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.define $local (/.number number/1))
+ (/.return $local)))
+ (list (/.number number/0)))))
+ (_.cover [/.declare]
+ (expression (|>> (:as Frac) (f.= number/1))
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.declare $local)
+ (/.set $local (/.number number/1))
+ (/.return $local)))
+ (list (/.number number/0)))))
+ )))
+
+(def: test/location
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ int/0 ..int/16
+ $foreign (# ! each /.var (random.ascii/lower 10))
+ field (random.ascii/upper 10)]
+ ($_ _.and
+ (_.cover [/.set]
+ (and (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0)))
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.+ $foreign $foreign))
+ (/.return $foreign)))
+ (list (/.number number/0))))
+ (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0)))
+ (let [@ (/.at (/.int +0) $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.array (list $foreign)))
+ (/.set @ (/.+ @ @))
+ (/.return @)))
+ (list (/.number number/0)))))
+ (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0)))
+ (let [@ (/.the field $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.object (list [field $foreign])))
+ (/.set @ (/.+ @ @))
+ (/.return @)))
+ (list (/.number number/0)))))))
+ (_.cover [/.delete]
+ (and (and (expression (|>> (:as Bit))
+ (/.apply/* (/.closure (list)
+ ($_ /.then
+ (/.set $foreign (/.number number/0))
+ (/.return (/.delete $foreign))))
+ (list)))
+ (expression (|>> (:as Bit) not)
+ (/.apply/* (/.closure (list $foreign)
+ (/.return (/.delete $foreign)))
+ (list (/.number number/0)))))
+ (expression (|>> (:as Bit))
+ (let [@ (/.at (/.int +0) $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.array (list $foreign)))
+ (/.return (|> (/.= (/.boolean true) (/.delete @))
+ (/.and (/.= /.undefined @))))))
+ (list (/.number number/0)))))
+ (expression (|>> (:as Bit))
+ (let [@ (/.the field $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.object (list [field $foreign])))
+ (/.return (|> (/.= (/.boolean true) (/.delete @))
+ (/.and (/.= /.undefined @))))))
+ (list (/.number number/0)))))
+ ))
+ (_.cover [/.Access]
+ (`` (and (~~ (template [<js> <lux>]
+ [(expression (|>> (:as Frac) f.int (i.= (<lux> int/0)))
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.statement (<js> $foreign))
+ (/.return $foreign)))
+ (list (/.int int/0))))
+ (expression (|>> (:as Frac) f.int (i.= (<lux> int/0)))
+ (let [@ (/.at (/.int +0) $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.array (list $foreign)))
+ (/.statement (<js> @))
+ (/.return @)))
+ (list (/.int int/0)))))
+ (expression (|>> (:as Frac) f.int (i.= (<lux> int/0)))
+ (let [@ (/.the field $foreign)]
+ (/.apply/* (/.closure (list $foreign)
+ ($_ /.then
+ (/.set $foreign (/.object (list [field $foreign])))
+ (/.statement (<js> @))
+ (/.return @)))
+ (list (/.int int/0)))))]
+
+ [/.++ .++]
+ [/.-- .--]
+ )))))
+ (_.for [/.Var]
+ ..test/var)
+ )))
+
+(def: test|label
+ Test
+ (do [! random.monad]
+ [input ..int/16
+
+ full_inner_iterations (# ! each (|>> (n.% 20) ++) random.nat)
+ expected_inner_iterations (# ! each (n.% full_inner_iterations) random.nat)
+
+ @outer (# ! each /.label (random.ascii/upper 5))
+ full_outer_iterations (# ! each (|>> (n.% 10) ++) random.nat)
+ expected_outer_iterations (# ! each (n.% full_outer_iterations) random.nat)
+
+ .let [$input (/.var "input")
+ $output (/.var "output")
+ $inner_index (/.var "inner_index")
+ $outer_index (/.var "outer_index")]]
+ ($_ _.and
+ (_.cover [/.break]
+ (let [expected (i.* (.int expected_inner_iterations) input)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $inner_index (/.int +0))
+ (/.define $output (/.int +0))
+ (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+ ($_ /.then
+ (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index)
+ /.break)
+ (/.set $output (/.+ $input $output))
+ (/.set $inner_index (/.+ (/.int +1) $inner_index))
+ ))
+ (/.return $output)))
+ (list (/.int input))))))
+ (_.cover [/.continue]
+ (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $inner_index (/.int +0))
+ (/.define $output (/.int +0))
+ (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+ ($_ /.then
+ (/.set $inner_index (/.+ (/.int +1) $inner_index))
+ (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index)
+ /.continue)
+ (/.set $output (/.+ $input $output))
+ ))
+ (/.return $output)))
+ (list (/.int input))))))
+ (_.for [/.label /.with_label]
+ ($_ _.and
+ (_.cover [/.break_at]
+ (let [expected (i.* (.int (n.* expected_outer_iterations
+ expected_inner_iterations))
+ input)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $output (/.int +0))
+ (/.define $outer_index (/.int +0))
+ (/.with_label @outer
+ (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index)
+ ($_ /.then
+ (/.define $inner_index (/.int +0))
+ (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+ ($_ /.then
+ (/.when (/.= (/.int (.int expected_outer_iterations)) $outer_index)
+ (/.break_at @outer))
+ (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index)
+ /.break)
+ (/.set $output (/.+ $input $output))
+ (/.set $inner_index (/.+ (/.int +1) $inner_index))
+ ))
+ (/.set $outer_index (/.+ (/.int +1) $outer_index))
+ )))
+ (/.return $output)))
+ (list (/.int input))))))
+ (_.cover [/.continue_at]
+ (let [expected (i.* (.int (n.* (n.- expected_outer_iterations full_outer_iterations)
+ (n.- expected_inner_iterations full_inner_iterations)))
+ input)]
+ (expression (|>> (:as Frac) f.int (i.= expected))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $output (/.int +0))
+ (/.define $outer_index (/.int +0))
+ (/.with_label @outer
+ (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index)
+ ($_ /.then
+ (/.set $outer_index (/.+ (/.int +1) $outer_index))
+ (/.define $inner_index (/.int +0))
+ (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+ ($_ /.then
+ (/.set $inner_index (/.+ (/.int +1) $inner_index))
+ (/.when (/.<= (/.int (.int expected_outer_iterations)) $outer_index)
+ (/.continue_at @outer))
+ (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index)
+ /.continue)
+ (/.set $output (/.+ $input $output))
+ ))
+ )
+ ))
+ (/.return $output)))
+ (list (/.int input))))))
+ ))
+ )))
+
+(def: test|loop
+ Test
+ (do [! random.monad]
+ [input ..int/16
+ iterations (# ! each (n.% 10) random.nat)
+ .let [$input (/.var "input")
+ $output (/.var "output")
+ $index (/.var "index")
+ expected|while (i.* (.int iterations) input)
+ expected|do_while (i.* (.int (n.max 1 iterations)) input)]]
+ ($_ _.and
+ (_.cover [/.while]
+ (expression (|>> (:as Frac) f.int (i.= expected|while))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $index (/.int +0))
+ (/.define $output (/.int +0))
+ (/.while (/.< (/.int (.int iterations)) $index)
+ ($_ /.then
+ (/.set $output (/.+ $input $output))
+ (/.set $index (/.+ (/.int +1) $index))
+ ))
+ (/.return $output)))
+ (list (/.int input)))))
+ (_.cover [/.do_while]
+ (expression (|>> (:as Frac) f.int (i.= expected|do_while))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $index (/.int +0))
+ (/.define $output (/.int +0))
+ (/.do_while (/.< (/.int (.int iterations)) $index)
+ ($_ /.then
+ (/.set $output (/.+ $input $output))
+ (/.set $index (/.+ (/.int +1) $index))
+ ))
+ (/.return $output)))
+ (list (/.int input)))))
+ (_.cover [/.for]
+ (expression (|>> (:as Frac) f.int (i.= expected|while))
+ (/.apply/* (/.closure (list $input)
+ ($_ /.then
+ (/.define $output (/.int +0))
+ (/.for $index (/.int +0)
+ (/.< (/.int (.int iterations)) $index)
+ (/.++ $index)
+ (/.set $output (/.+ $input $output)))
+ (/.return $output)))
+ (list (/.int input)))))
+ (_.for [/.Label]
+ ..test|label)
+ )))
+
+(def: test|exception
+ Test
+ (do [! random.monad]
+ [expected random.safe_frac
+ dummy (random.only (|>> (f.= expected) not)
+ random.safe_frac)
+ $ex (# ! each /.var (random.ascii/lower 10))]
+ ($_ _.and
+ (_.cover [/.try]
+ (expression (|>> (:as Frac) (f.= expected))
+ (/.apply/* (/.closure (list)
+ (/.try (/.return (/.number expected))
+ [$ex (/.return (/.number dummy))]))
+ (list))))
+ (_.cover [/.throw]
+ (expression (|>> (:as Frac) (f.= expected))
+ (/.apply/* (/.closure (list)
+ (/.try ($_ /.then
+ (/.throw (/.number expected))
+ (/.return (/.number dummy)))
+ [$ex (/.return $ex)]))
+ (list))))
+ )))
+
+(def: test|apply
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ number/1 random.safe_frac
+ number/2 random.safe_frac
+ $arg/0 (# ! each /.var (random.ascii/lower 10))
+ $arg/1 (# ! each /.var (random.ascii/lower 11))
+ $arg/2 (# ! each /.var (random.ascii/lower 12))]
+ (`` ($_ _.and
+ (_.cover [/.apply/1]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/1 (/.closure (list $arg/0) (/.return $arg/0))
+ (/.number number/0))))
+ (_.cover [/.apply/2]
+ (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1)))
+ (/.apply/2 (/.closure (list $arg/0 $arg/1) (/.return ($_ /.+ $arg/0 $arg/1)))
+ (/.number number/0)
+ (/.number number/1))))
+ (_.cover [/.apply/3]
+ (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1 number/2)))
+ (/.apply/3 (/.closure (list $arg/0 $arg/1 $arg/2) (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)))
+ (/.number number/0)
+ (/.number number/1)
+ (/.number number/2))))
+ (_.cover [/.apply/*]
+ (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1 number/2)))
+ (/.apply/* (/.closure (list $arg/0 $arg/1 $arg/2) (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)))
+ (list (/.number number/0)
+ (/.number number/1)
+ (/.number number/2)))))
+ ))))
+
+(def: test|function
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ iterations (# ! each (n.% 10) random.nat)
+ $self (# ! each /.var (random.ascii/lower 1))
+ $arg/0 (# ! each /.var (random.ascii/lower 2))
+ field (random.ascii/lower 3)
+ $class (# ! each /.var (random.ascii/upper 4))]
+ ($_ _.and
+ (_.cover [/.closure /.return]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/* (/.closure (list) (/.return (/.number number/0)))
+ (list))))
+ (_.cover [/.function]
+ (expression (|>> (:as Frac) f.nat (n.= iterations))
+ (/.apply/1 (/.function $self (list $arg/0)
+ (/.return (/.? (/.< (/.int (.int iterations)) $arg/0)
+ (/.apply/1 $self (/.+ (/.int +1) $arg/0))
+ $arg/0)))
+ (/.int +0))))
+ (_.cover [/.function!]
+ (expression (|>> (:as Frac) f.nat (n.= iterations))
+ (/.apply/* (/.closure (list)
+ ($_ /.then
+ (/.function! $self (list $arg/0)
+ (/.return (/.? (/.< (/.int (.int iterations)) $arg/0)
+ (/.apply/1 $self (/.+ (/.int +1) $arg/0))
+ $arg/0)))
+ (/.return (/.apply/1 $self (/.int +0)))))
+ (list))))
+ (_.cover [/.new]
+ (let [$this (/.var "this")]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/1 (/.closure (list $arg/0)
+ ($_ /.then
+ (/.function! $class (list)
+ (/.set (/.the field $this) $arg/0))
+ (/.return (/.the field (/.new $class (list))))))
+ (/.number number/0)))))
+ ..test|apply
+ )))
+
+(def: test|branching
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ number/1 random.safe_frac
+ number/2 random.safe_frac
+ arg/0 (random.ascii/lower 10)
+ arg/1 (random.only (|>> (text#= arg/0) not)
+ (random.ascii/lower 10))
+ arg/2 (random.only (predicate.and (|>> (text#= arg/0) not)
+ (|>> (text#= arg/1) not))
+ (random.ascii/lower 10))
+ .let [$arg/0 (/.var arg/0)
+ $arg/1 (/.var arg/1)
+ $arg/2 (/.var arg/2)]
+ ??? random.bit
+ int ..int/16]
+ ($_ _.and
+ (_.cover [/.if]
+ (expression (|>> (:as Frac) (f.= (if ??? number/0 number/1)))
+ (/.apply/* (/.closure (list)
+ (/.if (/.boolean ???)
+ (/.return (/.number number/0))
+ (/.return (/.number number/1))))
+ (list))))
+ (_.cover [/.when]
+ (expression (|>> (:as Frac) (f.= (if ??? number/0 number/1)))
+ (/.apply/* (/.closure (list)
+ ($_ /.then
+ (/.when (/.boolean ???)
+ (/.return (/.number number/0)))
+ (/.return (/.number number/1))))
+ (list))))
+ (_.cover [/.switch]
+ (let [number/0' (%.frac number/0)
+ number/1' (%.frac number/1)
+ number/2' (%.frac number/2)]
+ (and (expression (|>> (:as Text) (text#= number/0'))
+ (/.apply/* (/.closure (list)
+ (/.switch (/.number number/0)
+ (list [(list (/.number number/0)) (/.return (/.string number/0'))]
+ [(list (/.number number/1)) (/.return (/.string number/1'))])
+ {.#None}))
+ (list)))
+ (expression (|>> (:as Text) (text#= number/1'))
+ (/.apply/* (/.closure (list)
+ (/.switch (/.number number/1)
+ (list [(list (/.number number/0)) (/.return (/.string number/0'))]
+ [(list (/.number number/1)) (/.return (/.string number/1'))])
+ {.#Some (/.return (/.string number/2'))}))
+ (list)))
+ (expression (|>> (:as Text) (text#= number/2'))
+ (/.apply/* (/.closure (list)
+ (/.switch (/.number number/2)
+ (list [(list (/.number number/0)) (/.return (/.string number/0'))]
+ [(list (/.number number/1)) (/.return (/.string number/1'))])
+ {.#Some (/.return (/.string number/2'))}))
+ (list)))
+ )))
+ )))
+
+(def: test|statement
+ Test
+ (do [! random.monad]
+ [number/0 random.safe_frac
+ number/1 random.safe_frac
+ number/2 random.safe_frac
+ $arg/0 (# ! each /.var (random.ascii/lower 10))
+ $arg/1 (# ! each /.var (random.ascii/lower 11))
+ $arg/2 (# ! each /.var (random.ascii/lower 12))
+ ??? random.bit
+ int ..int/16]
+ (`` ($_ _.and
+ (_.cover [/.statement]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/1 (/.closure (list $arg/0)
+ ($_ /.then
+ (/.statement (/.+ $arg/0 $arg/0))
+ (/.return $arg/0)))
+ (/.number number/0))))
+ (~~ (template [<js> <lux>]
+ [(_.cover [<js>]
+ (expression (|>> (:as Frac) f.int (i.= (<lux> int)))
+ (/.apply/1 (/.closure (list $arg/0)
+ (/.return (/., (<js> $arg/0)
+ $arg/0)))
+ (/.int int))))]
+
+ [/.++ .++]
+ [/.-- .--]
+ ))
+ (_.cover [/.then]
+ (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/2 (/.closure (list $arg/0 $arg/1)
+ ($_ /.then
+ (/.return $arg/0)
+ (/.return $arg/1)))
+ (/.number number/0)
+ (/.number number/1))))
+ (_.cover [/.use_strict]
+ (and (expression (|>> (:as Frac) (f.= number/0))
+ (/.apply/* (/.closure (list)
+ ($_ /.then
+ /.use_strict
+ (/.declare $arg/0)
+ (/.set $arg/0 (/.number number/0))
+ (/.return $arg/0)))
+ (list)))
+ (|> (/.apply/* (/.closure (list)
+ ($_ /.then
+ /.use_strict
+ ... (/.declare $arg/0)
+ (/.set $arg/0 (/.number number/0))
+ (/.return $arg/0)))
+ (list))
+ ..eval
+ (case> {try.#Success it}
+ false
+
+ {try.#Failure error}
+ true))))
+ ..test|exception
+ ..test|function
+ ..test|branching
+ (_.for [/.Location]
+ ..test/location)
+ (_.for [/.Loop]
+ ..test|loop)
+ ))))
+
+(def: .public test
+ Test
+ (do [! random.monad]
+ []
+ (<| (_.covering /._)
+ (_.for [/.Code /.code])
+ (`` ($_ _.and
+ (_.for [/.Expression]
+ ..test|expression)
+ (_.for [/.Statement]
+ ..test|statement)
+ )))))