aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/specification
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/specification/aedifex/repository.lux30
-rw-r--r--stdlib/source/specification/compositor/analysis/type.lux8
-rw-r--r--stdlib/source/specification/compositor/generation/case.lux110
-rw-r--r--stdlib/source/specification/compositor/generation/common.lux412
-rw-r--r--stdlib/source/specification/compositor/generation/function.lux70
-rw-r--r--stdlib/source/specification/compositor/generation/primitive.lux14
-rw-r--r--stdlib/source/specification/compositor/generation/reference.lux34
-rw-r--r--stdlib/source/specification/compositor/generation/structure.lux76
-rw-r--r--stdlib/source/specification/lux/abstract/apply.lux46
-rw-r--r--stdlib/source/specification/lux/abstract/codec.lux14
-rw-r--r--stdlib/source/specification/lux/abstract/comonad.lux18
-rw-r--r--stdlib/source/specification/lux/abstract/enum.lux18
-rw-r--r--stdlib/source/specification/lux/abstract/equivalence.lux8
-rw-r--r--stdlib/source/specification/lux/abstract/functor.lux24
-rw-r--r--stdlib/source/specification/lux/abstract/functor/contravariant.lux8
-rw-r--r--stdlib/source/specification/lux/abstract/hash.lux8
-rw-r--r--stdlib/source/specification/lux/abstract/interval.lux8
-rw-r--r--stdlib/source/specification/lux/abstract/mix.lux6
-rw-r--r--stdlib/source/specification/lux/abstract/monad.lux24
-rw-r--r--stdlib/source/specification/lux/abstract/monoid.lux18
-rw-r--r--stdlib/source/specification/lux/abstract/order.lux58
-rw-r--r--stdlib/source/specification/lux/world/console.lux8
-rw-r--r--stdlib/source/specification/lux/world/file.lux140
-rw-r--r--stdlib/source/specification/lux/world/program.lux48
-rw-r--r--stdlib/source/specification/lux/world/shell.lux12
25 files changed, 610 insertions, 610 deletions
diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux
index 3d4fdd69e..699a6cc52 100644
--- a/stdlib/source/specification/aedifex/repository.lux
+++ b/stdlib/source/specification/aedifex/repository.lux
@@ -36,22 +36,22 @@
.let [bad_uri (/remote.uri (the //artifact.#version invalid_artifact) invalid_artifact //artifact/extension.lux_library)]
bad_upload! (# subject upload bad_uri expected)
bad_download! (# subject download bad_uri)]
- (_.cover' [/.Repository]
- (let [successfull_flow!
- (case [good_upload! good_download!]
- [{try.#Success _} {try.#Success actual}]
- (# binary.equivalence = expected actual)
+ (_.coverage' [/.Repository]
+ (let [successfull_flow!
+ (case [good_upload! good_download!]
+ [{try.#Success _} {try.#Success actual}]
+ (# binary.equivalence = expected actual)
- _
- false)
+ _
+ false)
- failed_flow!
- (case [bad_upload! bad_download!]
- [{try.#Failure _} {try.#Failure _}]
- true
+ failed_flow!
+ (case [bad_upload! bad_download!]
+ [{try.#Failure _} {try.#Failure _}]
+ true
- _
- false)]
- (and successfull_flow!
- failed_flow!))))
+ _
+ false)]
+ (and successfull_flow!
+ failed_flow!))))
))))
diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux
index 5f2820ba2..2cbc93cea 100644
--- a/stdlib/source/specification/compositor/analysis/type.lux
+++ b/stdlib/source/specification/compositor/analysis/type.lux
@@ -57,8 +57,8 @@
[[typeC exprT exprC] ..check
[other_typeC other_exprT other_exprC] ..check]
(all _.and
- (_.test "lux check"
- (check_success+ expander state "lux check" (list typeC exprC) exprT))
- (_.test "lux coerce"
- (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT))
+ (_.property "lux check"
+ (check_success+ expander state "lux check" (list typeC exprC) exprT))
+ (_.property "lux coerce"
+ (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT))
)))
diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux
index 12fa81a14..1e5502e17 100644
--- a/stdlib/source/specification/compositor/generation/case.lux
+++ b/stdlib/source/specification/compositor/generation/case.lux
@@ -101,12 +101,12 @@
(-> Runner Test)
(do r.monad
[value r.safe_frac]
- (_.test (%.symbol (symbol synthesis.branch/let))
- (|> (synthesis.branch/let [(synthesis.f64 value)
- 0
- (synthesis.variable/local 0)])
- (run "let_spec")
- (verify value)))))
+ (_.property (%.symbol (symbol synthesis.branch/let))
+ (|> (synthesis.branch/let [(synthesis.f64 value)
+ 0
+ (synthesis.variable/local 0)])
+ (run "let_spec")
+ (verify value)))))
(def: (if_spec run)
(-> Runner Test)
@@ -114,12 +114,12 @@
[on_true r.safe_frac
on_false (|> r.safe_frac (r.only (|>> (f.= on_true) not)))
verdict r.bit]
- (_.test (%.symbol (symbol synthesis.branch/if))
- (|> (synthesis.branch/if [(synthesis.bit verdict)
- (synthesis.f64 on_true)
- (synthesis.f64 on_false)])
- (run "if_spec")
- (verify (if verdict on_true on_false))))))
+ (_.property (%.symbol (symbol synthesis.branch/if))
+ (|> (synthesis.branch/if [(synthesis.bit verdict)
+ (synthesis.f64 on_true)
+ (synthesis.f64 on_false)])
+ (run "if_spec")
+ (verify (if verdict on_true on_false))))))
(def: (case_spec run)
(-> Runner Test)
@@ -127,16 +127,16 @@
[[inputS pathS] ..case
on_success r.safe_frac
on_failure (|> r.safe_frac (r.only (|>> (f.= on_success) not)))]
- (_.test (%.symbol (symbol synthesis.branch/case))
- (|> (synthesis.branch/case
- [inputS
- (all synthesis.path/alt
- (all synthesis.path/seq
- pathS
- (synthesis.path/then (synthesis.f64 on_success)))
- (synthesis.path/then (synthesis.f64 on_failure)))])
- (run "case_spec")
- (verify on_success)))))
+ (_.property (%.symbol (symbol synthesis.branch/case))
+ (|> (synthesis.branch/case
+ [inputS
+ (all synthesis.path/alt
+ (all synthesis.path/seq
+ pathS
+ (synthesis.path/then (synthesis.f64 on_success)))
+ (synthesis.path/then (synthesis.f64 on_failure)))])
+ (run "case_spec")
+ (verify on_success)))))
(def: special_input
Synthesis
@@ -243,39 +243,39 @@
(def: (special_spec run)
(-> Runner Test)
(all _.and
- (_.test "==="
- (and (text#= (synthesis.%path special_path)
- (synthesis.%path special_pattern_path))
- (# synthesis.path_equivalence = special_path special_pattern_path)))
- (_.test "CODE"
- (|> special_input
- (run "special_input")
- (pipe.case
- {try.#Success output}
- true
-
- {try.#Failure _}
- false)))
- (_.test "PATTERN_MATCHING 0"
- (|> (synthesis.branch/case [special_input
- special_path])
- (run "special_path")
- (pipe.case
- {try.#Success output}
- true
-
- {try.#Failure _}
- false)))
- (_.test "PATTERN_MATCHING 1"
- (|> (synthesis.branch/case [special_input
- special_pattern_path])
- (run "special_pattern_path")
- (pipe.case
- {try.#Success output}
- true
-
- {try.#Failure _}
- false)))
+ (_.property "==="
+ (and (text#= (synthesis.%path special_path)
+ (synthesis.%path special_pattern_path))
+ (# synthesis.path_equivalence = special_path special_pattern_path)))
+ (_.property "CODE"
+ (|> special_input
+ (run "special_input")
+ (pipe.case
+ {try.#Success output}
+ true
+
+ {try.#Failure _}
+ false)))
+ (_.property "PATTERN_MATCHING 0"
+ (|> (synthesis.branch/case [special_input
+ special_path])
+ (run "special_path")
+ (pipe.case
+ {try.#Success output}
+ true
+
+ {try.#Failure _}
+ false)))
+ (_.property "PATTERN_MATCHING 1"
+ (|> (synthesis.branch/case [special_input
+ special_pattern_path])
+ (run "special_pattern_path")
+ (pipe.case
+ {try.#Success output}
+ true
+
+ {try.#Failure _}
+ false)))
))
(def: .public (spec run)
diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux
index 77854d953..e93a46c29 100644
--- a/stdlib/source/specification/compositor/generation/common.lux
+++ b/stdlib/source/specification/compositor/generation/common.lux
@@ -40,17 +40,17 @@
[param r.i64
subject r.i64]
(with_expansions [<binary> (template [<extension> <reference> <param_expr>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
- (synthesis.i64 subject))}
- (run (..safe <extension>))
- (pipe.case
- {try.#Success valueT}
- (n.= (<reference> param subject) (as Nat valueT))
-
- {try.#Failure _}
- false)
- (let [param <param_expr>])))]
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
+ (synthesis.i64 subject))}
+ (run (..safe <extension>))
+ (pipe.case
+ {try.#Success valueT}
+ (n.= (<reference> param subject) (as Nat valueT))
+
+ {try.#Failure _}
+ false)
+ (let [param <param_expr>])))]
["lux i64 and" i64.and param]
["lux i64 or" i64.or param]
@@ -60,20 +60,20 @@
)]
(all _.and
<binary>
- (_.test "lux i64 arithmetic-right-shift"
- (|> {synthesis.#Extension "lux i64 arithmetic-right-shift"
- (list (synthesis.i64 subject)
- (synthesis.i64 param))}
- (run (..safe "lux i64 arithmetic-right-shift"))
- (pipe.case
- {try.#Success valueT}
- ("lux i64 ="
- (i64.arithmetic_right_shifted param subject)
- (as I64 valueT))
-
- {try.#Failure _}
- false)
- (let [param (n.% 64 param)])))
+ (_.property "lux i64 arithmetic-right-shift"
+ (|> {synthesis.#Extension "lux i64 arithmetic-right-shift"
+ (list (synthesis.i64 subject)
+ (synthesis.i64 param))}
+ (run (..safe "lux i64 arithmetic-right-shift"))
+ (pipe.case
+ {try.#Success valueT}
+ ("lux i64 ="
+ (i64.arithmetic_right_shifted param subject)
+ (as I64 valueT))
+
+ {try.#Failure _}
+ false)
+ (let [param (n.% 64 param)])))
))))
(def: (i64 run)
@@ -83,16 +83,16 @@
subject r.i64]
(`` (all _.and
(~~ (template [<extension> <type> <prepare> <comp> <subject_expr>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))}
- (run (..safe <extension>))
- (pipe.case
- {try.#Success valueT}
- (<comp> (<prepare> subject) (as <type> valueT))
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))}
+ (run (..safe <extension>))
+ (pipe.case
+ {try.#Success valueT}
+ (<comp> (<prepare> subject) (as <type> valueT))
- {try.#Failure _}
- false)
- (let [subject <subject_expr>])))]
+ {try.#Failure _}
+ false)
+ (let [subject <subject_expr>])))]
["lux i64 f64" Frac i.frac f.= subject]
["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject
@@ -101,16 +101,16 @@
(as Int))]
))
(~~ (template [<extension> <reference> <outputT> <comp>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
- (synthesis.i64 subject))}
- (run (..safe <extension>))
- (pipe.case
- {try.#Success valueT}
- (<comp> (<reference> param subject) (as <outputT> valueT))
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
+ (synthesis.i64 subject))}
+ (run (..safe <extension>))
+ (pipe.case
+ {try.#Success valueT}
+ (<comp> (<reference> param subject) (as <outputT> valueT))
- {try.#Failure _}
- false)))]
+ {try.#Failure _}
+ false)))]
["lux i64 +" i.+ Int i.=]
["lux i64 -" i.- Int i.=]
@@ -133,11 +133,11 @@
subject ..simple_frac]
(`` (all _.and
(~~ (template [<extension> <reference> <comp>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
- (synthesis.f64 subject))}
- (run (..safe <extension>))
- (//case.verify (<reference> param subject))))]
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
+ (synthesis.f64 subject))}
+ (run (..safe <extension>))
+ (//case.verify (<reference> param subject))))]
["lux f64 +" f.+ f.=]
["lux f64 -" f.- f.=]
@@ -146,37 +146,37 @@
["lux f64 %" f.% f.=]
))
(~~ (template [<extension> <text>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
- (synthesis.f64 subject))}
- (run (..safe <extension>))
- (pipe.case
- {try.#Success valueV}
- (bit#= (<text> param subject)
- (as Bit valueV))
-
- _
- false)))]
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
+ (synthesis.f64 subject))}
+ (run (..safe <extension>))
+ (pipe.case
+ {try.#Success valueV}
+ (bit#= (<text> param subject)
+ (as Bit valueV))
+
+ _
+ false)))]
["lux f64 =" f.=]
["lux f64 <" f.<]
))
(~~ (template [<extension> <reference>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list)}
- (run (..safe <extension>))
- (//case.verify <reference>)))]
+ [(_.property <extension>
+ (|> {synthesis.#Extension <extension> (list)}
+ (run (..safe <extension>))
+ (//case.verify <reference>)))]
["lux f64 min" ("lux f64 min")]
["lux f64 max" ("lux f64 max")]
["lux f64 smallest" ("lux f64 smallest")]
))
- (_.test "'lux f64 i64 && 'lux i64 f64'"
- (|> (run (..safe "lux f64 i64")
- (|> subject synthesis.f64
- (list) {synthesis.#Extension "lux f64 i64"}
- (list) {synthesis.#Extension "lux i64 f64"}))
- (//case.verify subject)))
+ (_.property "'lux f64 i64 && 'lux i64 f64'"
+ (|> (run (..safe "lux f64 i64")
+ (|> subject synthesis.f64
+ (list) {synthesis.#Extension "lux f64 i64"}
+ (list) {synthesis.#Extension "lux i64 f64"}))
+ (//case.verify subject)))
))))
(def: (text run)
@@ -197,75 +197,75 @@
pre_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_upper))
post_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_alpha))]]
(all _.and
- (_.test "Can compare texts for equality."
- (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)}
- (run (..safe "lux text ="))
- (pipe.case
- {try.#Success valueV}
- (as Bit valueV)
-
- _
- false))
- (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)}
- (run (..safe "lux text ="))
- (pipe.case
- {try.#Success valueV}
- (not (as Bit valueV))
-
- _
- false))))
- (_.test "Can compare texts for order."
- (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)}
- (run (..safe "lux text <"))
- (pipe.case
- {try.#Success valueV}
- (as Bit valueV)
-
- {try.#Failure _}
- false)))
- (_.test "Can get length of text."
- (|> {synthesis.#Extension "lux text size" (list sample_lowerS)}
- (run (..safe "lux text size"))
- (pipe.case
- {try.#Success valueV}
- (n.= sample_size (as Nat valueV))
-
- _
- false)))
- (_.test "Can concatenate text."
- (|> {synthesis.#Extension "lux text size" (list concatenatedS)}
- (run (..safe "lux text size"))
- (pipe.case
- {try.#Success valueV}
- (n.= (n.* 2 sample_size) (as Nat valueV))
-
- _
- false)))
- (_.test "Can find index of sub-text."
- (and (|> {synthesis.#Extension "lux text index"
- (list concatenatedS sample_lowerS
- (synthesis.i64 +0))}
- (run (..safe "lux text index"))
- (pipe.case
- (^.multi {try.#Success valueV}
- [(as (Maybe Nat) valueV)
- {.#Some valueV}])
- (n.= 0 valueV)
-
- _
- false))
- (|> {synthesis.#Extension "lux text index"
- (list concatenatedS sample_upperS
- (synthesis.i64 +0))}
- (run (..safe "lux text index"))
- (pipe.case
- (^.multi {try.#Success valueV}
- [(as (Maybe Nat) valueV)
- {.#Some valueV}])
- (n.= sample_size valueV)
-
- _
- false))))
+ (_.property "Can compare texts for equality."
+ (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)}
+ (run (..safe "lux text ="))
+ (pipe.case
+ {try.#Success valueV}
+ (as Bit valueV)
+
+ _
+ false))
+ (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)}
+ (run (..safe "lux text ="))
+ (pipe.case
+ {try.#Success valueV}
+ (not (as Bit valueV))
+
+ _
+ false))))
+ (_.property "Can compare texts for order."
+ (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)}
+ (run (..safe "lux text <"))
+ (pipe.case
+ {try.#Success valueV}
+ (as Bit valueV)
+
+ {try.#Failure _}
+ false)))
+ (_.property "Can get length of text."
+ (|> {synthesis.#Extension "lux text size" (list sample_lowerS)}
+ (run (..safe "lux text size"))
+ (pipe.case
+ {try.#Success valueV}
+ (n.= sample_size (as Nat valueV))
+
+ _
+ false)))
+ (_.property "Can concatenate text."
+ (|> {synthesis.#Extension "lux text size" (list concatenatedS)}
+ (run (..safe "lux text size"))
+ (pipe.case
+ {try.#Success valueV}
+ (n.= (n.* 2 sample_size) (as Nat valueV))
+
+ _
+ false)))
+ (_.property "Can find index of sub-text."
+ (and (|> {synthesis.#Extension "lux text index"
+ (list concatenatedS sample_lowerS
+ (synthesis.i64 +0))}
+ (run (..safe "lux text index"))
+ (pipe.case
+ (^.multi {try.#Success valueV}
+ [(as (Maybe Nat) valueV)
+ {.#Some valueV}])
+ (n.= 0 valueV)
+
+ _
+ false))
+ (|> {synthesis.#Extension "lux text index"
+ (list concatenatedS sample_upperS
+ (synthesis.i64 +0))}
+ (run (..safe "lux text index"))
+ (pipe.case
+ (^.multi {try.#Success valueV}
+ [(as (Maybe Nat) valueV)
+ {.#Some valueV}])
+ (n.= sample_size valueV)
+
+ _
+ false))))
(let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit)
(function (_ offset length expected)
(|> {synthesis.#Extension "lux text clip"
@@ -281,23 +281,23 @@
_
false))))]
- (_.test "Can clip text to extract sub-text."
- (and (test_clip 0 sample_size sample_lower)
- (test_clip sample_size sample_size sample_upper))))
- (_.test "Can extract individual characters from text."
- (|> {synthesis.#Extension "lux text char"
- (list sample_lowerS
- (synthesis.i64 char_idx))}
- (run (..safe "lux text char"))
- (pipe.case
- (^.multi {try.#Success valueV}
- [(as (Maybe Int) valueV)
- {.#Some valueV}])
- (text.contains? ("lux i64 char" valueV)
- sample_lower)
-
- _
- false)))
+ (_.property "Can clip text to extract sub-text."
+ (and (test_clip 0 sample_size sample_lower)
+ (test_clip sample_size sample_size sample_upper))))
+ (_.property "Can extract individual characters from text."
+ (|> {synthesis.#Extension "lux text char"
+ (list sample_lowerS
+ (synthesis.i64 char_idx))}
+ (run (..safe "lux text char"))
+ (pipe.case
+ (^.multi {try.#Success valueV}
+ [(as (Maybe Int) valueV)
+ {.#Some valueV}])
+ (text.contains? ("lux i64 char" valueV)
+ sample_lower)
+
+ _
+ false)))
)))
(def: (io run)
@@ -305,57 +305,57 @@
(do r.monad
[message (r.alphabetic 5)]
(all _.and
- (_.test "Can log messages."
- (|> {synthesis.#Extension "lux io log"
- (list (synthesis.text (format "LOG: " message)))}
- (run (..safe "lux io log"))
- (pipe.case
- {try.#Success valueV}
- true
-
- {try.#Failure _}
- false)))
- (_.test "Can throw runtime errors."
- (and (|> {synthesis.#Extension "lux try"
- (list (synthesis.function/abstraction
- [synthesis.#environment (list)
- synthesis.#arity 1
- synthesis.#body {synthesis.#Extension "lux io error"
- (list (synthesis.text message))}]))}
- (run (..safe "lux try"))
- (pipe.case
- (^.multi {try.#Success valueV}
- [(as (Try Text) valueV)
- {try.#Failure error}])
- (text.contains? message error)
-
- _
- false))
- (|> {synthesis.#Extension "lux try"
- (list (synthesis.function/abstraction
- [synthesis.#environment (list)
- synthesis.#arity 1
- synthesis.#body (synthesis.text message)]))}
- (run (..safe "lux try"))
- (pipe.case
- (^.multi {try.#Success valueV}
- [(as (Try Text) valueV)
- {try.#Success valueV}])
- (text#= message valueV)
-
- _
- false))))
- (_.test "Can obtain current time in milli-seconds."
- (|> (synthesis.tuple (list {synthesis.#Extension "lux io current-time" (list)}
- {synthesis.#Extension "lux io current-time" (list)}))
- (run (..safe "lux io current-time"))
- (pipe.case
- {try.#Success valueV}
- (let [[pre post] (as [Nat Nat] valueV)]
- (n.>= pre post))
-
- {try.#Failure _}
- false)))
+ (_.property "Can log messages."
+ (|> {synthesis.#Extension "lux io log"
+ (list (synthesis.text (format "LOG: " message)))}
+ (run (..safe "lux io log"))
+ (pipe.case
+ {try.#Success valueV}
+ true
+
+ {try.#Failure _}
+ false)))
+ (_.property "Can throw runtime errors."
+ (and (|> {synthesis.#Extension "lux try"
+ (list (synthesis.function/abstraction
+ [synthesis.#environment (list)
+ synthesis.#arity 1
+ synthesis.#body {synthesis.#Extension "lux io error"
+ (list (synthesis.text message))}]))}
+ (run (..safe "lux try"))
+ (pipe.case
+ (^.multi {try.#Success valueV}
+ [(as (Try Text) valueV)
+ {try.#Failure error}])
+ (text.contains? message error)
+
+ _
+ false))
+ (|> {synthesis.#Extension "lux try"
+ (list (synthesis.function/abstraction
+ [synthesis.#environment (list)
+ synthesis.#arity 1
+ synthesis.#body (synthesis.text message)]))}
+ (run (..safe "lux try"))
+ (pipe.case
+ (^.multi {try.#Success valueV}
+ [(as (Try Text) valueV)
+ {try.#Success valueV}])
+ (text#= message valueV)
+
+ _
+ false))))
+ (_.property "Can obtain current time in milli-seconds."
+ (|> (synthesis.tuple (list {synthesis.#Extension "lux io current-time" (list)}
+ {synthesis.#Extension "lux io current-time" (list)}))
+ (run (..safe "lux io current-time"))
+ (pipe.case
+ {try.#Success valueV}
+ (let [[pre post] (as [Nat Nat] valueV)]
+ (n.>= pre post))
+
+ {try.#Failure _}
+ false)))
)))
(def: .public (spec runner)
diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux
index 6cc0d14b5..33db49436 100644
--- a/stdlib/source/specification/compositor/generation/function.lux
+++ b/stdlib/source/specification/compositor/generation/function.lux
@@ -55,40 +55,40 @@
.let [expectation (maybe.trusted (list.item (-- local) inputs))
inputsS (list#each (|>> synthesis.f64) inputs)]]
(all _.and
- (_.test "Can read arguments."
- (|> (synthesis.function/apply [synthesis.#function functionS
+ (_.property "Can read arguments."
+ (|> (synthesis.function/apply [synthesis.#function functionS
+ synthesis.#arguments inputsS])
+ (run "with_local")
+ (//case.verify expectation)))
+ (_.property "Can partially apply functions."
+ (or (n.= 1 arity)
+ (let [preS (list.first partial_arity inputsS)
+ postS (list.after partial_arity inputsS)
+ partialS (synthesis.function/apply [synthesis.#function functionS
+ synthesis.#arguments preS])]
+ (|> (synthesis.function/apply [synthesis.#function partialS
+ synthesis.#arguments postS])
+ (run "partial_application")
+ (//case.verify expectation)))))
+ (_.property "Can read environment."
+ (or (n.= 1 arity)
+ (let [environment (|> partial_arity
+ (enum.range n.enum 1)
+ (list#each (|>> {reference.#Local})))
+ variableS (if (n.<= partial_arity local)
+ (synthesis.variable/foreign (-- local))
+ (synthesis.variable/local (|> local (n.- partial_arity))))
+ inner_arity (n.- partial_arity arity)
+ innerS (synthesis.function/abstraction
+ [synthesis.#environment environment
+ synthesis.#arity inner_arity
+ synthesis.#body variableS])
+ outerS (synthesis.function/abstraction
+ [synthesis.#environment (list)
+ synthesis.#arity partial_arity
+ synthesis.#body innerS])]
+ (|> (synthesis.function/apply [synthesis.#function outerS
synthesis.#arguments inputsS])
- (run "with_local")
- (//case.verify expectation)))
- (_.test "Can partially apply functions."
- (or (n.= 1 arity)
- (let [preS (list.first partial_arity inputsS)
- postS (list.after partial_arity inputsS)
- partialS (synthesis.function/apply [synthesis.#function functionS
- synthesis.#arguments preS])]
- (|> (synthesis.function/apply [synthesis.#function partialS
- synthesis.#arguments postS])
- (run "partial_application")
- (//case.verify expectation)))))
- (_.test "Can read environment."
- (or (n.= 1 arity)
- (let [environment (|> partial_arity
- (enum.range n.enum 1)
- (list#each (|>> {reference.#Local})))
- variableS (if (n.<= partial_arity local)
- (synthesis.variable/foreign (-- local))
- (synthesis.variable/local (|> local (n.- partial_arity))))
- inner_arity (n.- partial_arity arity)
- innerS (synthesis.function/abstraction
- [synthesis.#environment environment
- synthesis.#arity inner_arity
- synthesis.#body variableS])
- outerS (synthesis.function/abstraction
- [synthesis.#environment (list)
- synthesis.#arity partial_arity
- synthesis.#body innerS])]
- (|> (synthesis.function/apply [synthesis.#function outerS
- synthesis.#arguments inputsS])
- (run "with_foreign")
- (//case.verify expectation)))))
+ (run "with_foreign")
+ (//case.verify expectation)))))
)))
diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux
index 46ba10d00..d79b226c3 100644
--- a/stdlib/source/specification/compositor/generation/primitive.lux
+++ b/stdlib/source/specification/compositor/generation/primitive.lux
@@ -32,14 +32,14 @@
(~~ (template [<evaluation_name> <synthesis> <gen> <test>]
[(do r.monad
[expected <gen>]
- (_.test (%.symbol (symbol <synthesis>))
- (|> (run <evaluation_name> (<synthesis> expected))
- (pipe.case
- {try.#Success actual}
- (<test> expected (as_expected actual))
+ (_.property (%.symbol (symbol <synthesis>))
+ (|> (run <evaluation_name> (<synthesis> expected))
+ (pipe.case
+ {try.#Success actual}
+ (<test> expected (as_expected actual))
- {try.#Failure _}
- false))))]
+ {try.#Failure _}
+ false))))]
["bit" synthesis.bit r.bit bit#=]
["i64" synthesis.i64 r.i64 "lux i64 ="]
diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux
index df9482058..f0893573f 100644
--- a/stdlib/source/specification/compositor/generation/reference.lux
+++ b/stdlib/source/specification/compositor/generation/reference.lux
@@ -29,31 +29,31 @@
(do r.monad
[name ..symbol
expected r.safe_frac]
- (_.test "Definitions."
- (|> (define name (synthesis.f64 expected))
- (pipe.case
- {try.#Success actual}
- (f.= expected (as Frac actual))
+ (_.property "Definitions."
+ (|> (define name (synthesis.f64 expected))
+ (pipe.case
+ {try.#Success actual}
+ (f.= expected (as Frac actual))
- {try.#Failure _}
- false)))))
+ {try.#Failure _}
+ false)))))
(def: (variable run)
(-> Runner Test)
(do [! r.monad]
[register (|> r.nat (# ! each (n.% 100)))
expected r.safe_frac]
- (_.test "Local variables."
- (|> (synthesis.branch/let [(synthesis.f64 expected)
- register
- (synthesis.variable/local register)])
- (run "variable")
- (pipe.case
- {try.#Success actual}
- (f.= expected (as Frac actual))
+ (_.property "Local variables."
+ (|> (synthesis.branch/let [(synthesis.f64 expected)
+ register
+ (synthesis.variable/local register)])
+ (run "variable")
+ (pipe.case
+ {try.#Success actual}
+ (f.= expected (as Frac actual))
- {try.#Failure _}
- false)))))
+ {try.#Failure _}
+ false)))))
(def: .public (spec runner definer)
(-> Runner Definer Test)
diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux
index 4423a85bf..3080f6abd 100644
--- a/stdlib/source/specification/compositor/generation/structure.lux
+++ b/stdlib/source/specification/compositor/generation/structure.lux
@@ -35,53 +35,53 @@
tag_in (|> r.nat (# ! each (n.% num_tags)))
.let [last?_in (|> num_tags -- (n.= tag_in))]
value_in r.i64]
- (_.test (%.symbol (symbol synthesis.variant))
- (|> (synthesis.variant [analysis.#lefts (if last?_in
- (-- tag_in)
- tag_in)
- analysis.#right? last?_in
- analysis.#value (synthesis.i64 value_in)])
- (run "variant")
- (pipe.case
- {try.#Success valueT}
- (let [valueT (as (Array Any) valueT)]
- (and (n.= 3 (array.size valueT))
- (let [tag_out (as java/lang/Integer (maybe.trusted (array.read! 0 valueT)))
- last?_out (array.read! 1 valueT)
- value_out (as Any (maybe.trusted (array.read! 2 valueT)))
- same_tag? (|> tag_out ffi.int_to_long (as Nat) (n.= tag_in))
- same_flag? (case last?_out
- {.#Some last?_out'}
- (and last?_in (text#= "" (as Text last?_out')))
+ (_.property (%.symbol (symbol synthesis.variant))
+ (|> (synthesis.variant [analysis.#lefts (if last?_in
+ (-- tag_in)
+ tag_in)
+ analysis.#right? last?_in
+ analysis.#value (synthesis.i64 value_in)])
+ (run "variant")
+ (pipe.case
+ {try.#Success valueT}
+ (let [valueT (as (Array Any) valueT)]
+ (and (n.= 3 (array.size valueT))
+ (let [tag_out (as java/lang/Integer (maybe.trusted (array.read! 0 valueT)))
+ last?_out (array.read! 1 valueT)
+ value_out (as Any (maybe.trusted (array.read! 2 valueT)))
+ same_tag? (|> tag_out ffi.int_to_long (as Nat) (n.= tag_in))
+ same_flag? (case last?_out
+ {.#Some last?_out'}
+ (and last?_in (text#= "" (as Text last?_out')))
- {.#None}
- (not last?_in))
- same_value? (|> value_out (as Int) (i.= value_in))]
- (and same_tag?
- same_flag?
- same_value?))))
+ {.#None}
+ (not last?_in))
+ same_value? (|> value_out (as Int) (i.= value_in))]
+ (and same_tag?
+ same_flag?
+ same_value?))))
- {try.#Failure _}
- false)))))
+ {try.#Failure _}
+ false)))))
(def: (tuple run)
(-> Runner Test)
(do [! r.monad]
[size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2))))
tuple_in (r.list size r.i64)]
- (_.test (%.symbol (symbol synthesis.tuple))
- (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in))
- (run "tuple")
- (pipe.case
- {try.#Success tuple_out}
- (let [tuple_out (as (Array Any) tuple_out)]
- (and (n.= size (array.size tuple_out))
- (list.every? (function (_ [left right])
- (i.= left (as Int right)))
- (list.zipped_2 tuple_in (array.list tuple_out)))))
+ (_.property (%.symbol (symbol synthesis.tuple))
+ (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in))
+ (run "tuple")
+ (pipe.case
+ {try.#Success tuple_out}
+ (let [tuple_out (as (Array Any) tuple_out)]
+ (and (n.= size (array.size tuple_out))
+ (list.every? (function (_ [left right])
+ (i.= left (as Int right)))
+ (list.zipped_2 tuple_in (array.list tuple_out)))))
- {try.#Failure _}
- false)))))
+ {try.#Failure _}
+ false)))))
(def: .public (spec runner)
(-> Runner Test)
diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux
index 461f304c3..3266925ce 100644
--- a/stdlib/source/specification/lux/abstract/apply.lux
+++ b/stdlib/source/specification/lux/abstract/apply.lux
@@ -20,31 +20,31 @@
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
(do [! random.monad]
[sample (# ! each injection random.nat)]
- (_.test "Identity."
- ((comparison n.=)
- (/#on sample (injection function.identity))
- sample))))
+ (_.property "Identity."
+ ((comparison n.=)
+ (/#on sample (injection function.identity))
+ sample))))
(def: (homomorphism injection comparison (open "/#[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
(do [! random.monad]
[sample random.nat
increase (# ! each n.+ random.nat)]
- (_.test "Homomorphism."
- ((comparison n.=)
- (/#on (injection sample) (injection increase))
- (injection (increase sample))))))
+ (_.property "Homomorphism."
+ ((comparison n.=)
+ (/#on (injection sample) (injection increase))
+ (injection (increase sample))))))
(def: (interchange injection comparison (open "/#[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
(do [! random.monad]
[sample random.nat
increase (# ! each n.+ random.nat)]
- (_.test "Interchange."
- ((comparison n.=)
- (/#on (injection sample) (injection increase))
- (/#on (injection increase) (injection (is (-> (-> Nat Nat) Nat)
- (function (_ f) (f sample)))))))))
+ (_.property "Interchange."
+ ((comparison n.=)
+ (/#on (injection sample) (injection increase))
+ (/#on (injection increase) (injection (is (-> (-> Nat Nat) Nat)
+ (function (_ f) (f sample)))))))))
(def: (composition injection comparison (open "/#[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
@@ -55,16 +55,16 @@
(# ! each n.+ random.nat))
decrease (is (Random :$/1:)
(# ! each n.- random.nat))]
- (_.test "Composition."
- ((comparison n.=)
- (|> (injection (is (-> :$/1: :$/1: :$/1:)
- function.composite))
- (/#on (injection increase))
- (/#on (injection decrease))
- (/#on (injection sample)))
- (/#on (/#on (injection sample)
- (injection increase))
- (injection decrease)))))))
+ (_.property "Composition."
+ ((comparison n.=)
+ (|> (injection (is (-> :$/1: :$/1: :$/1:)
+ function.composite))
+ (/#on (injection increase))
+ (/#on (injection decrease))
+ (/#on (injection sample)))
+ (/#on (/#on (injection sample)
+ (injection increase))
+ (injection decrease)))))))
(def: .public (spec injection comparison apply)
(All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test))
diff --git a/stdlib/source/specification/lux/abstract/codec.lux b/stdlib/source/specification/lux/abstract/codec.lux
index 9a39f4b1c..af4a3b157 100644
--- a/stdlib/source/specification/lux/abstract/codec.lux
+++ b/stdlib/source/specification/lux/abstract/codec.lux
@@ -18,10 +18,10 @@
(do random.monad
[expected generator]
(_.for [/.Codec]
- (_.test "Isomorphism."
- (case (|> expected @//encoded @//decoded)
- {try.#Success actual}
- (@//= expected actual)
-
- {try.#Failure _}
- false)))))
+ (_.property "Isomorphism."
+ (case (|> expected @//encoded @//decoded)
+ {try.#Success actual}
+ (@//= expected actual)
+
+ {try.#Failure _}
+ false)))))
diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux
index dca713ac2..4ef7f6b22 100644
--- a/stdlib/source/specification/lux/abstract/comonad.lux
+++ b/stdlib/source/specification/lux/abstract/comonad.lux
@@ -21,9 +21,9 @@
(|>> _//out (n.+ diff)))
random.nat)
.let [start (injection sample)]]
- (_.test "Left identity."
- (n.= (morphism start)
- (|> start _//disjoint (_//each morphism) _//out)))))
+ (_.property "Left identity."
+ (n.= (morphism start)
+ (|> start _//disjoint (_//each morphism) _//out)))))
(def: (right_identity injection comparison (open "_//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test))
@@ -31,9 +31,9 @@
[sample random.nat
.let [start (injection sample)
== (comparison n.=)]]
- (_.test "Right identity."
- (== start
- (|> start _//disjoint (_//each _//out))))))
+ (_.property "Right identity."
+ (== start
+ (|> start _//disjoint (_//each _//out))))))
(def: (associativity injection comparison (open "_//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test))
@@ -47,9 +47,9 @@
random.nat)
.let [start (injection sample)
== (comparison n.=)]]
- (_.test "Associativity."
- (== (|> start _//disjoint (_//each (|>> _//disjoint (_//each increase) decrease)))
- (|> start _//disjoint (_//each increase) _//disjoint (_//each decrease))))))
+ (_.property "Associativity."
+ (== (|> start _//disjoint (_//each (|>> _//disjoint (_//each increase) decrease)))
+ (|> start _//disjoint (_//each increase) _//disjoint (_//each decrease))))))
(def: .public (spec injection comparison subject)
(All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test))
diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux
index bff39db70..572550645 100644
--- a/stdlib/source/specification/lux/abstract/enum.lux
+++ b/stdlib/source/specification/lux/abstract/enum.lux
@@ -15,13 +15,13 @@
[sample gen_sample]
(<| (_.for [/.Enum])
(all _.and
- (_.test "Successor and predecessor are inverse functions."
- (and (_#= (|> sample _#succ _#pred)
- sample)
- (_#= (|> sample _#pred _#succ)
- sample)
- (not (_#= (_#succ sample)
- sample))
- (not (_#= (_#pred sample)
- sample))))
+ (_.property "Successor and predecessor are inverse functions."
+ (and (_#= (|> sample _#succ _#pred)
+ sample)
+ (_#= (|> sample _#pred _#succ)
+ sample)
+ (not (_#= (_#succ sample)
+ sample))
+ (not (_#= (_#pred sample)
+ sample))))
))))
diff --git a/stdlib/source/specification/lux/abstract/equivalence.lux b/stdlib/source/specification/lux/abstract/equivalence.lux
index 892d77524..21b425f3d 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
- (_.test "Reflexivity"
- (/#= left left))
- (_.test "Symmetry"
- (bit#= (/#= left right) (/#= right left)))))))
+ (_.property "Reflexivity"
+ (/#= left left))
+ (_.property "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 f5b3a6205..9e2110a97 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 (# ! each injection random.nat)]
- (_.test "Identity."
- ((comparison n.=)
- (@//each function.identity sample)
- sample))))
+ (_.property "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 (# ! each n.+ random.nat)]
- (_.test "Homomorphism."
- ((comparison n.=)
- (@//each increase (injection sample))
- (injection (increase sample))))))
+ (_.property "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 (# ! each injection random.nat)
increase (# ! each n.+ random.nat)
decrease (# ! each n.- random.nat)]
- (_.test "Composition."
- ((comparison n.=)
- (|> sample (@//each increase) (@//each decrease))
- (|> sample (@//each (|>> increase decrease)))))))
+ (_.property "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 0fca98448..291476eb4 100644
--- a/stdlib/source/specification/lux/abstract/functor/contravariant.lux
+++ b/stdlib/source/specification/lux/abstract/functor/contravariant.lux
@@ -16,10 +16,10 @@
(def: (identity equivalence value (open "@//[0]"))
(All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test))
- (_.test "Law of identity."
- (equivalence
- (@//each function.identity value)
- value)))
+ (_.property "Law of identity."
+ (equivalence
+ (@//each function.identity value)
+ value)))
(def: .public (spec equivalence value functor)
(All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test))
diff --git a/stdlib/source/specification/lux/abstract/hash.lux b/stdlib/source/specification/lux/abstract/hash.lux
index 935dc6a2d..29b5a2a2f 100644
--- a/stdlib/source/specification/lux/abstract/hash.lux
+++ b/stdlib/source/specification/lux/abstract/hash.lux
@@ -16,7 +16,7 @@
(do random.monad
[parameter random
subject random]
- (_.cover [/.Hash]
- (if (_#= parameter subject)
- (n.= (_#hash parameter) (_#hash subject))
- true))))
+ (_.coverage [/.Hash]
+ (if (_#= parameter subject)
+ (n.= (_#hash parameter) (_#hash subject))
+ true))))
diff --git a/stdlib/source/specification/lux/abstract/interval.lux b/stdlib/source/specification/lux/abstract/interval.lux
index 4ea7ca50e..10e18cd81 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
- (_.test "No value is bigger than the top."
- (@//< @//top sample))
- (_.test "No value is smaller than the bottom."
- (order.> @//order @//bottom sample))
+ (_.property "No value is bigger than the top."
+ (@//< @//top sample))
+ (_.property "No value is smaller than the bottom."
+ (order.> @//order @//bottom sample))
))))
diff --git a/stdlib/source/specification/lux/abstract/mix.lux b/stdlib/source/specification/lux/abstract/mix.lux
index 8ea932916..57b900a03 100644
--- a/stdlib/source/specification/lux/abstract/mix.lux
+++ b/stdlib/source/specification/lux/abstract/mix.lux
@@ -18,6 +18,6 @@
(do random.monad
[subject random.nat
parameter random.nat]
- (_.cover [/.Mix]
- (n.= (@//mix n.+ parameter (injection subject))
- (n.+ parameter subject)))))
+ (_.coverage [/.Mix]
+ (n.= (@//mix n.+ parameter (injection subject))
+ (n.+ parameter subject)))))
diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux
index e42b0dbdf..4344e5236 100644
--- a/stdlib/source/specification/lux/abstract/monad.lux
+++ b/stdlib/source/specification/lux/abstract/monad.lux
@@ -18,19 +18,19 @@
morphism (# ! each (function (_ diff)
(|>> (n.+ diff) _//in))
random.nat)]
- (_.test "Left identity."
- ((comparison n.=)
- (|> (injection sample) (_//each morphism) _//conjoint)
- (morphism sample)))))
+ (_.property "Left identity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each morphism) _//conjoint)
+ (morphism sample)))))
(def: (right_identity injection comparison (open "_//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test))
(do random.monad
[sample random.nat]
- (_.test "Right identity."
- ((comparison n.=)
- (|> (injection sample) (_//each _//in) _//conjoint)
- (injection sample)))))
+ (_.property "Right identity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each _//in) _//conjoint)
+ (injection sample)))))
(def: (associativity injection comparison (open "_//[0]"))
(All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test))
@@ -42,10 +42,10 @@
decrease (# ! each (function (_ diff)
(|>> (n.- diff) _//in))
random.nat)]
- (_.test "Associativity."
- ((comparison n.=)
- (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint)
- (|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint)))))
+ (_.property "Associativity."
+ ((comparison n.=)
+ (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint)
+ (|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint)))))
(def: .public (spec injection comparison monad)
(All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test))
diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux
index f6daaa867..815cf8c4d 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
- (_.test "Left identity."
- (_#= sample
- (_#composite _#identity sample)))
- (_.test "Right identity."
- (_#= sample
- (_#composite sample _#identity)))
- (_.test "Associativity."
- (_#= (_#composite left (_#composite mid right))
- (_#composite (_#composite left mid) right)))
+ (_.property "Left identity."
+ (_#= sample
+ (_#composite _#identity sample)))
+ (_.property "Right identity."
+ (_#= sample
+ (_#composite sample _#identity)))
+ (_.property "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 e6e85a1e8..18d6b845f 100644
--- a/stdlib/source/specification/lux/abstract/order.lux
+++ b/stdlib/source/specification/lux/abstract/order.lux
@@ -16,16 +16,16 @@
(do random.monad
[parameter generator
subject generator]
- (_.test "Values are either ordered, or they are equal. All options(_ are mutually exclusive."
- (cond (@//< parameter subject)
- (not (or (@//< subject parameter)
- (@//= parameter subject)))
+ (_.property "Values are either ordered, or they are equal. All options(_ are mutually exclusive."
+ (cond (@//< parameter subject)
+ (not (or (@//< subject parameter)
+ (@//= parameter subject)))
- (@//< subject parameter)
- (not (@//= parameter subject))
+ (@//< subject parameter)
+ (not (@//= parameter subject))
- ... else
- (@//= parameter subject))))
+ ... else
+ (@//= parameter subject))))
(do random.monad
[parameter generator
subject (random.only (|>> (@//= parameter) not)
@@ -34,25 +34,25 @@
(not (or (@//= parameter value)
(@//= subject value))))
generator)]
- (_.test "Transitive property."
- (if (@//< parameter subject)
- (let [greater? (and (@//< subject extra)
- (@//< parameter extra))
- lesser? (and (@//< extra parameter)
- (@//< extra subject))
- in_between? (and (@//< parameter extra)
- (@//< extra subject))]
- (or greater?
- lesser?
- in_between?))
- ... (@//< subject parameter)
- (let [greater? (and (@//< extra subject)
- (@//< extra parameter))
- lesser? (and (@//< parameter extra)
- (@//< subject extra))
- in_between? (and (@//< subject extra)
- (@//< extra parameter))]
- (or greater?
- lesser?
- in_between?)))))
+ (_.property "Transitive property."
+ (if (@//< parameter subject)
+ (let [greater? (and (@//< subject extra)
+ (@//< parameter extra))
+ lesser? (and (@//< extra parameter)
+ (@//< extra subject))
+ in_between? (and (@//< parameter extra)
+ (@//< extra subject))]
+ (or greater?
+ lesser?
+ in_between?))
+ ... (@//< subject parameter)
+ (let [greater? (and (@//< extra subject)
+ (@//< extra parameter))
+ lesser? (and (@//< parameter extra)
+ (@//< subject extra))
+ in_between? (and (@//< subject extra)
+ (@//< extra parameter))]
+ (or greater?
+ lesser?
+ in_between?)))))
)))
diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux
index e9faf9834..38bb5ed8b 100644
--- a/stdlib/source/specification/lux/world/console.lux
+++ b/stdlib/source/specification/lux/world/console.lux
@@ -52,7 +52,7 @@
_
false)]]
- (_.cover' [/.Console]
- (and can_write!
- can_read!
- can_close!))))))
+ (_.coverage' [/.Console]
+ (and can_write!
+ can_read!
+ can_close!))))))
diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux
index 75bf2a571..da20b8d30 100644
--- a/stdlib/source/specification/lux/world/file.lux
+++ b/stdlib/source/specification/lux/world/file.lux
@@ -40,19 +40,19 @@
(do async.monad
[fs (async.future fs)]
(all _.and'
- (_.cover' [/.rooted]
- (let [path (/.rooted fs parent child)]
- (and (text.starts_with? parent path)
- (text.ends_with? child path))))
- (_.cover' [/.parent]
- (|> (/.rooted fs parent child)
- (/.parent fs)
- (maybe#each (text#= parent))
- (maybe.else false)))
- (_.cover' [/.name]
- (|> (/.rooted fs parent child)
- (/.name fs)
- (text#= child)))
+ (_.coverage' [/.rooted]
+ (let [path (/.rooted fs parent child)]
+ (and (text.starts_with? parent path)
+ (text.ends_with? child path))))
+ (_.coverage' [/.parent]
+ (|> (/.rooted fs parent child)
+ (/.parent fs)
+ (maybe#each (text#= parent))
+ (maybe.else false)))
+ (_.coverage' [/.name]
+ (|> (/.rooted fs parent child)
+ (/.name fs)
+ (text#= child)))
))))
(def: (directory?&make_directory fs parent)
@@ -196,14 +196,14 @@
move&delete
(..move&delete fs parent child alternate_child)])
- (_.cover' [/.System]
- (and directory?&make_directory
- file?&write
- file_size&read&append
- modified?&last_modified
- can_execute?
- directory_files&sub_directories
- move&delete))))
+ (_.coverage' [/.System]
+ (and directory?&make_directory
+ file?&write
+ file_size&read&append
+ modified?&last_modified
+ can_execute?
+ directory_files&sub_directories
+ move&delete))))
(def: (make_directories&cannot_make_directory fs)
(-> (IO (/.System Async)) Test)
@@ -227,29 +227,29 @@
cannot_make_directory!/0 (/.make_directories ! fs "")
cannot_make_directory!/1 (/.make_directories ! fs (# fs separator))])
(all _.and'
- (_.cover' [/.make_directories]
- (and (not pre_dir/0)
- (not pre_dir/1)
- (not pre_dir/2)
- (case made?
- {try.#Success _} true
- {try.#Failure _} false)
- post_dir/0
- post_dir/1
- post_dir/2))
- (_.cover' [/.cannot_make_directory]
- (and (case cannot_make_directory!/0
- {try.#Success _}
- false
-
- {try.#Failure error}
- (exception.match? /.cannot_make_directory error))
- (case cannot_make_directory!/1
- {try.#Success _}
- false
-
- {try.#Failure error}
- (exception.match? /.cannot_make_directory error))))
+ (_.coverage' [/.make_directories]
+ (and (not pre_dir/0)
+ (not pre_dir/1)
+ (not pre_dir/2)
+ (case made?
+ {try.#Success _} true
+ {try.#Failure _} false)
+ post_dir/0
+ post_dir/1
+ post_dir/2))
+ (_.coverage' [/.cannot_make_directory]
+ (and (case cannot_make_directory!/0
+ {try.#Success _}
+ false
+
+ {try.#Failure error}
+ (exception.match? /.cannot_make_directory error))
+ (case cannot_make_directory!/1
+ {try.#Success _}
+ false
+
+ {try.#Failure error}
+ (exception.match? /.cannot_make_directory error))))
)))
(def: (make_file&cannot_make_file fs)
@@ -262,17 +262,17 @@
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'
- (_.cover' [/.make_file]
- (case make_file!/0
- {try.#Success _} true
- {try.#Failure error} false))
- (_.cover' [/.cannot_make_file]
- (case make_file!/1
- {try.#Success _}
- false
-
- {try.#Failure error}
- (exception.match? /.cannot_make_file error)))
+ (_.coverage' [/.make_file]
+ (case make_file!/0
+ {try.#Success _} true
+ {try.#Failure error} false))
+ (_.coverage' [/.cannot_make_file]
+ (case make_file!/1
+ {try.#Success _}
+ false
+
+ {try.#Failure error}
+ (exception.match? /.cannot_make_file error)))
)))
(def: (for_utilities fs)
@@ -304,23 +304,23 @@
post_file/1 (/.exists? ! fs file)
post_dir/0 (# fs directory? dir)
post_dir/1 (/.exists? ! fs dir)])
- (_.cover' [/.exists?]
- (and (not pre_file/0)
- (not pre_file/1)
- (not pre_dir/0)
- (not pre_dir/1)
+ (_.coverage' [/.exists?]
+ (and (not pre_file/0)
+ (not pre_file/1)
+ (not pre_dir/0)
+ (not pre_dir/1)
- (case made_file?
- {try.#Success _} true
- {try.#Failure _} false)
- (case made_dir?
- {try.#Success _} true
- {try.#Failure _} false)
+ (case made_file?
+ {try.#Success _} true
+ {try.#Failure _} false)
+ (case made_dir?
+ {try.#Success _} true
+ {try.#Failure _} false)
- post_file/0
- post_file/1
- post_dir/0
- post_dir/1))))
+ post_file/0
+ post_file/1
+ post_dir/0
+ post_dir/1))))
(def: .public (spec fs)
(-> (IO (/.System Async)) Test)
diff --git a/stdlib/source/specification/lux/world/program.lux b/stdlib/source/specification/lux/world/program.lux
index b7c742164..08392541c 100644
--- a/stdlib/source/specification/lux/world/program.lux
+++ b/stdlib/source/specification/lux/world/program.lux
@@ -1,22 +1,22 @@
(.using
- [library
- [lux "*"
- ["_" test {"+" Test}]
- [abstract
- [monad {"+" do}]]
- [control
- ["[0]" try]
- [concurrency
- ["[0]" async {"+" Async}]]]
- [data
- ["[0]" text]
- [collection
- ["[0]" dictionary]
- ["[0]" list]]]
- [math
- ["[0]" random]]]]
- [\\library
- ["[0]" /]])
+ [library
+ [lux "*"
+ ["_" test {"+" Test}]
+ [abstract
+ [monad {"+" do}]]
+ [control
+ ["[0]" try]
+ [concurrency
+ ["[0]" async {"+" Async}]]]
+ [data
+ ["[0]" text]
+ [collection
+ ["[0]" dictionary]
+ ["[0]" list]]]
+ [math
+ ["[0]" random]]]]
+ [\\library
+ ["[0]" /]])
(def: .public (spec subject)
(-> (/.Program Async) Test)
@@ -24,9 +24,9 @@
[exit random.int]
(in (do [! async.monad]
[environment (/.environment ! subject)]
- (_.cover' [/.Program]
- (and (not (dictionary.empty? environment))
- (list.every? (|>> text.empty? not)
- (dictionary.keys environment))
- (not (text.empty? (# subject home)))
- (not (text.empty? (# subject directory)))))))))
+ (_.coverage' [/.Program]
+ (and (not (dictionary.empty? environment))
+ (list.every? (|>> text.empty? not)
+ (dictionary.keys environment))
+ (not (text.empty? (# subject home)))
+ (not (text.empty? (# subject directory)))))))))
diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux
index 3b367bdd1..7d136b7e1 100644
--- a/stdlib/source/specification/lux/world/shell.lux
+++ b/stdlib/source/specification/lux/world/shell.lux
@@ -38,7 +38,7 @@
(|> (# process await [])
(async#each (|>> (try#each (i.= /.normal))
(try.else false)
- (_.cover' [/.Exit /.normal])))
+ (_.coverage' [/.Exit /.normal])))
async#conjoint))
(def: (can_read! expected process)
@@ -81,12 +81,12 @@
[can_read! (..can_read! message echo)
can_destroy! (..can_destroy! sleep)]
(all _.and'
- (_.cover' <shell_coverage>
- (and can_read!
- can_destroy!))
+ (_.coverage' <shell_coverage>
+ (and can_read!
+ can_destroy!))
(..can_wait! echo)
))
_
- (_.cover' <shell_coverage>
- false))))))))
+ (_.coverage' <shell_coverage>
+ false))))))))