diff options
Diffstat (limited to 'stdlib/source/test/lux/data')
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/list.lux | 5 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/sequence.lux | 2 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/json.lux | 14 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/xml.lux | 10 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/name.lux | 12 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/product.lux | 8 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/sum.lux | 154 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text.lux | 2 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/format.lux | 163 |
10 files changed, 277 insertions, 97 deletions
diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index e5f37d5de..2080e387a 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -4,7 +4,6 @@ [abstract [hash (#+ Hash)] [monad (#+ do)] - ["." equivalence] {[0 #spec] [/ ["$." equivalence] @@ -13,6 +12,7 @@ ["." try] ["." exception]] [data + ["." product] ["." maybe] [number ["n" nat]] @@ -62,7 +62,7 @@ (is? hash (/.key-hash (/.new hash))))) (_.cover [/.entries /.keys /.values] - (\ (list.equivalence (equivalence.product n.equivalence n.equivalence)) = + (\ (list.equivalence (product.equivalence n.equivalence n.equivalence)) = (/.entries dict) (list.zip/2 (/.keys dict) (/.values dict)))) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 792feeabc..ffde9bcf4 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -4,7 +4,6 @@ [abstract [monad (#+ do)] ["." enum] - ["." equivalence] {[0 #spec] [/ ["$." equivalence] @@ -315,10 +314,10 @@ (and size-of-smaller-list! can-extract-values!))) (_.cover [/.zip] - (and (\ (/.equivalence (equivalence.product n.equivalence n.equivalence)) = + (and (\ (/.equivalence (product.equivalence n.equivalence n.equivalence)) = (/.zip/2 sample/0 sample/1) ((/.zip 2) sample/0 sample/1)) - (\ (/.equivalence ($_ equivalence.product n.equivalence n.equivalence n.equivalence)) = + (\ (/.equivalence ($_ product.equivalence n.equivalence n.equivalence n.equivalence)) = (/.zip/3 sample/0 sample/1 sample/2) ((/.zip 3) sample/0 sample/1 sample/2)))) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index e24e30c58..b21741752 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -2,8 +2,6 @@ [lux #* ["_" test (#+ Test)] [abstract - [comonad (#+)] - [functor (#+)] [monad (#+ do)] [equivalence (#+ Equivalence)] ["." enum] diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux index 61ba93d30..09f608543 100644 --- a/stdlib/source/test/lux/data/format/json.lux +++ b/stdlib/source/test/lux/data/format/json.lux @@ -31,7 +31,7 @@ {1 ["." / (#+ JSON) ("\." equivalence)]}) -(def: #export json +(def: #export random (Random /.JSON) (random.rec (function (_ recur) @@ -67,12 +67,12 @@ (_.for [/.JSON]) (`` ($_ _.and (_.for [/.equivalence] - ($equivalence.spec /.equivalence ..json)) + ($equivalence.spec /.equivalence ..random)) (_.for [/.codec] - ($codec.spec /.equivalence /.codec ..json)) + ($codec.spec /.equivalence /.codec ..random)) (do random.monad - [sample ..json] + [sample ..random] (_.cover [/.Null /.null?] (\ bit.equivalence = (/.null? sample) @@ -80,7 +80,7 @@ #/.Null true _ false)))) (do random.monad - [expected ..json] + [expected ..random] (_.cover [/.format] (|> expected /.format @@ -147,8 +147,8 @@ [/.Boolean /.get-boolean #/.Boolean random.bit bit.equivalence] [/.Number /.get-number #/.Number random.safe-frac frac.equivalence] [/.String /.get-string #/.String (random.ascii/alpha 1) text.equivalence] - [/.Array /.get-array #/.Array (random.row 3 ..json) (row.equivalence /.equivalence)] - [/.Object /.get-object #/.Object (random.dictionary text.hash 3 (random.ascii/alpha 1) ..json) (dictionary.equivalence /.equivalence)] + [/.Array /.get-array #/.Array (random.row 3 ..random) (row.equivalence /.equivalence)] + [/.Object /.get-object #/.Object (random.dictionary text.hash 3 (random.ascii/alpha 1) ..random) (dictionary.equivalence /.equivalence)] )) (with-expansions [<boolean> (boolean) <number> (number) diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux index a263b2a82..e95b843d2 100644 --- a/stdlib/source/test/lux/data/format/xml.lux +++ b/stdlib/source/test/lux/data/format/xml.lux @@ -55,16 +55,16 @@ (random.and (..text 0 10) (..text 1 10))) -(def: #export xml +(def: #export random (Random XML) - (random.rec (function (_ xml) + (random.rec (function (_ random) (random.or (..text 1 10) (do random.monad [size (..size 0 2)] ($_ random.and ..identifier (random.dictionary name.hash size ..identifier (..text 0 10)) - (random.list size xml))))))) + (random.list size random))))))) (def: #export test Test @@ -72,9 +72,9 @@ (_.for [/.XML]) ($_ _.and (_.for [/.equivalence] - ($equivalence.spec /.equivalence ..xml)) + ($equivalence.spec /.equivalence ..random)) (_.for [/.codec] - ($codec.spec /.equivalence /.codec ..xml)) + ($codec.spec /.equivalence /.codec ..random)) (do {! random.monad} [(^@ identifier [namespace name]) ..identifier] diff --git a/stdlib/source/test/lux/data/name.lux b/stdlib/source/test/lux/data/name.lux index 904c14668..dd5238aa4 100644 --- a/stdlib/source/test/lux/data/name.lux +++ b/stdlib/source/test/lux/data/name.lux @@ -24,7 +24,7 @@ (random.filter (|>> (text.contains? ".") not) (random.unicode size))) -(def: #export (name module-size short-size) +(def: #export (random module-size short-size) (-> Nat Nat (Random Name)) (random.and (..part module-size) (..part short-size))) @@ -36,19 +36,19 @@ [## First Name sizeM1 (|> random.nat (\ ! map (n.% 100))) sizeS1 (|> random.nat (\ ! map (|>> (n.% 100) (n.max 1)))) - (^@ name1 [module1 short1]) (..name sizeM1 sizeS1) + (^@ name1 [module1 short1]) (..random sizeM1 sizeS1) ## Second Name sizeM2 (|> random.nat (\ ! map (n.% 100))) sizeS2 (|> random.nat (\ ! map (|>> (n.% 100) (n.max 1)))) - (^@ name2 [module2 short2]) (..name sizeM2 sizeS2)] + (^@ name2 [module2 short2]) (..random sizeM2 sizeS2)] (_.for [.Name] ($_ _.and (_.for [/.equivalence] - ($equivalence.spec /.equivalence (..name sizeM1 sizeS1))) + ($equivalence.spec /.equivalence (..random sizeM1 sizeS1))) (_.for [/.order] - ($order.spec /.order (..name sizeM1 sizeS1))) + ($order.spec /.order (..random sizeM1 sizeS1))) (_.for [/.codec] - (_.and ($codec.spec /.equivalence /.codec (..name sizeM1 sizeS1)) + (_.and ($codec.spec /.equivalence /.codec (..random sizeM1 sizeS1)) (let [(^open "/\.") /.codec] (_.test "Encoding an name without a module component results in text equal to the short of the name." (if (text.empty? module1) diff --git a/stdlib/source/test/lux/data/product.lux b/stdlib/source/test/lux/data/product.lux index 6e15c90b8..3c61091bb 100644 --- a/stdlib/source/test/lux/data/product.lux +++ b/stdlib/source/test/lux/data/product.lux @@ -28,6 +28,14 @@ (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence i.equivalence) (random.and random.nat random.int))) + (do random.monad + [left random.int + right random.nat] + (_.cover [/.hash] + (let [hash (/.hash i.hash n.hash)] + (n.= (n.+ (\ i.hash hash left) + (\ n.hash hash right)) + (\ hash hash [left right]))))) (<| (_.cover [/.left]) (n.= expected (/.left [expected dummy]))) diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux index 8dadcf272..7fbf816a1 100644 --- a/stdlib/source/test/lux/data/sum.lux +++ b/stdlib/source/test/lux/data/sum.lux @@ -11,7 +11,8 @@ [data ["." text] [number - ["n" nat]] + ["n" nat] + ["i" int]] [collection ["." list ("#\." functor)]]] [math @@ -25,75 +26,84 @@ (_.for [.|]) (do {! random.monad} [expected random.nat - shift random.nat]) - ($_ _.and - (_.for [/.equivalence] - ($equivalence.spec (/.equivalence n.equivalence n.equivalence) - (random.or random.nat random.nat))) + shift random.nat] + ($_ _.and + (_.for [/.equivalence] + ($equivalence.spec (/.equivalence n.equivalence n.equivalence) + (random.or random.nat random.nat))) + (do random.monad + [left random.int + right random.nat] + (_.cover [/.hash] + (let [hash (/.hash i.hash n.hash)] + (and (n.= (\ i.hash hash left) + (\ hash hash (#.Left left))) + (n.= (\ n.hash hash right) + (\ hash hash (#.Right right))))))) - (_.cover [/.left] - (|> (/.left expected) - (: (| Nat Nat)) - (case> (0 #0 actual) (n.= expected actual) - _ false))) - (_.cover [/.right] - (|> (/.right expected) - (: (| Nat Nat)) - (case> (0 #1 actual) (n.= expected actual) - _ false))) - (_.cover [/.either] - (and (|> (/.left expected) - (: (| Nat Nat)) - (/.either (n.+ shift) (n.- shift)) - (n.= (n.+ shift expected))) - (|> (/.right expected) - (: (| Nat Nat)) - (/.either (n.+ shift) (n.- shift)) - (n.= (n.- shift expected))))) - (_.cover [/.each] - (and (|> (/.left expected) - (: (| Nat Nat)) - (/.each (n.+ shift) (n.- shift)) - (case> (0 #0 actual) (n.= (n.+ shift expected) actual) _ false)) - (|> (/.right expected) - (: (| Nat Nat)) - (/.each (n.+ shift) (n.- shift)) - (case> (0 #1 actual) (n.= (n.- shift expected) actual) _ false)))) - (do ! - [size (\ ! map (n.% 5) random.nat) - expected (random.list size random.nat)] - ($_ _.and - (_.cover [/.lefts] - (let [actual (: (List (| Nat Nat)) - (list\map /.left expected))] - (and (\ (list.equivalence n.equivalence) = - expected - (/.lefts actual)) - (\ (list.equivalence n.equivalence) = - (list) - (/.rights actual))))) - (_.cover [/.rights] - (let [actual (: (List (| Nat Nat)) - (list\map /.right expected))] - (and (\ (list.equivalence n.equivalence) = - expected - (/.rights actual)) - (\ (list.equivalence n.equivalence) = - (list) - (/.lefts actual))))) - (_.cover [/.partition] - (let [[lefts rights] (|> expected - (list\map (function (_ value) - (if (n.even? value) - (/.left value) - (/.right value)))) - (: (List (| Nat Nat))) - /.partition)] - (and (\ (list.equivalence n.equivalence) = - (list.filter n.even? expected) - lefts) - (\ (list.equivalence n.equivalence) = - (list.filter (|>> n.even? not) expected) - rights)))) - )) - ))) + (_.cover [/.left] + (|> (/.left expected) + (: (| Nat Nat)) + (case> (0 #0 actual) (n.= expected actual) + _ false))) + (_.cover [/.right] + (|> (/.right expected) + (: (| Nat Nat)) + (case> (0 #1 actual) (n.= expected actual) + _ false))) + (_.cover [/.either] + (and (|> (/.left expected) + (: (| Nat Nat)) + (/.either (n.+ shift) (n.- shift)) + (n.= (n.+ shift expected))) + (|> (/.right expected) + (: (| Nat Nat)) + (/.either (n.+ shift) (n.- shift)) + (n.= (n.- shift expected))))) + (_.cover [/.each] + (and (|> (/.left expected) + (: (| Nat Nat)) + (/.each (n.+ shift) (n.- shift)) + (case> (0 #0 actual) (n.= (n.+ shift expected) actual) _ false)) + (|> (/.right expected) + (: (| Nat Nat)) + (/.each (n.+ shift) (n.- shift)) + (case> (0 #1 actual) (n.= (n.- shift expected) actual) _ false)))) + (do ! + [size (\ ! map (n.% 5) random.nat) + expected (random.list size random.nat)] + ($_ _.and + (_.cover [/.lefts] + (let [actual (: (List (| Nat Nat)) + (list\map /.left expected))] + (and (\ (list.equivalence n.equivalence) = + expected + (/.lefts actual)) + (\ (list.equivalence n.equivalence) = + (list) + (/.rights actual))))) + (_.cover [/.rights] + (let [actual (: (List (| Nat Nat)) + (list\map /.right expected))] + (and (\ (list.equivalence n.equivalence) = + expected + (/.rights actual)) + (\ (list.equivalence n.equivalence) = + (list) + (/.lefts actual))))) + (_.cover [/.partition] + (let [[lefts rights] (|> expected + (list\map (function (_ value) + (if (n.even? value) + (/.left value) + (/.right value)))) + (: (List (| Nat Nat))) + /.partition)] + (and (\ (list.equivalence n.equivalence) = + (list.filter n.even? expected) + lefts) + (\ (list.equivalence n.equivalence) = + (list.filter (|>> n.even? not) expected) + rights)))) + )) + )))) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index 2dcd2bfa8..2cf0e2cfd 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -22,6 +22,7 @@ ["." / #_ ["#." buffer] ["#." encoding] + ["#." format] ["#." regex]] {1 ["." /]}) @@ -299,5 +300,6 @@ /buffer.test /encoding.test + /format.test /regex.test ))) diff --git a/stdlib/source/test/lux/data/text/format.lux b/stdlib/source/test/lux/data/text/format.lux new file mode 100644 index 000000000..a8004f919 --- /dev/null +++ b/stdlib/source/test/lux/data/text/format.lux @@ -0,0 +1,163 @@ +(.module: + [lux #* + ["_" test (#+ Test)] + [abstract + [monad (#+ do)] + [equivalence (#+ Equivalence)] + [functor + {[0 #spec] + [/ + ["$." contravariant]]}]] + [control + ["." try]] + [data + ["." text ("#\." equivalence)] + ["." bit] + ["." name] + [number + ["." nat] + ["." int] + ["." rev] + ["." frac] + ["." ratio]] + [format + ["." xml] + ["." json]] + [collection + ["." list ("#\." functor)]]] + [time + ["." instant] + ["." duration] + ["." date]] + [math + ["." random (#+ Random) ("#\." monad)] + ["." modular]] + [macro + ["." code]] + [meta + ["." location]] + ["." type]] + ["$." /// #_ + [format + ["#." xml] + ["#." json]] + ["#." name] + [// + ["#." type] + [macro + ["#." code]]]] + {1 + ["." /]}) + +(structure: (equivalence example) + (All [a] (-> a (Equivalence (/.Format a)))) + + (def: (= reference subject) + (text\= (reference example) (subject example)))) + +(def: random-contravariant + (Random (Ex [a] [(/.Format a) + (Random a)])) + ($_ random.either + (random\wrap [/.bit random.bit]) + (random\wrap [/.nat random.nat]) + (random\wrap [/.int random.int]) + (random\wrap [/.rev random.rev]) + (random\wrap [/.frac random.frac]) + )) + +(def: #export test + Test + (<| (_.covering /._) + (_.for [/.Format]) + (`` ($_ _.and + (_.for [/.functor] + (do random.monad + [[format random] ..random-contravariant + example random] + ($contravariant.spec (..equivalence example) + format + /.functor))) + + (do random.monad + [left (random.unicode 5) + mid (random.unicode 5) + right (random.unicode 5)] + (_.cover [/.format] + (text\= (/.format left mid right) + ($_ "lux text concat" left mid right)))) + (~~ (template [<format> <codec> <random>] + [(do random.monad + [sample <random>] + (_.cover [<format>] + (text\= (\ <codec> encode sample) + (<format> sample))))] + + [/.bit bit.codec random.bit] + [/.nat nat.decimal random.nat] + [/.int int.decimal random.int] + [/.rev rev.decimal random.rev] + [/.frac frac.decimal random.frac] + [/.ratio ratio.codec random.ratio] + [/.name name.codec ($///name.random 5 5)] + [/.xml xml.codec $///xml.random] + [/.json json.codec $///json.random] + [/.instant instant.codec random.instant] + [/.duration duration.codec random.duration] + [/.date date.codec random.date] + + [/.nat/2 nat.binary random.nat] + [/.nat/8 nat.octal random.nat] + [/.nat/10 nat.decimal random.nat] + [/.nat/16 nat.hex random.nat] + + [/.int/2 int.binary random.int] + [/.int/8 int.octal random.int] + [/.int/10 int.decimal random.int] + [/.int/16 int.hex random.int] + + [/.rev/2 rev.binary random.rev] + [/.rev/8 rev.octal random.rev] + [/.rev/10 rev.decimal random.rev] + [/.rev/16 rev.hex random.rev] + + [/.frac/2 frac.binary random.frac] + [/.frac/8 frac.octal random.frac] + [/.frac/10 frac.decimal random.frac] + [/.frac/16 frac.hex random.frac] + )) + (~~ (template [<format> <alias> <random>] + [(do random.monad + [sample <random>] + (_.cover [<format>] + (text\= (<alias> sample) + (<format> sample))))] + + [/.text text.encode (random.unicode 5)] + [/.code code.format $///code.random] + [/.type type.format $///type.random] + [/.location location.format + ($_ random.and + (random.unicode 5) + random.nat + random.nat)] + )) + (do random.monad + [members (random.list 5 random.nat)] + (_.cover [/.list] + (text\= (/.list /.nat members) + (|> members + (list\map /.nat) + (text.join-with " ") + list + (/.list (|>>)))))) + (do {! random.monad} + [modulus (random.one (|>> modular.from-int + try.to-maybe) + random.int) + sample (\ ! map (modular.mod modulus) + random.int)] + (_.cover [/.mod] + (text\= (\ (modular.codec modulus) encode sample) + (/.mod sample)))) + )))) |