aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/specification/lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/specification/lux/abstract/apply.lux8
-rw-r--r--stdlib/source/specification/lux/abstract/codec.lux2
-rw-r--r--stdlib/source/specification/lux/abstract/comonad.lux6
-rw-r--r--stdlib/source/specification/lux/abstract/enum.lux2
-rw-r--r--stdlib/source/specification/lux/abstract/equivalence.lux4
-rw-r--r--stdlib/source/specification/lux/abstract/functor.lux24
-rw-r--r--stdlib/source/specification/lux/abstract/functor/contravariant.lux2
-rw-r--r--stdlib/source/specification/lux/abstract/interval.lux4
-rw-r--r--stdlib/source/specification/lux/abstract/monad.lux6
-rw-r--r--stdlib/source/specification/lux/abstract/monoid.lux6
-rw-r--r--stdlib/source/specification/lux/abstract/order.lux4
-rw-r--r--stdlib/source/specification/lux/world/console.lux7
-rw-r--r--stdlib/source/specification/lux/world/environment.lux7
-rw-r--r--stdlib/source/specification/lux/world/file.lux29
-rw-r--r--stdlib/source/specification/lux/world/shell.lux15
15 files changed, 65 insertions, 61 deletions
diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux
index 9c29ed974..460469078 100644
--- a/stdlib/source/specification/lux/abstract/apply.lux
+++ b/stdlib/source/specification/lux/abstract/apply.lux
@@ -21,7 +21,7 @@
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
(do [! random.monad]
[sample (at ! each injection random.nat)]
- (_.property "Identity."
+ (_.test "Identity."
((comparison n.=)
(/#on sample (injection function.identity))
sample))))
@@ -31,7 +31,7 @@
(do [! random.monad]
[sample random.nat
increase (at ! each n.+ random.nat)]
- (_.property "Homomorphism."
+ (_.test "Homomorphism."
((comparison n.=)
(/#on (injection sample) (injection increase))
(injection (increase sample))))))
@@ -41,7 +41,7 @@
(do [! random.monad]
[sample random.nat
increase (at ! each n.+ random.nat)]
- (_.property "Interchange."
+ (_.test "Interchange."
((comparison n.=)
(/#on (injection sample) (injection increase))
(/#on (injection increase) (injection (is (-> (-> Nat Nat) Nat)
@@ -56,7 +56,7 @@
(at ! each n.+ random.nat))
decrease (is (Random :$/1:)
(at ! each n.- random.nat))]
- (_.property "Composition."
+ (_.test "Composition."
((comparison n.=)
(|> (injection (is (-> :$/1: :$/1: :$/1:)
function.composite))
diff --git a/stdlib/source/specification/lux/abstract/codec.lux b/stdlib/source/specification/lux/abstract/codec.lux
index acbc07647..7ed8612b1 100644
--- a/stdlib/source/specification/lux/abstract/codec.lux
+++ b/stdlib/source/specification/lux/abstract/codec.lux
@@ -18,7 +18,7 @@
(do random.monad
[expected generator]
(_.for [/.Codec]
- (_.property "Isomorphism."
+ (_.test "Isomorphism."
(case (|> expected @//encoded @//decoded)
{try.#Success actual}
(@//= expected actual)
diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux
index 897c29f06..9bd0ec336 100644
--- a/stdlib/source/specification/lux/abstract/comonad.lux
+++ b/stdlib/source/specification/lux/abstract/comonad.lux
@@ -21,7 +21,7 @@
(|>> _//out (n.+ diff)))
random.nat)
.let [start (injection sample)]]
- (_.property "Left identity."
+ (_.test "Left identity."
(n.= (morphism start)
(|> start _//disjoint (_//each morphism) _//out)))))
@@ -31,7 +31,7 @@
[sample random.nat
.let [start (injection sample)
== (comparison n.=)]]
- (_.property "Right identity."
+ (_.test "Right identity."
(== start
(|> start _//disjoint (_//each _//out))))))
@@ -47,7 +47,7 @@
random.nat)
.let [start (injection sample)
== (comparison n.=)]]
- (_.property "Associativity."
+ (_.test "Associativity."
(== (|> start _//disjoint (_//each (|>> _//disjoint (_//each increase) decrease)))
(|> start _//disjoint (_//each increase) _//disjoint (_//each decrease))))))
diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux
index a1cf2820e..84cd03321 100644
--- a/stdlib/source/specification/lux/abstract/enum.lux
+++ b/stdlib/source/specification/lux/abstract/enum.lux
@@ -15,7 +15,7 @@
[sample gen_sample]
(<| (_.for [/.Enum])
(all _.and
- (_.property "Successor and predecessor are inverse functions."
+ (_.test "Successor and predecessor are inverse functions."
(and (_#= (|> sample _#succ _#pred)
sample)
(_#= (|> sample _#pred _#succ)
diff --git a/stdlib/source/specification/lux/abstract/equivalence.lux b/stdlib/source/specification/lux/abstract/equivalence.lux
index b2b643d4f..215a015fe 100644
--- a/stdlib/source/specification/lux/abstract/equivalence.lux
+++ b/stdlib/source/specification/lux/abstract/equivalence.lux
@@ -18,7 +18,7 @@
right random]
(<| (_.for [/.Equivalence])
(all _.and
- (_.property "Reflexivity"
+ (_.test "Reflexivity"
(/#= left left))
- (_.property "Symmetry"
+ (_.test "Symmetry"
(bit#= (/#= left right) (/#= right left)))))))
diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux
index e1be8eba2..383037e9e 100644
--- a/stdlib/source/specification/lux/abstract/functor.lux
+++ b/stdlib/source/specification/lux/abstract/functor.lux
@@ -26,20 +26,20 @@
(All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test))
(do [! random.monad]
[sample (at ! each injection random.nat)]
- (_.property "Identity."
- ((comparison n.=)
- (@//each function.identity sample)
- sample))))
+ (_.test "Identity."
+ ((comparison n.=)
+ (@//each function.identity sample)
+ sample))))
(def (homomorphism injection comparison (open "@//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test))
(do [! random.monad]
[sample random.nat
increase (at ! each n.+ random.nat)]
- (_.property "Homomorphism."
- ((comparison n.=)
- (@//each increase (injection sample))
- (injection (increase sample))))))
+ (_.test "Homomorphism."
+ ((comparison n.=)
+ (@//each increase (injection sample))
+ (injection (increase sample))))))
(def (composition injection comparison (open "@//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test))
@@ -47,10 +47,10 @@
[sample (at ! each injection random.nat)
increase (at ! each n.+ random.nat)
decrease (at ! each n.- random.nat)]
- (_.property "Composition."
- ((comparison n.=)
- (|> sample (@//each increase) (@//each decrease))
- (|> sample (@//each (|>> increase decrease)))))))
+ (_.test "Composition."
+ ((comparison n.=)
+ (|> sample (@//each increase) (@//each decrease))
+ (|> sample (@//each (|>> increase decrease)))))))
(def .public (spec injection comparison functor)
(All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test))
diff --git a/stdlib/source/specification/lux/abstract/functor/contravariant.lux b/stdlib/source/specification/lux/abstract/functor/contravariant.lux
index 6099ce42a..3f02e35c8 100644
--- a/stdlib/source/specification/lux/abstract/functor/contravariant.lux
+++ b/stdlib/source/specification/lux/abstract/functor/contravariant.lux
@@ -16,7 +16,7 @@
(def (identity equivalence value (open "@//[0]"))
(All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test))
- (_.property "Law of identity."
+ (_.test "Law of identity."
(equivalence
(@//each function.identity value)
value)))
diff --git a/stdlib/source/specification/lux/abstract/interval.lux b/stdlib/source/specification/lux/abstract/interval.lux
index e0a012e9b..51688e4ce 100644
--- a/stdlib/source/specification/lux/abstract/interval.lux
+++ b/stdlib/source/specification/lux/abstract/interval.lux
@@ -16,8 +16,8 @@
(do random.monad
[sample gen_sample]
(all _.and
- (_.property "No value is bigger than the top."
+ (_.test "No value is bigger than the top."
(@//< @//top sample))
- (_.property "No value is smaller than the bottom."
+ (_.test "No value is smaller than the bottom."
(order.> @//order @//bottom sample))
))))
diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux
index e95ddf67d..3613a3214 100644
--- a/stdlib/source/specification/lux/abstract/monad.lux
+++ b/stdlib/source/specification/lux/abstract/monad.lux
@@ -18,7 +18,7 @@
morphism (at ! each (function (_ diff)
(|>> (n.+ diff) _//in))
random.nat)]
- (_.property "Left identity."
+ (_.test "Left identity."
((comparison n.=)
(|> (injection sample) (_//each morphism) _//conjoint)
(morphism sample)))))
@@ -27,7 +27,7 @@
(All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test))
(do random.monad
[sample random.nat]
- (_.property "Right identity."
+ (_.test "Right identity."
((comparison n.=)
(|> (injection sample) (_//each _//in) _//conjoint)
(injection sample)))))
@@ -42,7 +42,7 @@
decrease (at ! each (function (_ diff)
(|>> (n.- diff) _//in))
random.nat)]
- (_.property "Associativity."
+ (_.test "Associativity."
((comparison n.=)
(|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint)
(|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint)))))
diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux
index dedaca77b..78f387f5f 100644
--- a/stdlib/source/specification/lux/abstract/monoid.lux
+++ b/stdlib/source/specification/lux/abstract/monoid.lux
@@ -20,13 +20,13 @@
right gen_sample]
(<| (_.for [/.Monoid])
(all _.and
- (_.property "Left identity."
+ (_.test "Left identity."
(_#= sample
(_#composite _#identity sample)))
- (_.property "Right identity."
+ (_.test "Right identity."
(_#= sample
(_#composite sample _#identity)))
- (_.property "Associativity."
+ (_.test "Associativity."
(_#= (_#composite left (_#composite mid right))
(_#composite (_#composite left mid) right)))
))))
diff --git a/stdlib/source/specification/lux/abstract/order.lux b/stdlib/source/specification/lux/abstract/order.lux
index 4d448c958..3ec435fb8 100644
--- a/stdlib/source/specification/lux/abstract/order.lux
+++ b/stdlib/source/specification/lux/abstract/order.lux
@@ -16,7 +16,7 @@
(do random.monad
[parameter generator
subject generator]
- (_.property "Values are either ordered, or they are equal. All options(_ are mutually exclusive."
+ (_.test "Values are either ordered, or they are equal. All options(_ are mutually exclusive."
(cond (@//< parameter subject)
(not (or (@//< subject parameter)
(@//= parameter subject)))
@@ -34,7 +34,7 @@
(not (or (@//= parameter value)
(@//= subject value))))
generator)]
- (_.property "Transitive property."
+ (_.test "Transitive property."
(if (@//< parameter subject)
(let [greater? (and (@//< subject extra)
(@//< parameter extra))
diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux
index 78953c351..cb17b4338 100644
--- a/stdlib/source/specification/lux/world/console.lux
+++ b/stdlib/source/specification/lux/world/console.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except)
- ["_" test (.only Test)]
[abstract
[monad (.only do)]]
[control
@@ -13,7 +12,9 @@
["[0]" text (.only)
["%" \\format (.only format)]]]
[math
- ["[0]" random]]]]
+ ["[0]" random]]
+ ["_" test (.only Test)
+ ["[0]" unit]]]]
[\\library
["[0]" /]])
@@ -52,7 +53,7 @@
_
false)]]
- (_.coverage' [/.Console]
+ (unit.coverage [/.Console]
(and can_write!
can_read!
can_close!))))))
diff --git a/stdlib/source/specification/lux/world/environment.lux b/stdlib/source/specification/lux/world/environment.lux
index 2163fc2e1..fb6600bfe 100644
--- a/stdlib/source/specification/lux/world/environment.lux
+++ b/stdlib/source/specification/lux/world/environment.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except)
- ["_" test (.only Test)]
[abstract
[monad (.only do)]]
[control
@@ -14,7 +13,9 @@
["[0]" dictionary]
["[0]" list]]]
[math
- ["[0]" random]]]]
+ ["[0]" random]]
+ ["_" test (.only Test)
+ ["[0]" unit]]]]
[\\library
["[0]" /]])
@@ -24,7 +25,7 @@
[exit random.int]
(in (do [! async.monad]
[environment (/.environment ! subject)]
- (_.coverage' [/.Environment]
+ (unit.coverage [/.Environment]
(and (not (dictionary.empty? environment))
(list.every? (|>> text.empty? not)
(dictionary.keys environment))
diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux
index dc6cb6528..0f642d2aa 100644
--- a/stdlib/source/specification/lux/world/file.lux
+++ b/stdlib/source/specification/lux/world/file.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except)
- ["_" test (.only Test)]
[abstract
[monad (.only do)]]
[control
@@ -28,7 +27,9 @@
["n" nat]]]
[world
[time
- ["[0]" instant (.only Instant) (.use "[1]#[0]" equivalence)]]]]]
+ ["[0]" instant (.only Instant) (.use "[1]#[0]" equivalence)]]]
+ ["_" test (.only Test)
+ ["[0]" unit]]]]
[\\library
["[0]" /]])
@@ -41,17 +42,17 @@
in
(do async.monad
[fs (async.future fs)]
- (all _.and'
- (_.coverage' [/.rooted]
+ (all unit.and
+ (unit.coverage [/.rooted]
(let [path (/.rooted fs parent child)]
(and (text.starts_with? parent path)
(text.ends_with? child path))))
- (_.coverage' [/.parent]
+ (unit.coverage [/.parent]
(|> (/.rooted fs parent child)
(/.parent fs)
(maybe#each (text#= parent))
(maybe.else false)))
- (_.coverage' [/.name]
+ (unit.coverage [/.name]
(|> (/.rooted fs parent child)
(/.name fs)
(text#= child)))
@@ -198,7 +199,7 @@
move&delete
(..move&delete fs parent child alternate_child)])
- (_.coverage' [/.System]
+ (unit.coverage [/.System]
(and directory?&make_directory
file?&write
file_size&read&append
@@ -228,8 +229,8 @@
cannot_make_directory!/0 (/.make_directories ! fs "")
cannot_make_directory!/1 (/.make_directories ! fs (at fs separator))])
- (all _.and'
- (_.coverage' [/.make_directories]
+ (all unit.and
+ (unit.coverage [/.make_directories]
(and (not pre_dir/0)
(not pre_dir/1)
(not pre_dir/2)
@@ -239,7 +240,7 @@
post_dir/0
post_dir/1
post_dir/2))
- (_.coverage' [/.cannot_make_directory]
+ (unit.coverage [/.cannot_make_directory]
(and (case cannot_make_directory!/0
{try.#Success _}
false
@@ -263,12 +264,12 @@
[fs (async.future fs)
make_file!/0 (/.make_file ! fs (utf8#encoded file/0) file/0)
make_file!/1 (/.make_file ! fs (utf8#encoded file/0) file/0)])
- (all _.and'
- (_.coverage' [/.make_file]
+ (all unit.and
+ (unit.coverage [/.make_file]
(case make_file!/0
{try.#Success _} true
{try.#Failure error} false))
- (_.coverage' [/.cannot_make_file]
+ (unit.coverage [/.cannot_make_file]
(case make_file!/1
{try.#Success _}
false
@@ -306,7 +307,7 @@
post_file/1 (/.exists? ! fs file)
post_dir/0 (at fs directory? dir)
post_dir/1 (/.exists? ! fs dir)])
- (_.coverage' [/.exists?]
+ (unit.coverage [/.exists?]
(and (not pre_file/0)
(not pre_file/1)
(not pre_dir/0)
diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux
index ddf544c55..bf507b536 100644
--- a/stdlib/source/specification/lux/world/shell.lux
+++ b/stdlib/source/specification/lux/world/shell.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except)
- ["_" test (.only Test)]
[abstract
[monad (.only do)]]
[control
@@ -16,7 +15,9 @@
["[0]" random]
[number
["n" nat]
- ["i" int]]]]]
+ ["i" int]]]
+ ["_" test (.only Test)
+ ["[0]" unit]]]]
[\\library
["[0]" / (.only)
[//
@@ -34,11 +35,11 @@
)
(def (can_wait! process)
- (-> (/.Process Async) _.Assertion)
+ (-> (/.Process Async) unit.Test)
(|> (at process await [])
(async#each (|>> (try#each (i.= /.normal))
(try.else false)
- (_.coverage' [/.Exit /.normal])))
+ (unit.coverage [/.Exit /.normal])))
async#conjoint))
(def (can_read! expected process)
@@ -80,13 +81,13 @@
(do !
[can_read! (..can_read! message echo)
can_destroy! (..can_destroy! sleep)]
- (all _.and'
- (_.coverage' <shell_coverage>
+ (all unit.and
+ (unit.coverage <shell_coverage>
(and can_read!
can_destroy!))
(..can_wait! echo)
))
_
- (_.coverage' <shell_coverage>
+ (unit.coverage <shell_coverage>
false))))))))