aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/spec/compositor
diff options
context:
space:
mode:
authorEduardo Julian2019-07-26 21:23:27 -0400
committerEduardo Julian2019-07-26 21:23:27 -0400
commita0889b2ee76c1ae7a9a5bbe2eec9f051b4f341e4 (patch)
tree08df3db7f8fffad6360a476d20db1d40b36c85cb /stdlib/source/spec/compositor
parent78fd01f7e6688448bbd710336d4d7b1c35ae058a (diff)
No more "n/"-prefixed functions.
Diffstat (limited to '')
-rw-r--r--stdlib/source/spec/compositor/generation/case.lux11
-rw-r--r--stdlib/source/spec/compositor/generation/common.lux29
-rw-r--r--stdlib/source/spec/compositor/generation/function.lux18
-rw-r--r--stdlib/source/spec/compositor/generation/reference.lux3
-rw-r--r--stdlib/source/spec/compositor/generation/structure.lux15
5 files changed, 41 insertions, 35 deletions
diff --git a/stdlib/source/spec/compositor/generation/case.lux b/stdlib/source/spec/compositor/generation/case.lux
index 00a5e4d7c..414b468e2 100644
--- a/stdlib/source/spec/compositor/generation/case.lux
+++ b/stdlib/source/spec/compositor/generation/case.lux
@@ -10,6 +10,7 @@
["." text ("#@." equivalence)
["%" format (#+ format)]]
[number
+ ["n" nat]
["f" frac]]
[collection
["." list ("#@." fold)]]]
@@ -31,11 +32,11 @@
(def: size
(Random Nat)
- (|> r.nat (:: r.monad map (|>> (n/% ..limit) (n/max 2)))))
+ (|> r.nat (:: r.monad map (|>> (n.% ..limit) (n.max 2)))))
(def: (tail? size idx)
(-> Nat Nat Bit)
- (n/= (dec size) idx))
+ (n.= (dec size) idx))
(def: #export (verify expected)
(-> Frac (Try Any) Bit)
@@ -65,13 +66,13 @@
[(r.unicode 5) synthesis.text synthesis.path/text]))
(do r.monad
[size ..size
- idx (|> r.nat (:: @ map (n/% size)))
+ idx (|> r.nat (:: @ map (n.% size)))
[subS subP] case
#let [unitS (synthesis.text synthesis.unit)
caseS (synthesis.tuple
(list.concat (list (list.repeat idx unitS)
(list subS)
- (list.repeat (|> size dec (n/- idx)) unitS))))
+ (list.repeat (|> size dec (n.- idx)) unitS))))
caseP ($_ synthesis.path/seq
(if (tail? size idx)
(synthesis.member/right idx)
@@ -80,7 +81,7 @@
(wrap [caseS caseP]))
(do r.monad
[size ..size
- idx (|> r.nat (:: @ map (n/% size)))
+ idx (|> r.nat (:: @ map (n.% size)))
[subS subP] case
#let [right? (tail? size idx)
caseS (synthesis.variant
diff --git a/stdlib/source/spec/compositor/generation/common.lux b/stdlib/source/spec/compositor/generation/common.lux
index b7a114893..c2289571a 100644
--- a/stdlib/source/spec/compositor/generation/common.lux
+++ b/stdlib/source/spec/compositor/generation/common.lux
@@ -10,6 +10,7 @@
["." bit ("#@." equivalence)]
[number
["." i64]
+ ["n" nat]
["i" int]
["f" frac]]
["." text ("#@." equivalence)
@@ -42,7 +43,7 @@
(synthesis.i64 subject)))
(run (..sanitize <extension>))
(case> (#try.Success valueT)
- (n/= (<reference> param subject) (:coerce Nat valueT))
+ (n.= (<reference> param subject) (:coerce Nat valueT))
(#try.Failure _)
false)
@@ -51,8 +52,8 @@
["lux i64 and" i64.and param]
["lux i64 or" i64.or param]
["lux i64 xor" i64.xor param]
- ["lux i64 left-shift" i64.left-shift (n/% 64 param)]
- ["lux i64 logical-right-shift" i64.logic-right-shift (n/% 64 param)]
+ ["lux i64 left-shift" i64.left-shift (n.% 64 param)]
+ ["lux i64 logical-right-shift" i64.logic-right-shift (n.% 64 param)]
)]
($_ _.and
<binary>
@@ -68,7 +69,7 @@
(#try.Failure _)
false)
- (let [param (n/% 64 param)])))
+ (let [param (n.% 64 param)])))
))))
(def: (i64 run)
@@ -91,7 +92,7 @@
["lux i64 f64" Frac i.frac f.= subject]
["lux i64 char" Text (|>> (:coerce Nat) text.from-code) text@= (|> subject
(:coerce Nat)
- (n/% (i64.left-shift 8 1))
+ (n.% (i64.left-shift 8 1))
(:coerce Int))]
))
(~~ (template [<extension> <reference> <outputT> <comp>]
@@ -117,7 +118,7 @@
(def: simple-frac
(Random Frac)
- (|> r.nat (:: r.monad map (|>> (n/% 1000) .int i.frac))))
+ (|> r.nat (:: r.monad map (|>> (n.% 1000) .int i.frac))))
(def: (f64 run)
(-> Runner Test)
@@ -174,12 +175,12 @@
(def: (text run)
(-> Runner Test)
(do r.monad
- [sample-size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 1))))
+ [sample-size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 1))))
sample-lower (r.ascii/lower-alpha sample-size)
sample-upper (r.ascii/upper-alpha sample-size)
sample-alpha (|> (r.ascii/alpha sample-size)
(r.filter (|>> (text@= sample-upper) not)))
- char-idx (|> r.nat (:: @ map (n/% sample-size)))
+ char-idx (|> r.nat (:: @ map (n.% sample-size)))
#let [sample-lowerS (synthesis.text sample-lower)
sample-upperS (synthesis.text sample-upper)
sample-alphaS (synthesis.text sample-alpha)
@@ -216,7 +217,7 @@
(|> (#synthesis.Extension "lux text size" (list sample-lowerS))
(run (..sanitize "lux text size"))
(case> (#try.Success valueV)
- (n/= sample-size (:coerce Nat valueV))
+ (n.= sample-size (:coerce Nat valueV))
_
false)))
@@ -224,7 +225,7 @@
(|> (#synthesis.Extension "lux text size" (list concatenatedS))
(run (..sanitize "lux text size"))
(case> (#try.Success valueV)
- (n/= (n/* 2 sample-size) (:coerce Nat valueV))
+ (n.= (n.* 2 sample-size) (:coerce Nat valueV))
_
false)))
@@ -235,7 +236,7 @@
(run (..sanitize "lux text index"))
(case> (^multi (#try.Success valueV)
[(:coerce (Maybe Nat) valueV) (#.Some valueV)])
- (n/= 0 valueV)
+ (n.= 0 valueV)
_
false))
@@ -245,7 +246,7 @@
(run (..sanitize "lux text index"))
(case> (^multi (#try.Success valueV)
[(:coerce (Maybe Nat) valueV) (#.Some valueV)])
- (n/= sample-size valueV)
+ (n.= sample-size valueV)
_
false))))
@@ -264,7 +265,7 @@
false))))]
(_.test "Can clip text to extract sub-text."
(and (test-clip 0 sample-size sample-lower)
- (test-clip sample-size (n/* 2 sample-size) sample-upper))))
+ (test-clip sample-size (n.* 2 sample-size) sample-upper))))
(_.test "Can extract individual characters from text."
(|> (#synthesis.Extension "lux text char"
(list sample-lowerS
@@ -325,7 +326,7 @@
(run (..sanitize "lux io current-time"))
(case> (#try.Success valueV)
(let [[pre post] (:coerce [Nat Nat] valueV)]
- (n/>= pre post))
+ (n.>= pre post))
(#try.Failure _)
false)))
diff --git a/stdlib/source/spec/compositor/generation/function.lux b/stdlib/source/spec/compositor/generation/function.lux
index 0b8810620..9af307287 100644
--- a/stdlib/source/spec/compositor/generation/function.lux
+++ b/stdlib/source/spec/compositor/generation/function.lux
@@ -7,6 +7,8 @@
[pipe (#+ case>)]]
[data
["." maybe]
+ [number
+ ["n" nat]]
[collection
["." list ("#@." functor)]]]
[math
@@ -25,11 +27,11 @@
(def: arity
(Random Arity)
- (|> r.nat (r@map (|>> (n/% max-arity) (n/max 1)))))
+ (|> r.nat (r@map (|>> (n.% max-arity) (n.max 1)))))
(def: (local arity)
(-> Arity (Random Register))
- (|> r.nat (r@map (|>> (n/% arity) inc))))
+ (|> r.nat (r@map (|>> (n.% arity) inc))))
(def: function
(Random [Arity Register Synthesis])
@@ -46,7 +48,7 @@
(-> Runner Test)
(do r.monad
[[arity local functionS] ..function
- partial-arity (|> r.nat (:: @ map (|>> (n/% arity) (n/max 1))))
+ partial-arity (|> r.nat (:: @ map (|>> (n.% arity) (n.max 1))))
inputs (r.list arity r.safe-frac)
#let [expectation (maybe.assume (list.nth (dec local) inputs))
inputsS (list@map (|>> synthesis.f64) inputs)]]
@@ -57,7 +59,7 @@
(run "with-local")
(//case.verify expectation)))
(_.test "Can partially apply functions."
- (or (n/= 1 arity)
+ (or (n.= 1 arity)
(let [preS (list.take partial-arity inputsS)
postS (list.drop partial-arity inputsS)
partialS (synthesis.function/apply {#synthesis.function functionS
@@ -67,14 +69,14 @@
(run "partial-application")
(//case.verify expectation)))))
(_.test "Can read environment."
- (or (n/= 1 arity)
+ (or (n.= 1 arity)
(let [environment (|> partial-arity
(list.n/range 1)
(list@map (|>> #reference.Local)))
- variableS (if (n/<= partial-arity local)
+ variableS (if (n.<= partial-arity local)
(synthesis.variable/foreign (dec local))
- (synthesis.variable/local (|> local (n/- partial-arity))))
- inner-arity (n/- partial-arity arity)
+ (synthesis.variable/local (|> local (n.- partial-arity))))
+ inner-arity (n.- partial-arity arity)
innerS (synthesis.function/abstraction
{#synthesis.environment environment
#synthesis.arity inner-arity
diff --git a/stdlib/source/spec/compositor/generation/reference.lux b/stdlib/source/spec/compositor/generation/reference.lux
index a5e75b590..5da59d0b4 100644
--- a/stdlib/source/spec/compositor/generation/reference.lux
+++ b/stdlib/source/spec/compositor/generation/reference.lux
@@ -8,6 +8,7 @@
["." try]]
[data
[number
+ ["n" nat]
["f" frac]]]
[tool
[compiler
@@ -39,7 +40,7 @@
(def: (variable run)
(-> Runner Test)
(do r.monad
- [register (|> r.nat (:: @ map (n/% 100)))
+ [register (|> r.nat (:: @ map (n.% 100)))
expected r.safe-frac]
(_.test "Local variables."
(|> (synthesis.branch/let [(synthesis.f64 expected)
diff --git a/stdlib/source/spec/compositor/generation/structure.lux b/stdlib/source/spec/compositor/generation/structure.lux
index a93b27086..0697e5338 100644
--- a/stdlib/source/spec/compositor/generation/structure.lux
+++ b/stdlib/source/spec/compositor/generation/structure.lux
@@ -9,6 +9,7 @@
[data
["." maybe]
[number
+ ["n" nat]
["i" int]]
["." text ("#@." equivalence)
["%" format (#+ format)]]
@@ -30,9 +31,9 @@
(def: (variant run)
(-> Runner Test)
(do r.monad
- [num-tags (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2))))
- tag-in (|> r.nat (:: @ map (n/% num-tags)))
- #let [last?-in (|> num-tags dec (n/= tag-in))]
+ [num-tags (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2))))
+ tag-in (|> r.nat (:: @ map (n.% num-tags)))
+ #let [last?-in (|> num-tags dec (n.= tag-in))]
value-in r.i64]
(_.test (%.name (name-of synthesis.variant))
(|> (synthesis.variant {#analysis.lefts (if last?-in
@@ -43,11 +44,11 @@
(run "variant")
(case> (#try.Success valueT)
(let [valueT (:coerce (Array Any) valueT)]
- (and (n/= 3 (array.size valueT))
+ (and (n.= 3 (array.size valueT))
(let [tag-out (:coerce java/lang/Integer (maybe.assume (array.read 0 valueT)))
last?-out (array.read 1 valueT)
value-out (:coerce Any (maybe.assume (array.read 2 valueT)))
- same-tag? (|> tag-out host.int-to-long (:coerce Nat) (n/= tag-in))
+ same-tag? (|> tag-out host.int-to-long (:coerce Nat) (n.= tag-in))
same-flag? (case last?-out
(#.Some last?-out')
(and last?-in (text@= "" (:coerce Text last?-out')))
@@ -65,14 +66,14 @@
(def: (tuple run)
(-> Runner Test)
(do r.monad
- [size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2))))
+ [size (|> r.nat (:: @ map (|>> (n.% 10) (n.max 2))))
tuple-in (r.list size r.i64)]
(_.test (%.name (name-of synthesis.tuple))
(|> (synthesis.tuple (list@map (|>> synthesis.i64) tuple-in))
(run "tuple")
(case> (#try.Success tuple-out)
(let [tuple-out (:coerce (Array Any) tuple-out)]
- (and (n/= size (array.size tuple-out))
+ (and (n.= size (array.size tuple-out))
(list.every? (function (_ [left right])
(i.= left (:coerce Int right)))
(list.zip2 tuple-in (array.to-list tuple-out)))))