aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/data
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux/data.lux16
-rw-r--r--stdlib/source/test/lux/data/collection/set/ordered.lux14
-rw-r--r--stdlib/source/test/lux/data/collection/tree/finger.lux18
-rw-r--r--stdlib/source/test/lux/data/format/binary.lux35
-rw-r--r--stdlib/source/test/lux/data/format/tar.lux26
-rw-r--r--stdlib/source/test/lux/data/format/xml.lux14
-rw-r--r--stdlib/source/test/lux/data/identity.lux8
-rw-r--r--stdlib/source/test/lux/data/text/regex.lux12
8 files changed, 87 insertions, 56 deletions
diff --git a/stdlib/source/test/lux/data.lux b/stdlib/source/test/lux/data.lux
index c65567c23..74a295777 100644
--- a/stdlib/source/test/lux/data.lux
+++ b/stdlib/source/test/lux/data.lux
@@ -17,10 +17,11 @@
["#." sum]
["#." color
["#/." named]]
- [format
- ["#." json]
- ["#." tar]
- ["#." xml]]
+ ["#." format #_
+ ["#/." binary]
+ ["#/." json]
+ ["#/." tar]
+ ["#/." xml]]
[number
["#." i8]
["#." i16]
@@ -51,9 +52,10 @@
(def: format
($_ _.and
- /json.test
- /tar.test
- /xml.test
+ /format/binary.test
+ /format/json.test
+ /format/tar.test
+ /format/xml.test
))
(def: #export test
diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux
index 7257a7f7b..1734d80c4 100644
--- a/stdlib/source/test/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/set/ordered.lux
@@ -8,13 +8,13 @@
[/
["$." equivalence]]}]
[data
- ["." bit ("#@." equivalence)]
+ ["." bit ("#\." equivalence)]
[number
["n" nat]]
[collection
["." list]]]
[math
- ["." random (#+ Random) ("#@." monad)]]]
+ ["." random (#+ Random) ("#\." monad)]]]
{1
["." / (#+ Set)
["." //]]})
@@ -27,7 +27,7 @@
(All [a] (-> Nat (Order a) (Random a) (Random (Set a))))
(case size
0
- (random@wrap (/.new &order))
+ (random\wrap (/.new &order))
_
(do random.monad
@@ -48,7 +48,7 @@
random.nat)
#let [listL (//.to-list usetL)]
listR (|> (random.set n.hash sizeR random.nat) (:: ! map //.to-list))
- #let [(^open "/@.") /.equivalence
+ #let [(^open "/\.") /.equivalence
setL (/.from-list n.order listL)
setR (/.from-list n.order listR)
empty (/.new n.order)]]
@@ -59,7 +59,7 @@
(_.cover [/.size]
(n.= sizeL (/.size setL)))
(_.cover [/.empty?]
- (bit@= (n.= 0 (/.size setL))
+ (bit\= (n.= 0 (/.size setL))
(/.empty? setL)))
(_.cover [/.new]
(/.empty? (/.new n.order)))
@@ -70,7 +70,7 @@
(_.cover [/.from-list]
(|> setL
/.to-list (/.from-list n.order)
- (/@= setL)))
+ (/\= setL)))
(~~ (template [<coverage> <comparison>]
[(_.cover [<coverage>]
(case (<coverage> setL)
@@ -118,7 +118,7 @@
(/.super? empty setL)
symmetry!
- (bit@= (/.super? setL setR)
+ (bit\= (/.super? setL setR)
(/.sub? setR setL))]
(and self!
empty!
diff --git a/stdlib/source/test/lux/data/collection/tree/finger.lux b/stdlib/source/test/lux/data/collection/tree/finger.lux
index a0dfabb54..7c93fb0c1 100644
--- a/stdlib/source/test/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/test/lux/data/collection/tree/finger.lux
@@ -4,8 +4,8 @@
[abstract
[monad (#+ do)]]
[data
- ["." maybe ("#@." functor)]
- ["." text ("#@." equivalence monoid)]
+ ["." maybe ("#\." functor)]
+ ["." text ("#\." equivalence monoid)]
[number
["n" nat]]]
[math
@@ -29,7 +29,7 @@
(_.with-cover [/.Tree])
(do {! random.monad}
[tag-left (random.ascii/alpha-num 1)
- tag-right (random.filter (|>> (text@= tag-left) not)
+ tag-right (random.filter (|>> (text\= tag-left) not)
(random.ascii/alpha-num 1))
expected-left random.nat
expected-right random.nat]
@@ -38,9 +38,9 @@
(exec (/.builder text.monoid)
true))
(_.cover [/.tag]
- (and (text@= tag-left
+ (and (text\= tag-left
(/.tag (:: ..builder leaf tag-left expected-left)))
- (text@= (text@compose tag-left tag-right)
+ (text\= (text\compose tag-left tag-right)
(/.tag (:: ..builder branch
(:: ..builder leaf tag-left expected-left)
(:: ..builder leaf tag-right expected-right))))))
@@ -77,13 +77,13 @@
(let [can-find-correct-one!
(|> (:: ..builder leaf tag-left expected-left)
(/.search (text.contains? tag-left))
- (maybe@map (n.= expected-left))
+ (maybe\map (n.= expected-left))
(maybe.default false))
cannot-find-incorrect-one!
(|> (:: ..builder leaf tag-right expected-right)
(/.search (text.contains? tag-left))
- (maybe@map (n.= expected-left))
+ (maybe\map (n.= expected-left))
(maybe.default false)
not)
@@ -92,7 +92,7 @@
(:: ..builder leaf tag-left expected-left)
(:: ..builder leaf tag-right expected-right))
(/.search (text.contains? tag-left))
- (maybe@map (n.= expected-left))
+ (maybe\map (n.= expected-left))
(maybe.default false))
can-find-right!
@@ -100,7 +100,7 @@
(:: ..builder leaf tag-left expected-left)
(:: ..builder leaf tag-right expected-right))
(/.search (text.contains? tag-right))
- (maybe@map (n.= expected-right))
+ (maybe\map (n.= expected-right))
(maybe.default false))]
(and can-find-correct-one!
cannot-find-incorrect-one!
diff --git a/stdlib/source/test/lux/data/format/binary.lux b/stdlib/source/test/lux/data/format/binary.lux
new file mode 100644
index 000000000..9b00113f0
--- /dev/null
+++ b/stdlib/source/test/lux/data/format/binary.lux
@@ -0,0 +1,35 @@
+(.module:
+ [lux #*
+ ["_" test (#+ Test)]
+ [abstract
+ [equivalence (#+ Equivalence)]
+ [monad (#+ do)]
+ {[0 #spec]
+ [/
+ ["$." monoid]]}]
+ [data
+ ["." binary ("#\." equivalence)]]
+ [math
+ ["." random (#+ Random)]]]
+ {1
+ ["." /]})
+
+(structure: equivalence
+ (Equivalence /.Specification)
+
+ (def: (= reference subject)
+ (binary\= (/.instance reference)
+ (/.instance subject))))
+
+(def: random
+ (Random /.Specification)
+ (:: random.monad map /.nat random.nat))
+
+(def: #export test
+ Test
+ (<| (_.covering /._)
+ (_.with-cover [/.Mutation /.Specification /.Writer])
+ ($_ _.and
+ (_.with-cover [/.monoid]
+ ($monoid.spec ..equivalence /.monoid ..random))
+ )))
diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux
index 0e274a6e6..9c83040fa 100644
--- a/stdlib/source/test/lux/data/format/tar.lux
+++ b/stdlib/source/test/lux/data/format/tar.lux
@@ -11,8 +11,8 @@
[data
["." product]
["." maybe]
- ["." binary ("#@." equivalence)]
- ["." text ("#@." equivalence)
+ ["." binary ("#\." equivalence)]
+ ["." text ("#\." equivalence)
["." encoding]
["." unicode]
["%" format (#+ format)]]
@@ -21,7 +21,7 @@
["i" int]]
[collection
["." row]
- ["." list ("#@." fold)]]
+ ["." list ("#\." fold)]]
["." format #_
["#" binary]]]
[time
@@ -44,7 +44,7 @@
(_.cover [/.path /.from-path]
(case (/.path expected)
(#try.Success actual)
- (text@= expected
+ (text\= expected
(/.from-path actual))
(#try.Failure error)
@@ -77,7 +77,7 @@
(_.cover [/.name /.from-name]
(case (/.name expected)
(#try.Success actual)
- (text@= expected
+ (text\= expected
(/.from-name actual))
(#try.Failure error)
@@ -170,7 +170,7 @@
(<b>.run /.parser))]
(wrap (case (row.to-list tar)
(^ (list (<tag> actual-path)))
- (text@= (/.from-path expected-path)
+ (text\= (/.from-path expected-path)
(/.from-path actual-path))
_
@@ -201,11 +201,11 @@
(^ (list (<tag> [actual-path actual-moment actual-mode actual-ownership actual-content])))
(let [seconds (: (-> Instant Int)
(|>> instant.relative (duration.query duration.second)))]
- (and (text@= (/.from-path expected-path)
+ (and (text\= (/.from-path expected-path)
(/.from-path actual-path))
(i.= (seconds expected-moment)
(seconds actual-moment))
- (binary@= (/.data expected-content)
+ (binary\= (/.data expected-content)
(/.data actual-content))))
_
@@ -239,7 +239,7 @@
(do {! random.monad}
[path (random.ascii/lower-alpha 10)
modes (random.list 4 ..random-mode)
- #let [expected-mode (list@fold /.and /.none modes)]]
+ #let [expected-mode (list\fold /.and /.none modes)]]
(`` ($_ _.and
(_.cover [/.and]
(|> (do try.monad
@@ -347,9 +347,9 @@
(<b>.run /.parser))]
(wrap (case (row.to-list tar)
(^ (list (#/.Normal [_ _ _ actual-ownership _])))
- (and (text@= (/.from-name expected)
+ (and (text\= (/.from-name expected)
(/.from-name (get@ [#/.user #/.name] actual-ownership)))
- (text@= (/.from-name /.anonymous)
+ (text\= (/.from-name /.anonymous)
(/.from-name (get@ [#/.group #/.name] actual-ownership))))
_
@@ -371,11 +371,11 @@
(<b>.run /.parser))]
(wrap (case (row.to-list tar)
(^ (list (#/.Normal [_ _ _ actual-ownership _])))
- (and (text@= (/.from-name /.anonymous)
+ (and (text\= (/.from-name /.anonymous)
(/.from-name (get@ [#/.user #/.name] actual-ownership)))
(n.= (/.from-small /.no-id)
(/.from-small (get@ [#/.user #/.id] actual-ownership)))
- (text@= (/.from-name /.anonymous)
+ (text\= (/.from-name /.anonymous)
(/.from-name (get@ [#/.group #/.name] actual-ownership)))
(n.= (/.from-small /.no-id)
(/.from-small (get@ [#/.group #/.id] actual-ownership))))
diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux
index e0a1a5c05..531326d92 100644
--- a/stdlib/source/test/lux/data/format/xml.lux
+++ b/stdlib/source/test/lux/data/format/xml.lux
@@ -16,14 +16,14 @@
[data
["." name]
["." maybe]
- ["." text ("#@." equivalence)]
+ ["." text ("#\." equivalence)]
[number
["n" nat]]
[collection
["." dictionary]
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[math
- ["r" random (#+ Random) ("#@." monad)]]]
+ ["r" random (#+ Random) ("#\." monad)]]]
{1
["." / (#+ XML)]})
@@ -42,7 +42,7 @@
(def: (size bottom top)
(-> Nat Nat (Random Nat))
(let [constraint (|>> (n.% top) (n.max bottom))]
- (r@map constraint r.nat)))
+ (r\map constraint r.nat)))
(def: (text bottom top)
(-> Nat Nat (Random Text))
@@ -82,21 +82,21 @@
value (..text 1 10)
#let [node (#/.Node tag
(dictionary.put attribute value /.attrs)
- (list@map (|>> #/.Text) children))]]
+ (list\map (|>> #/.Text) children))]]
($_ _.and
(_.test "Can parse text."
(E.default #0
(do E.monad
[output (</>.run </>.text
(#/.Text text))]
- (wrap (text@= text output)))))
+ (wrap (text\= text output)))))
(_.test "Can parse attributes."
(E.default #0
(do E.monad
[output (</>.run (p.before </>.ignore
(</>.attribute attribute))
node)]
- (wrap (text@= value output)))))
+ (wrap (text\= value output)))))
(_.test "Can parse nodes."
(E.default #0
(do E.monad
diff --git a/stdlib/source/test/lux/data/identity.lux b/stdlib/source/test/lux/data/identity.lux
index cc2ccf096..4601aaf0b 100644
--- a/stdlib/source/test/lux/data/identity.lux
+++ b/stdlib/source/test/lux/data/identity.lux
@@ -2,19 +2,13 @@
[lux #*
["_" test (#+ Test)]
[abstract
- [equivalence (#+)]
- [functor (#+)]
- comonad
[monad (#+ do)]
{[0 #spec]
[/
["$." functor (#+ Injection Comparison)]
["$." apply]
["$." monad]
- ["$." comonad]]}]
- [data
- ["." text ("#@." monoid equivalence)
- ["%" format (#+ format)]]]]
+ ["$." comonad]]}]]
{1
["." / (#+ Identity)]})
diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux
index bef97b853..83d2cfcc4 100644
--- a/stdlib/source/test/lux/data/text/regex.lux
+++ b/stdlib/source/test/lux/data/text/regex.lux
@@ -11,7 +11,7 @@
["s" code]]]
[data
[number (#+ hex)]
- ["." text ("#@." equivalence)]]
+ ["." text ("#\." equivalence)]]
[math
["r" random]]
["." meta]
@@ -25,7 +25,7 @@
(|> input
(<text>.run regex)
(case> (#try.Success parsed)
- (text@= parsed input)
+ (text\= parsed input)
_
#0)))
@@ -35,7 +35,7 @@
(|> input
(<text>.run regex)
(case> (#try.Success parsed)
- (text@= test parsed)
+ (text\= test parsed)
_
false)))
@@ -283,9 +283,9 @@
(/.^regex "(.{3})-(.{3})-(.{4})"
[_ match1 match2 match3])
(_.test "Can pattern-match using regular-expressions."
- (and (text@= sample1 match1)
- (text@= sample2 match2)
- (text@= sample3 match3)))
+ (and (text\= sample1 match1)
+ (text\= sample2 match2)
+ (text\= sample3 match3)))
_
(_.test "Cannot pattern-match using regular-expressions."