From b68f2b6aead6224c14902c80fc00c27705eece6c Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 16 Feb 2022 02:32:09 -0400 Subject: FIXED generating artifact IDs in the context of "lux in-module". --- stdlib/source/test/lux/data/binary.lux | 14 +- stdlib/source/test/lux/math/number/int.lux | 49 ++- .../lux/tool/compiler/language/lux/analysis.lux | 2 + .../compiler/language/lux/analysis/coverage.lux | 453 +++++++++++++++++++++ 4 files changed, 507 insertions(+), 11 deletions(-) create mode 100644 stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index 0a354092d..c9e821229 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -19,8 +19,8 @@ [math ["[0]" random {"+" Random}] [number - ["[0]" i64] - ["n" nat]]]]] + ["n" nat] + ["[0]" i64]]]]] [\\library ["[0]" / ["!" \\unsafe]]]) @@ -204,6 +204,7 @@ (_.cover [/.after] (and (# /.equivalence = sample (/.after 0 sample)) (# /.equivalence = (/.empty 0) (/.after size sample)) + (n.= (n.- offset size) (/.size (/.after offset sample))) (case (list.reversed (..as_list sample)) {.#End} false @@ -227,6 +228,15 @@ copy/1 (/.read/8! 1 copy)] (in (and (n.= sample/0 copy/0) (n.= 0 copy/1))))))) + (_.cover [/.cannot_copy] + (and (not (throws? /.cannot_copy + (/.copy size 0 sample 0 (/.empty size)))) + (throws? /.cannot_copy + (/.copy (n.+ offset size) 0 sample 0 (/.empty size))) + (throws? /.cannot_copy + (/.copy size offset sample 0 (/.empty size))) + (throws? /.cannot_copy + (/.copy size 0 sample offset (/.empty size))))) ..test|unsafe )))) diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux index 394c34c15..2c47ee6d1 100644 --- a/stdlib/source/test/lux/math/number/int.lux +++ b/stdlib/source/test/lux/math/number/int.lux @@ -36,15 +36,15 @@ ($enum.spec /.enum random.int)) (_.for [/.interval] ($interval.spec /.interval random.int)) - (~~ (template [ ] - [(_.for [ ] + (~~ (template [] + [(_.for [] ($monoid.spec /.equivalence random.int))] - [/.+ /.addition] - [/.* /.multiplication] + [/.addition] + [/.multiplication] - [/.min /.minimum] - [/.max /.maximum] + [/.minimum] + [/.maximum] )) (~~ (template [] [(_.for [] @@ -77,24 +77,55 @@ Test (<| (_.covering /._) (_.for [.Int]) + (let [(^open "/#[0]") /.interval]) ($_ _.and (do random.monad - [sample random.int] + [sample random.int + left random.int + right random.int] ($_ _.and + (_.cover [/.+] + (and (/.= (/.+ left right) + (/.+ right left)) + (/.= sample (/.+ +0 sample)))) (_.cover [/.-] (and (/.= +0 (/.- sample sample)) (/.= sample (/.- +0 sample)) (/.= (/.opposite sample) - (/.- sample +0)))) + (/.- sample +0)) + (/.= /#bottom + (/.- /#bottom +0)))) + (_.cover [/.*] + (and (/.= (/.* left right) + (/.* right left)) + (/.= sample (/.* +1 sample)) + (/.= /#bottom + (/.* -1 /#bottom)))) (_.cover [/./] (and (/.= +1 (/./ sample sample)) - (/.= sample (/./ +1 sample)))) + (/.= sample (/./ +1 sample)) + (/.= /#bottom + (/./ -1 /#bottom)))) (_.cover [/.abs] (bit#= (/.> sample (/.abs sample)) (/.negative? sample))) (_.cover [/.signum] (/.= (/.abs sample) (/.* (/.signum sample) sample))) + (_.cover [/.min] + (and (/.= (/.min left right) + (/.min right left)) + (/.= sample + (/.min /#top sample)) + (/.= /#bottom + (/.min /#bottom sample)))) + (_.cover [/.max] + (and (/.= (/.max left right) + (/.max right left)) + (/.= /#top + (/.max /#top sample)) + (/.= sample + (/.max /#bottom sample)))) )) (do random.monad [left random.int diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux index 858a294ae..75f0d5d1c 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux @@ -33,6 +33,7 @@ ["[1][0]" scope] ["[1][0]" simple] ["[1][0]" type] + ["[1][0]" coverage] [//// ["[1][0]" reference ["[2][0]" variable]] @@ -474,4 +475,5 @@ /scope.test /simple.test /type.test + /coverage.test )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux new file mode 100644 index 000000000..ab856f9a1 --- /dev/null +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -0,0 +1,453 @@ +(.using + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + ["[0]" monad {"+" do}] + ["[0]" predicate] + [\\specification + ["$[0]" equivalence]]] + [control + [pipe {"+" case>}] + ["[0]" try {"+" Try} ("[1]#[0]" functor)] + ["[0]" exception {"+" Exception}]] + [data + ["[0]" product] + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format]] + [collection + ["[0]" set] + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat ("[1]#[0]" interval)] + ["i" int] + ["r" rev] + ["f" frac]]]]] + [\\library + ["[0]" / + ["/[1]" // "_" + ["[1][0]" simple] + ["[1][0]" complex] + ["[1][0]" pattern {"+" Pattern}]]]]) + +(def: spread 16) + +(def: random_tag + (Random Nat) + (random#each (n.% ..spread) random.nat)) + +(def: .public random + (Random /.Coverage) + (<| random.rec + (function (_ again)) + ($_ random.or + (random#in []) + random.bit + (random.set n.hash ..spread random.nat) + (random.set i.hash ..spread random.int) + (random.set r.hash ..spread random.rev) + (random.set f.hash ..spread random.frac) + (random.set text.hash ..spread (random.unicode 1)) + ($_ random.and + (random.maybe (random#in ..spread)) + (do [! random.monad] + [cases ..random_tag + cases (random.set n.hash cases ..random_tag)] + (|> cases + set.list + (monad.each ! (function (_ case) (# ! each (|>> [case]) again))) + (# ! each (dictionary.of_list n.hash)))) + ) + (random.and again again) + (random.and again again) + ))) + +(def: (ranged min range) + (-> Nat Nat (Random Nat)) + (random#each (|>> (n.% (++ range)) (n.+ min)) + random.nat)) + +(def: random_pattern + (Random [/.Coverage Pattern]) + (<| random.rec + (function (_ again)) + (`` ($_ random.either + (random#in [{/.#Exhaustive} + {//pattern.#Simple {//simple.#Unit}}]) + (do random.monad + [it random.bit] + (in [{/.#Bit it} + {//pattern.#Simple {//simple.#Bit it}}])) + (~~ (template [ ] + [(do random.monad + [it ] + (in [{ (set.of_list (list it))} + {//pattern.#Simple { it}}]))] + + [random.nat n.hash /.#Nat //simple.#Nat] + [random.int i.hash /.#Int //simple.#Int] + [random.rev r.hash /.#Rev //simple.#Rev] + [random.frac f.hash /.#Frac //simple.#Frac] + [(random.unicode 1) text.hash /.#Text //simple.#Text] + )) + + (do [! random.monad] + [tag (# ! each ++ ..random_tag) + right? random.bit + .let [lefts (//complex.lefts right? tag)] + [sub_coverage sub_pattern] again] + (in [{/.#Variant (if right? {.#Some tag} {.#None}) + (dictionary.of_list n.hash (list [tag sub_coverage]))} + {//pattern.#Complex + {//complex.#Variant + [//complex.#lefts lefts + //complex.#right? right? + //complex.#value sub_pattern]}}])) + + (do [! random.monad] + [arity (..ranged 2 (n.- 2 ..spread)) + it (random.list arity again) + .let [coverages (list#each product.left it) + patterns (list#each product.right it)]] + (in [(|> coverages + (list.only (|>> /.exhaustive? not)) + list.reversed + (case> {.#End} + {/.#Exhaustive} + + {.#Item last prevs} + (list#mix (function (_ left right) + {/.#Seq left right}) + last + prevs))) + {//pattern.#Complex {//complex.#Tuple patterns}}])) + + (do random.monad + [register random.nat] + (in [{/.#Exhaustive} + {//pattern.#Bind register}])) + )))) + +(def: (failure? exception it) + (All (_ a) (-> (Exception a) (Try /.Coverage) Bit)) + (case it + {try.#Failure error} + (exception.match? exception error) + + _ + false)) + +(def: test|value + Test + (<| (let [(^open "/#[0]") /.equivalence]) + (do [! random.monad] + [left ..random + right ..random] + ($_ _.and + (_.for [/.equivalence] + ($equivalence.spec /.equivalence ..random)) + + (_.cover [/.exhaustive?] + (bit#= (/#= {/.#Exhaustive} left) + (/.exhaustive? left))) + (_.cover [/.format] + (bit#= (/#= left right) + (text#= (/.format left) (/.format right)))) + )))) + +(def: test|coverage + Test + (<| (let [(^open "/#[0]") /.equivalence]) + (do [! random.monad] + [[expected pattern] ..random_pattern] + ($_ _.and + (_.cover [/.coverage] + (|> pattern + /.coverage + (try#each (/#= expected)) + (try.else false))) + (_.cover [/.invalid_tuple] + (let [invalid? (..failure? /.invalid_tuple)] + (and (|> (list) + {//complex.#Tuple} + {//pattern.#Complex} + /.coverage + invalid?) + (|> (list pattern) + {//complex.#Tuple} + {//pattern.#Complex} + /.coverage + invalid?) + (|> (list pattern pattern) + {//complex.#Tuple} + {//pattern.#Complex} + /.coverage + invalid? + not)))) + )))) + +(def: random_partial_pattern + (Random [/.Coverage Pattern]) + (random.only (|>> product.left /.exhaustive? not) + ..random_pattern)) + +(def: test|variant + Test + (<| (let [(^open "/#[0]") /.equivalence]) + (do [! random.monad] + [[expected/0 pattern/0] ..random_partial_pattern + [expected/1 pattern/1] (random.only (|>> product.left (/#= expected/0) not) + ..random_partial_pattern) + expected_maximum (# ! each (n.+ 2) ..random_tag) + .let [random_tag (random#each (n.% expected_maximum) random.nat)] + tag/0 random_tag + tag/1 (random.only (|>> (n.= tag/0) not) random_tag) + .let [cases (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1])) + expected_minimum (++ (n.max tag/0 tag/1))]] + ($_ _.and + (_.cover [/.minimum] + (and (n.= expected_minimum (/.minimum [{.#None} cases])) + (n.= expected_maximum (/.minimum [{.#Some expected_maximum} cases])))) + (_.cover [/.maximum] + (and (n.= n#top (/.maximum [{.#None} cases])) + (n.= expected_maximum (/.maximum [{.#Some expected_maximum} cases])))) + )))) + +(def: test|composite + Test + (<| (let [(^open "/#[0]") /.equivalence]) + (do [! random.monad] + [[expected/0 pattern/0] ..random_partial_pattern + [expected/1 pattern/1] (random.only (|>> product.left (/#= expected/0) not) + ..random_partial_pattern) + [expected/2 pattern/2] (random.only ($_ predicate.and + (|>> product.left (/#= expected/0) not) + (|>> product.left (/#= expected/1) not) + (|>> product.left (case> {/.#Variant _} false _ true))) + ..random_partial_pattern) + + bit random.bit + nat random.nat + int random.int + rev random.rev + frac random.frac + text (random.unicode 1) + + arity (# ! each (n.+ 2) ..random_tag) + .let [random_tag (random#each (n.% arity) random.nat)] + tag/0 random_tag + tag/1 (random.only (|>> (n.= tag/0) not) random_tag)] + ($_ _.and + (_.cover [/.composite] + (let [composes_simples! + (`` (and (|> (/.composite {/.#Bit bit} {/.#Bit (not bit)}) + (try#each (/#= {/.#Exhaustive})) + (try.else false)) + (|> {/.#Bit bit} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false)) + (~~ (template [ ] + [(|> (/.composite { (set.of_list (list ))} + { (set.of_list (list (|> )))}) + (try#each (/#= { (set.of_list (list (|> )))})) + (try.else false)) + (|> { (set.of_list (list ))} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false))] + + [/.#Nat n.hash nat ++] + [/.#Int i.hash int ++] + [/.#Rev r.hash rev ++] + [/.#Frac f.hash frac (f.+ frac)] + [/.#Text text.hash text (%.format text)] + )))) + + composes_variants! + (let [composes_different_variants! + (let [composes? (: (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/1 expected/1]))}) + (try#each (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1]))})) + (try.else false))))] + (and (composes? {.#None} {.#None} {.#None}) + (composes? {.#Some arity} {.#None} {.#Some arity}) + (composes? {.#None} {.#Some arity} {.#Some arity}) + (composes? {.#Some arity} {.#Some arity} {.#Some arity}))) + + composes_same_variants! + (let [composes? (: (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (do try.monad + [variant (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/0 expected/1]))}) + expected (/.composite expected/0 expected/1)] + (in (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected]))} + variant))) + (try.else false))))] + (and (composes? {.#None} {.#None} {.#None}) + (composes? {.#Some arity} {.#None} {.#Some arity}) + (composes? {.#None} {.#Some arity} {.#Some arity}) + (composes? {.#Some arity} {.#Some arity} {.#Some arity})))] + (and composes_different_variants! + composes_same_variants! + (and (|> {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false)) + (|> {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false))))) + + composes_sequences! + (and (|> (/.composite {/.#Seq expected/0 expected/1} + {/.#Seq expected/1 expected/0}) + (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} + {/.#Seq expected/1 expected/0}})) + (try.else false)) + (|> (do try.monad + [seq (/.composite {/.#Seq expected/0 expected/0} + {/.#Seq expected/0 expected/1}) + expected (/.composite expected/0 expected/1)] + (in (/#= (if (/.exhaustive? expected) + expected/0 + {/.#Seq expected/0 expected}) + seq))) + (try.else false)) + (|> (do try.monad + [seq (/.composite {/.#Seq expected/0 expected/0} + {/.#Seq expected/1 expected/0}) + expected (/.composite expected/0 expected/1)] + (in (/#= {/.#Seq expected expected/0} + seq))) + (try.else false)) + (|> (/.composite {/.#Seq expected/0 expected/1} + expected/1) + (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} + expected/1})) + (try.else false)) + (|> (/.composite expected/1 + {/.#Seq expected/0 expected/1}) + (try#each (/#= {/.#Alt expected/1 + {/.#Seq expected/0 expected/1}})) + (try.else false)) + (|> (/.composite expected/0 + {/.#Seq expected/0 expected/1}) + (try#each (/#= expected/0)) + (try.else false))) + + composes_alts! + (and (|> (do try.monad + [alt (/.composite {/.#Exhaustive} + {/.#Alt expected/0 + expected/1})] + (in (/#= {/.#Exhaustive} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/1]))}})] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}})] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}] + [tag/1 expected/1]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/2]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) + expected (/.composite expected/2 expected/0)] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected] + [tag/1 expected/1]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/2]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) + expected (/.composite expected/2 expected/1)] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + expected/2})] + (in (/#= {/.#Alt expected/2 + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1]))}} + alt))) + (try.else false)))] + (and composes_simples! + composes_variants! + composes_sequences! + composes_alts!))) + (_.cover [/.redundancy] + (let [redundant? (..failure? /.redundancy)] + (`` (and (redundant? (/.composite {/.#Exhaustive} {/.#Exhaustive})) + (~~ (template [] + [(redundant? (/.composite )) + (redundant? (/.composite {/.#Exhaustive}))] + + [{/.#Bit bit}] + [{/.#Nat (set.of_list n.hash (list nat))}] + [{/.#Int (set.of_list i.hash (list int))}] + [{/.#Rev (set.of_list r.hash (list rev))}] + [{/.#Frac (set.of_list f.hash (list frac))}] + [{/.#Text (set.of_list text.hash (list text))}] + [{/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] + [{/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] + [{/.#Seq expected/0 expected/1}] + )) + (redundant? (/.composite {/.#Seq expected/0 expected/1} expected/0)))))) + (_.cover [/.variant_mismatch] + (let [mismatch? (..failure? /.variant_mismatch)] + (and (not (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) + + (mismatch? (/.composite {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + + (mismatch? (/.composite {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + + (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) + (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [arity expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [(-- arity) expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})))))) + )))) + +(def: .public test + Test + (<| (_.covering /._) + (_.for [/.Coverage]) + ($_ _.and + ..test|value + ..test|coverage + (_.for [/.Variant] + ..test|variant) + ..test|composite + ))) -- cgit v1.2.3