From 28c724857d76afdc40b5b036f415cc151eb66263 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 2 Dec 2020 20:37:13 -0400 Subject: Replaced "contains?" function with "key?" function. --- stdlib/source/test/aedifex.lux | 2 + stdlib/source/test/aedifex/cli.lux | 3 ++ stdlib/source/test/aedifex/command/deps.lux | 4 +- stdlib/source/test/aedifex/command/version.lux | 27 ++++++++++++++ .../source/test/aedifex/dependency/resolution.lux | 6 +-- .../source/test/lux/data/collection/dictionary.lux | 43 +++++++++++++++------- .../lux/data/collection/dictionary/ordered.lux | 13 +++---- stdlib/source/test/lux/data/number/frac.lux | 40 ++++++++++++-------- stdlib/source/test/lux/data/number/i16.lux | 39 ++++++++++---------- stdlib/source/test/lux/data/number/i32.lux | 39 ++++++++++---------- stdlib/source/test/lux/data/number/i8.lux | 39 ++++++++++---------- 11 files changed, 157 insertions(+), 98 deletions(-) create mode 100644 stdlib/source/test/aedifex/command/version.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/aedifex.lux b/stdlib/source/test/aedifex.lux index 02d2b8ed2..9166a4367 100644 --- a/stdlib/source/test/aedifex.lux +++ b/stdlib/source/test/aedifex.lux @@ -9,6 +9,7 @@ ["#." artifact] ["#." input] ["#." command #_ + ["#/." version] ["#/." clean] ["#/." pom] ["#/." install] @@ -36,6 +37,7 @@ ($_ _.and /artifact.test /input.test + /command/version.test /command/clean.test /command/pom.test /command/install.test diff --git a/stdlib/source/test/aedifex/cli.lux b/stdlib/source/test/aedifex/cli.lux index 805ccee03..c4c76f32f 100644 --- a/stdlib/source/test/aedifex/cli.lux +++ b/stdlib/source/test/aedifex/cli.lux @@ -29,6 +29,8 @@ (def: command (Random /.Command) ($_ random.or + ## #Version + (random\wrap []) ## #Clean (random\wrap []) ## #POM @@ -56,6 +58,7 @@ (def: (format value) (-> /.Command (List Text)) (case value + #/.Version (list "version") #/.Clean (list "clean") #/.POM (list "pom") #/.Dependencies (list "deps") diff --git a/stdlib/source/test/aedifex/command/deps.lux b/stdlib/source/test/aedifex/command/deps.lux index 42739a5ff..2f221a7ce 100644 --- a/stdlib/source/test/aedifex/command/deps.lux +++ b/stdlib/source/test/aedifex/command/deps.lux @@ -82,7 +82,7 @@ (/.do! fs (list (///repository.mock ($///dependency/resolution.single depender-artifact depender-package) []))))] (wrap (and (and (set.member? pre dependee-artifact) (not (set.member? pre depender-artifact))) - (and (dictionary.contains? dependee post) - (dictionary.contains? depender post)))))] + (and (dictionary.key? post dependee) + (dictionary.key? post depender)))))] (_.cover' [/.do!] (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/version.lux b/stdlib/source/test/aedifex/command/version.lux new file mode 100644 index 000000000..f6196556d --- /dev/null +++ b/stdlib/source/test/aedifex/command/version.lux @@ -0,0 +1,27 @@ +(.module: + [lux #* + ["_" test (#+ Test)] + [abstract + [monad (#+ do)]] + [control + ["." try] + [concurrency + ["." promise]]] + [math + ["." random]]] + [/// + ["@." profile]] + {#program + ["." /]}) + +(def: #export test + Test + (<| (_.covering /._) + (do random.monad + [profile @profile.random] + (wrap (do promise.monad + [verdict (do (try.with promise.monad) + [_ (/.do! profile)] + (wrap true))] + (_.cover' [/.do!] + (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/dependency/resolution.lux b/stdlib/source/test/aedifex/dependency/resolution.lux index b426a100d..0b3bf1634 100644 --- a/stdlib/source/test/aedifex/dependency/resolution.lux +++ b/stdlib/source/test/aedifex/dependency/resolution.lux @@ -346,9 +346,9 @@ (_.cover' [/.all] (case resolution (#try.Success resolution) - (and (dictionary.contains? depender resolution) - (dictionary.contains? dependee resolution) - (not (dictionary.contains? ignored resolution))) + (and (dictionary.key? resolution depender) + (dictionary.key? resolution dependee) + (not (dictionary.key? resolution ignored))) (#try.Failure error) false)))) diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 718c9f0c9..b852f8dbf 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -2,6 +2,7 @@ [lux #* ["_" test (#+ Test)] [abstract + [hash (#+ Hash)] [monad (#+ do)] ["." equivalence] {[0 #spec] @@ -28,12 +29,14 @@ (def: for-dictionaries Test - (do random.monad + (do {! random.monad} [#let [capped-nat (\ random.monad map (n.% 100) random.nat)] size capped-nat dict (random.dictionary n.hash size random.nat capped-nat) - non-key (|> random.nat (random.filter (function (_ key) (not (/.contains? key dict))))) - test-val (|> random.nat (random.filter (function (_ val) (not (list.member? n.equivalence (/.values dict) val)))))] + non-key (random.filter (|>> (/.key? dict) not) + random.nat) + test-val (random.filter (|>> (list.member? n.equivalence (/.values dict)) not) + random.nat)] ($_ _.and (_.cover [/.size] (n.= size (/.size dict))) @@ -47,6 +50,16 @@ (let [sample (/.new n.hash)] (and (n.= 0 (/.size sample)) (/.empty? sample)))) + + (do ! + [constant random.nat + #let [hash (: (Hash Nat) + (structure + (def: &equivalence n.equivalence) + (def: (hash _) + constant)))]] + (_.cover [/.key-hash] + (is? hash (/.key-hash (/.new hash))))) (_.cover [/.entries /.keys /.values] (\ (list.equivalence (equivalence.product n.equivalence n.equivalence)) = @@ -82,11 +95,13 @@ [#let [capped-nat (\ random.monad map (n.% 100) random.nat)] size capped-nat dict (random.dictionary n.hash size random.nat capped-nat) - non-key (|> random.nat (random.filter (function (_ key) (not (/.contains? key dict))))) - test-val (|> random.nat (random.filter (function (_ val) (not (list.member? n.equivalence (/.values dict) val)))))] + non-key (random.filter (|>> (/.key? dict) not) + random.nat) + test-val (random.filter (|>> (list.member? n.equivalence (/.values dict)) not) + random.nat)] ($_ _.and - (_.cover [/.contains?] - (list.every? (function (_ key) (/.contains? key dict)) + (_.cover [/.key?] + (list.every? (/.key? dict) (/.keys dict))) (_.cover [/.get] @@ -130,8 +145,8 @@ (_.cover [/.remove] (and (let [base (/.put non-key test-val dict)] - (and (/.contains? non-key base) - (not (/.contains? non-key (/.remove non-key base))))) + (and (/.key? base non-key) + (not (/.key? (/.remove non-key base) non-key)))) (case (list.head (/.keys dict)) #.None true @@ -186,8 +201,8 @@ (let [first-key (|> dict /.keys list.head maybe.assume) rebound (/.re-bind first-key non-key dict)] (and (n.= (/.size dict) (/.size rebound)) - (/.contains? non-key rebound) - (not (/.contains? first-key rebound)) + (/.key? rebound non-key) + (not (/.key? rebound first-key)) (n.= (maybe.assume (/.get first-key dict)) (maybe.assume (/.get non-key rebound))))))) ))) @@ -200,8 +215,10 @@ [#let [capped-nat (\ random.monad map (n.% 100) random.nat)] size capped-nat dict (random.dictionary n.hash size random.nat capped-nat) - non-key (|> random.nat (random.filter (function (_ key) (not (/.contains? key dict))))) - test-val (|> random.nat (random.filter (function (_ val) (not (list.member? n.equivalence (/.values dict) val)))))] + non-key (random.filter (|>> (/.key? dict) not) + random.nat) + test-val (random.filter (|>> (list.member? n.equivalence (/.values dict)) not) + random.nat)] ($_ _.and (_.with-cover [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index c34f3e3cf..01920fa1c 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -32,8 +32,7 @@ _ (do random.monad [partial (dictionary order gen-key gen-value (dec size)) - key (random.filter (function (_ candidate) - (not (/.contains? candidate partial))) + key (random.filter (|>> (/.key? partial) not) gen-key) value gen-value] (wrap (/.put key value partial))))) @@ -103,14 +102,14 @@ (|> sample /.entries (/.from-list n.order) (/\= sample))) - (_.cover [/.contains?] - (and (list.every? (function (_ key) (/.contains? key sample)) + (_.cover [/.key?] + (and (list.every? (/.key? sample) (/.keys sample)) - (not (/.contains? extra-key sample)))) + (not (/.key? sample extra-key)))) (_.cover [/.put] - (and (not (/.contains? extra-key sample)) + (and (not (/.key? sample extra-key)) (let [sample+ (/.put extra-key extra-value sample)] - (and (/.contains? extra-key sample+) + (and (/.key? sample+ extra-key) (n.= (inc (/.size sample)) (/.size sample+)))))) (_.cover [/.get] diff --git a/stdlib/source/test/lux/data/number/frac.lux b/stdlib/source/test/lux/data/number/frac.lux index ca3d4d21c..b9669756d 100644 --- a/stdlib/source/test/lux/data/number/frac.lux +++ b/stdlib/source/test/lux/data/number/frac.lux @@ -10,7 +10,9 @@ ["$." monoid] ["$." codec]]}] [data - ["." bit ("#\." equivalence)]] + ["." bit ("#\." equivalence)] + [text + ["%" format (#+ format)]]] [math ["." random (#+ Random)]]] {1 @@ -32,14 +34,15 @@ ($equivalence.spec /.equivalence random.safe-frac)) (_.with-cover [/.order /.<] ($order.spec /.order random.safe-frac)) - (~~ (template [ ] + (~~ (template [ ] [(_.with-cover [ ] ($monoid.spec /.equivalence ..random))] - [/.addition /.+] - [/.multiplication /.*] - [/.minimum /.min] - [/.maximum /.max] + [/.+ /.addition] + [/.* /.multiplication] + + [/.min /.minimum] + [/.max /.maximum] )) (~~ (template [] [(_.with-cover [] @@ -161,16 +164,21 @@ (/.* (/.signum sample) sample))))) (do random.monad [expected random.frac] - ($_ _.and - (_.cover [/.to-bits /.from-bits] - (let [actual (|> expected /.to-bits /.from-bits)] - (or (/.= expected actual) - (and (/.not-a-number? expected) - (/.not-a-number? actual))))) - (_.cover [/.negate] - (and (/.= +0.0 (/.+ (/.negate expected) expected)) - (|> expected /.negate /.negate (/.= expected)))) - )) + (_.cover [/.to-bits /.from-bits] + (let [actual (|> expected /.to-bits /.from-bits)] + (or (/.= expected actual) + (and (/.not-a-number? expected) + (/.not-a-number? actual)))))) + (do random.monad + [expected random.safe-frac] + (_.cover [/.negate] + (let [subtraction! + (/.= +0.0 (/.+ (/.negate expected) expected)) + + inverse! + (|> expected /.negate /.negate (/.= expected))] + (and subtraction! + inverse!)))) ..signature ..constant diff --git a/stdlib/source/test/lux/data/number/i16.lux b/stdlib/source/test/lux/data/number/i16.lux index f3d8030c0..038d6d7f2 100644 --- a/stdlib/source/test/lux/data/number/i16.lux +++ b/stdlib/source/test/lux/data/number/i16.lux @@ -1,39 +1,40 @@ (.module: [lux #* ["_" test (#+ Test)] - [data - ["." name] - ["%" text/format (#+ format)]] [abstract [monad (#+ do)] {[0 #spec] [/ ["$." equivalence]]}] + [data + [number + ["i" int]]] [math - ["r" random (#+ Random)]]] + ["." random (#+ Random)]]] {1 ["." / ["/#" // #_ - ["#." i64 (#+ Mask)]]]}) + ["#." i64]]]}) -(def: #export i16 +(def: #export random (Random /.I16) - (\ r.functor map /.i16 r.i64)) - -(def: mask - Mask - (//i64.or //i64.sign - (//i64.mask 15))) + (\ random.functor map /.i16 random.i64)) (def: #export test Test - (<| (_.context (name.module (name-of /._))) - (do {! r.monad} - [expected (\ ! map (|>> (//i64.and ..mask) (: I64)) r.i64)] + (<| (_.covering /._) + (_.with-cover [/.I16]) + (do {! random.monad} + [#let [limit (|> (dec /.width) + //i64.mask + .int + inc)] + expected (\ ! map (i.% limit) random.int)] ($_ _.and - ($equivalence.spec /.equivalence ..i16) + (_.with-cover [/.equivalence] + ($equivalence.spec /.equivalence ..random)) - (_.test "Can convert between I64 and I16" - (let [actual (|> expected /.i16 /.i64)] - (\ //i64.equivalence = expected actual))) + (_.cover [/.i16 /.i64 /.width] + (let [actual (|> expected .i64 /.i16 /.i64)] + (\ //i64.equivalence = expected actual))) )))) diff --git a/stdlib/source/test/lux/data/number/i32.lux b/stdlib/source/test/lux/data/number/i32.lux index 1bf6bfee7..11dd6f3f9 100644 --- a/stdlib/source/test/lux/data/number/i32.lux +++ b/stdlib/source/test/lux/data/number/i32.lux @@ -1,39 +1,40 @@ (.module: [lux #* ["_" test (#+ Test)] - [data - ["." name] - ["%" text/format (#+ format)]] [abstract [monad (#+ do)] {[0 #spec] [/ ["$." equivalence]]}] + [data + [number + ["i" int]]] [math - ["r" random (#+ Random)]]] + ["." random (#+ Random)]]] {1 ["." / ["/#" // #_ - ["#." i64 (#+ Mask)]]]}) + ["#." i64]]]}) -(def: #export i32 +(def: #export random (Random /.I32) - (\ r.functor map /.i32 r.i64)) - -(def: mask - Mask - (//i64.or //i64.sign - (//i64.mask 31))) + (\ random.functor map /.i32 random.i64)) (def: #export test Test - (<| (_.context (name.module (name-of /._))) - (do {! r.monad} - [expected (\ ! map (|>> (//i64.and ..mask) (: I64)) r.i64)] + (<| (_.covering /._) + (_.with-cover [/.I32]) + (do {! random.monad} + [#let [limit (|> (dec /.width) + //i64.mask + .int + inc)] + expected (\ ! map (i.% limit) random.int)] ($_ _.and - ($equivalence.spec /.equivalence ..i32) + (_.with-cover [/.equivalence] + ($equivalence.spec /.equivalence ..random)) - (_.test "Can convert between I64 and I32" - (let [actual (|> expected /.i32 /.i64)] - (\ //i64.equivalence = expected actual))) + (_.cover [/.i32 /.i64 /.width] + (let [actual (|> expected .i64 /.i32 /.i64)] + (\ //i64.equivalence = expected actual))) )))) diff --git a/stdlib/source/test/lux/data/number/i8.lux b/stdlib/source/test/lux/data/number/i8.lux index 88f456bca..b855ac1e0 100644 --- a/stdlib/source/test/lux/data/number/i8.lux +++ b/stdlib/source/test/lux/data/number/i8.lux @@ -1,39 +1,40 @@ (.module: [lux #* ["_" test (#+ Test)] - [data - ["." name] - ["%" text/format (#+ format)]] [abstract [monad (#+ do)] {[0 #spec] [/ ["$." equivalence]]}] + [data + [number + ["i" int]]] [math - ["r" random (#+ Random)]]] + ["." random (#+ Random)]]] {1 ["." / ["/#" // #_ - ["#." i64 (#+ Mask)]]]}) + ["#." i64]]]}) -(def: #export i8 +(def: #export random (Random /.I8) - (\ r.functor map /.i8 r.i64)) - -(def: mask - Mask - (//i64.or //i64.sign - (//i64.mask 7))) + (\ random.functor map /.i8 random.i64)) (def: #export test Test - (<| (_.context (name.module (name-of /._))) - (do {! r.monad} - [expected (\ ! map (|>> (//i64.and ..mask) (: I64)) r.i64)] + (<| (_.covering /._) + (_.with-cover [/.I8]) + (do {! random.monad} + [#let [limit (|> (dec /.width) + //i64.mask + .int + inc)] + expected (\ ! map (i.% limit) random.int)] ($_ _.and - ($equivalence.spec /.equivalence ..i8) + (_.with-cover [/.equivalence] + ($equivalence.spec /.equivalence ..random)) - (_.test "Can convert between I64 and I8" - (let [actual (|> expected /.i8 /.i64)] - (\ //i64.equivalence = expected actual))) + (_.cover [/.i8 /.i64 /.width] + (let [actual (|> expected .i64 /.i8 /.i64)] + (\ //i64.equivalence = expected actual))) )))) -- cgit v1.2.3