aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/specification/compositor
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/specification/compositor')
-rw-r--r--stdlib/source/specification/compositor/analysis/type.lux4
-rw-r--r--stdlib/source/specification/compositor/generation/case.lux14
-rw-r--r--stdlib/source/specification/compositor/generation/common.lux34
-rw-r--r--stdlib/source/specification/compositor/generation/function.lux6
-rw-r--r--stdlib/source/specification/compositor/generation/primitive.lux2
-rw-r--r--stdlib/source/specification/compositor/generation/reference.lux4
-rw-r--r--stdlib/source/specification/compositor/generation/structure.lux4
7 files changed, 34 insertions, 34 deletions
diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux
index 6675fad09..89ee8646f 100644
--- a/stdlib/source/specification/compositor/analysis/type.lux
+++ b/stdlib/source/specification/compositor/analysis/type.lux
@@ -56,8 +56,8 @@
[[typeC exprT exprC] ..check
[other_typeC other_exprT other_exprC] ..check]
(all _.and
- (_.property "lux check"
+ (_.test "lux check"
(check_success+ expander state "lux check" (list typeC exprC) exprT))
- (_.property "lux coerce"
+ (_.test "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 5e00820b2..6ac785a12 100644
--- a/stdlib/source/specification/compositor/generation/case.lux
+++ b/stdlib/source/specification/compositor/generation/case.lux
@@ -101,7 +101,7 @@
(-> Runner Test)
(do r.monad
[value r.safe_frac]
- (_.property (%.symbol (symbol synthesis.branch/let))
+ (_.test (%.symbol (symbol synthesis.branch/let))
(|> (synthesis.branch/let [(synthesis.f64 value)
0
(synthesis.variable/local 0)])
@@ -114,7 +114,7 @@
[on_true r.safe_frac
on_false (|> r.safe_frac (r.only (|>> (f.= on_true) not)))
verdict r.bit]
- (_.property (%.symbol (symbol synthesis.branch/if))
+ (_.test (%.symbol (symbol synthesis.branch/if))
(|> (synthesis.branch/if [(synthesis.bit verdict)
(synthesis.f64 on_true)
(synthesis.f64 on_false)])
@@ -127,7 +127,7 @@
[[inputS pathS] ..case
on_success r.safe_frac
on_failure (|> r.safe_frac (r.only (|>> (f.= on_success) not)))]
- (_.property (%.symbol (symbol synthesis.branch/case))
+ (_.test (%.symbol (symbol synthesis.branch/case))
(|> (synthesis.branch/case
[inputS
(all synthesis.path/alt
@@ -243,11 +243,11 @@
(def (special_spec run)
(-> Runner Test)
(all _.and
- (_.property "==="
+ (_.test "==="
(and (text#= (synthesis.%path special_path)
(synthesis.%path special_pattern_path))
(at synthesis.path_equivalence = special_path special_pattern_path)))
- (_.property "CODE"
+ (_.test "CODE"
(|> special_input
(run "special_input")
(pipe.case
@@ -256,7 +256,7 @@
{try.#Failure _}
false)))
- (_.property "PATTERN_MATCHING 0"
+ (_.test "PATTERN_MATCHING 0"
(|> (synthesis.branch/case [special_input
special_path])
(run "special_path")
@@ -266,7 +266,7 @@
{try.#Failure _}
false)))
- (_.property "PATTERN_MATCHING 1"
+ (_.test "PATTERN_MATCHING 1"
(|> (synthesis.branch/case [special_input
special_pattern_path])
(run "special_pattern_path")
diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux
index eb1a1ac70..ba691bde7 100644
--- a/stdlib/source/specification/compositor/generation/common.lux
+++ b/stdlib/source/specification/compositor/generation/common.lux
@@ -40,7 +40,7 @@
[param r.i64
subject r.i64]
(with_expansions [<binary> (with_template [<extension> <reference> <param_expr>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
(synthesis.i64 subject))}
(run (..safe <extension>))
@@ -60,7 +60,7 @@
)]
(all _.and
<binary>
- (_.property "lux i64 arithmetic-right-shift"
+ (_.test "lux i64 arithmetic-right-shift"
(|> {synthesis.#Extension "lux i64 arithmetic-right-shift"
(list (synthesis.i64 subject)
(synthesis.i64 param))}
@@ -83,7 +83,7 @@
subject r.i64]
(`` (all _.and
(,, (with_template [<extension> <type> <prepare> <comp> <subject_expr>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))}
(run (..safe <extension>))
(pipe.case
@@ -101,7 +101,7 @@
(as Int))]
))
(,, (with_template [<extension> <reference> <outputT> <comp>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
(synthesis.i64 subject))}
(run (..safe <extension>))
@@ -133,7 +133,7 @@
subject ..simple_frac]
(`` (all _.and
(,, (with_template [<extension> <reference> <comp>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
(synthesis.f64 subject))}
(run (..safe <extension>))
@@ -146,7 +146,7 @@
["lux f64 %" f.% f.=]
))
(,, (with_template [<extension> <text>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
(synthesis.f64 subject))}
(run (..safe <extension>))
@@ -162,7 +162,7 @@
["lux f64 <" f.<]
))
(,, (with_template [<extension> <reference>]
- [(_.property <extension>
+ [(_.test <extension>
(|> {synthesis.#Extension <extension> (list)}
(run (..safe <extension>))
(//case.verify <reference>)))]
@@ -171,7 +171,7 @@
["lux f64 max" ("lux f64 max")]
["lux f64 smallest" ("lux f64 smallest")]
))
- (_.property "'lux f64 i64 && 'lux i64 f64'"
+ (_.test "'lux f64 i64 && 'lux i64 f64'"
(|> (run (..safe "lux f64 i64")
(|> subject synthesis.f64
(list) {synthesis.#Extension "lux f64 i64"}
@@ -197,7 +197,7 @@
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
- (_.property "Can compare texts for equality."
+ (_.test "Can compare texts for equality."
(and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)}
(run (..safe "lux text ="))
(pipe.case
@@ -214,7 +214,7 @@
_
false))))
- (_.property "Can compare texts for order."
+ (_.test "Can compare texts for order."
(|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)}
(run (..safe "lux text <"))
(pipe.case
@@ -223,7 +223,7 @@
{try.#Failure _}
false)))
- (_.property "Can get length of text."
+ (_.test "Can get length of text."
(|> {synthesis.#Extension "lux text size" (list sample_lowerS)}
(run (..safe "lux text size"))
(pipe.case
@@ -232,7 +232,7 @@
_
false)))
- (_.property "Can concatenate text."
+ (_.test "Can concatenate text."
(|> {synthesis.#Extension "lux text size" (list concatenatedS)}
(run (..safe "lux text size"))
(pipe.case
@@ -241,7 +241,7 @@
_
false)))
- (_.property "Can find index of sub-text."
+ (_.test "Can find index of sub-text."
(and (|> {synthesis.#Extension "lux text index"
(list concatenatedS sample_lowerS
(synthesis.i64 +0))}
@@ -281,10 +281,10 @@
_
false))))]
- (_.property "Can clip text to extract sub-text."
+ (_.test "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."
+ (_.test "Can extract individual characters from text."
(|> {synthesis.#Extension "lux text char"
(list sample_lowerS
(synthesis.i64 char_idx))}
@@ -305,7 +305,7 @@
(do r.monad
[message (r.alphabetic 5)]
(all _.and
- (_.property "Can log messages."
+ (_.test "Can log messages."
(|> {synthesis.#Extension "lux io log"
(list (synthesis.text (format "LOG: " message)))}
(run (..safe "lux io log"))
@@ -315,7 +315,7 @@
{try.#Failure _}
false)))
- (_.property "Can throw runtime errors."
+ (_.test "Can throw runtime errors."
(and (|> {synthesis.#Extension "lux try"
(list (synthesis.function/abstraction
[synthesis.#environment (list)
diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux
index 7fc24cfb8..2fb9714e0 100644
--- a/stdlib/source/specification/compositor/generation/function.lux
+++ b/stdlib/source/specification/compositor/generation/function.lux
@@ -55,12 +55,12 @@
.let [expectation (maybe.trusted (list.item (-- local) inputs))
inputsS (list#each (|>> synthesis.f64) inputs)]]
(all _.and
- (_.property "Can read arguments."
+ (_.test "Can read arguments."
(|> (synthesis.function/apply [synthesis.#function functionS
synthesis.#arguments inputsS])
(run "with_local")
(//case.verify expectation)))
- (_.property "Can partially apply functions."
+ (_.test "Can partially apply functions."
(or (n.= 1 arity)
(let [preS (list.first partial_arity inputsS)
postS (list.after partial_arity inputsS)
@@ -70,7 +70,7 @@
synthesis.#arguments postS])
(run "partial_application")
(//case.verify expectation)))))
- (_.property "Can read environment."
+ (_.test "Can read environment."
(or (n.= 1 arity)
(let [environment (|> partial_arity
(enum.range n.enum 1)
diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux
index 9e6ea2e02..fcb6bd050 100644
--- a/stdlib/source/specification/compositor/generation/primitive.lux
+++ b/stdlib/source/specification/compositor/generation/primitive.lux
@@ -32,7 +32,7 @@
(,, (with_template [<evaluation_name> <synthesis> <gen> <test>]
[(do r.monad
[expected <gen>]
- (_.property (%.symbol (symbol <synthesis>))
+ (_.test (%.symbol (symbol <synthesis>))
(|> (run <evaluation_name> (<synthesis> expected))
(pipe.case
{try.#Success actual}
diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux
index 7159afe1b..27441f349 100644
--- a/stdlib/source/specification/compositor/generation/reference.lux
+++ b/stdlib/source/specification/compositor/generation/reference.lux
@@ -29,7 +29,7 @@
(do r.monad
[name ..symbol
expected r.safe_frac]
- (_.property "Definitions."
+ (_.test "Definitions."
(|> (define name (synthesis.f64 expected))
(pipe.case
{try.#Success actual}
@@ -43,7 +43,7 @@
(do [! r.monad]
[register (|> r.nat (at ! each (n.% 100)))
expected r.safe_frac]
- (_.property "Local variables."
+ (_.test "Local variables."
(|> (synthesis.branch/let [(synthesis.f64 expected)
register
(synthesis.variable/local register)])
diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux
index 523ad990e..5521c6303 100644
--- a/stdlib/source/specification/compositor/generation/structure.lux
+++ b/stdlib/source/specification/compositor/generation/structure.lux
@@ -35,7 +35,7 @@
tag_in (|> r.nat (at ! each (n.% num_tags)))
.let [last?_in (|> num_tags -- (n.= tag_in))]
value_in r.i64]
- (_.property (%.symbol (symbol synthesis.variant))
+ (_.test (%.symbol (symbol synthesis.variant))
(|> (synthesis.variant [analysis.#lefts (if last?_in
(-- tag_in)
tag_in)
@@ -69,7 +69,7 @@
(do [! r.monad]
[size (|> r.nat (at ! each (|>> (n.% 10) (n.max 2))))
tuple_in (r.list size r.i64)]
- (_.property (%.symbol (symbol synthesis.tuple))
+ (_.test (%.symbol (symbol synthesis.tuple))
(|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in))
(run "tuple")
(pipe.case