aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test
diff options
context:
space:
mode:
authorEduardo Julian2019-03-15 00:23:49 -0400
committerEduardo Julian2019-03-15 00:23:49 -0400
commitf9d4d316ef9666f6b122b0eec8180351216e95f8 (patch)
tree2a66da0c7552dcb3642ba37afd53f1bef44eef41 /stdlib/source/test
parent9449d89f611ba3192373fdeb6848d02707ff1292 (diff)
Changed the convention for the structure opening separator from "/" to ";", to avoid confusion since "/" is used for relative module paths.
Diffstat (limited to 'stdlib/source/test')
-rw-r--r--stdlib/source/test/licentia.lux34
-rw-r--r--stdlib/source/test/lux.lux14
-rw-r--r--stdlib/source/test/lux/cli.lux14
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/case.lux48
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/function.lux10
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/primitive.lux8
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/procedure/common.lux4
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/reference.lux14
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/analysis/structure.lux40
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/synthesis/case.lux4
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/synthesis/function.lux14
-rw-r--r--stdlib/source/test/lux/compiler/default/phase/synthesis/structure.lux4
-rw-r--r--stdlib/source/test/lux/compiler/default/syntax.lux32
-rw-r--r--stdlib/source/test/lux/control/apply.lux24
-rw-r--r--stdlib/source/test/lux/control/concurrency/actor.lux6
-rw-r--r--stdlib/source/test/lux/control/concurrency/frp.lux18
-rw-r--r--stdlib/source/test/lux/control/concurrency/promise.lux4
-rw-r--r--stdlib/source/test/lux/control/concurrency/semaphore.lux12
-rw-r--r--stdlib/source/test/lux/control/concurrency/stm.lux4
-rw-r--r--stdlib/source/test/lux/control/continuation.lux14
-rw-r--r--stdlib/source/test/lux/control/equivalence.lux14
-rw-r--r--stdlib/source/test/lux/control/functor.lux18
-rw-r--r--stdlib/source/test/lux/control/interval.lux8
-rw-r--r--stdlib/source/test/lux/control/monad.lux24
-rw-r--r--stdlib/source/test/lux/control/parser.lux36
-rw-r--r--stdlib/source/test/lux/control/pipe.lux10
-rw-r--r--stdlib/source/test/lux/control/reader.lux4
-rw-r--r--stdlib/source/test/lux/control/security/integrity.lux6
-rw-r--r--stdlib/source/test/lux/control/security/privacy.lux4
-rw-r--r--stdlib/source/test/lux/control/state.lux9
-rw-r--r--stdlib/source/test/lux/control/writer.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary.lux4
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary/ordered.lux12
-rw-r--r--stdlib/source/test/lux/data/collection/list.lux22
-rw-r--r--stdlib/source/test/lux/data/collection/queue.lux4
-rw-r--r--stdlib/source/test/lux/data/collection/row.lux38
-rw-r--r--stdlib/source/test/lux/data/collection/sequence.lux48
-rw-r--r--stdlib/source/test/lux/data/collection/set.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/set/ordered.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/tree/rose.lux18
-rw-r--r--stdlib/source/test/lux/data/collection/tree/rose/zipper.lux6
-rw-r--r--stdlib/source/test/lux/data/color.lux4
-rw-r--r--stdlib/source/test/lux/data/error.lux18
-rw-r--r--stdlib/source/test/lux/data/format/xml.lux24
-rw-r--r--stdlib/source/test/lux/data/identity.lux24
-rw-r--r--stdlib/source/test/lux/data/lazy.lux6
-rw-r--r--stdlib/source/test/lux/data/maybe.lux46
-rw-r--r--stdlib/source/test/lux/data/name.lux42
-rw-r--r--stdlib/source/test/lux/data/number.lux6
-rw-r--r--stdlib/source/test/lux/data/number/complex.lux16
-rw-r--r--stdlib/source/test/lux/data/number/ratio.lux14
-rw-r--r--stdlib/source/test/lux/data/text.lux30
-rw-r--r--stdlib/source/test/lux/data/text/format.lux16
-rw-r--r--stdlib/source/test/lux/data/text/lexer.lux14
-rw-r--r--stdlib/source/test/lux/data/text/regex.lux12
-rw-r--r--stdlib/source/test/lux/host.jvm.lux4
-rw-r--r--stdlib/source/test/lux/macro/code.lux4
-rw-r--r--stdlib/source/test/lux/macro/poly/equivalence.lux8
-rw-r--r--stdlib/source/test/lux/math.lux14
-rw-r--r--stdlib/source/test/lux/math/logic/fuzzy.lux22
-rw-r--r--stdlib/source/test/lux/math/modular.lux20
-rw-r--r--stdlib/source/test/lux/time/date.lux40
-rw-r--r--stdlib/source/test/lux/type.lux30
-rw-r--r--stdlib/source/test/lux/type/check.lux16
-rw-r--r--stdlib/source/test/lux/type/implicit.lux8
-rw-r--r--stdlib/source/test/lux/world/file.lux6
-rw-r--r--stdlib/source/test/lux/world/net/tcp.lux4
67 files changed, 542 insertions, 537 deletions
diff --git a/stdlib/source/test/licentia.lux b/stdlib/source/test/licentia.lux
index 0dd3183ca..1526b8a04 100644
--- a/stdlib/source/test/licentia.lux
+++ b/stdlib/source/test/licentia.lux
@@ -6,13 +6,13 @@
[control
[monad (#+ do)]]
[data
- ["." bit ("#/." equivalence)]
- ["." maybe ("#/." functor)]
+ ["." bit ("#;." equivalence)]
+ ["." maybe ("#;." functor)]
[number
- ["." nat ("#/." interval)]]
+ ["." nat ("#;." interval)]]
["." text]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random (#+ Random)]]]
{#program
@@ -44,9 +44,9 @@
(def: period
(Random (Period Nat))
(do r.monad
- [start (r.filter (|>> (n/= nat/top) not)
+ [start (r.filter (|>> (n/= nat;top) not)
r.nat)
- #let [wiggle-room (n/- start nat/top)]
+ #let [wiggle-room (n/- start nat;top)]
end (:: @ map
(|>> (n/% wiggle-room) (n/max 1))
r.nat)]
@@ -174,10 +174,10 @@
(_.test "Litigation conditions are present."
(present? liability.litigation))
(_.test "Liability acceptance conditions may be present."
- (bit/= (get@ #license.can-accept? liability)
+ (bit;= (get@ #license.can-accept? liability)
(present? liability.can-accept)))
(_.test "Liability acceptance conditions may be present."
- (bit/= (get@ #license.disclaim-high-risk? liability)
+ (bit;= (get@ #license.disclaim-high-risk? liability)
(present? liability.disclaim-high-risk)))
))
@@ -196,13 +196,13 @@
(Concern Commercial)
($_ _.and
(_.test "Non-commercial clause is present."
- (bit/= (not (get@ #license.can-sell? commercial))
+ (bit;= (not (get@ #license.can-sell? commercial))
(present? commercial.cannot-sell)))
(_.test "Contributor credit condition is present."
- (bit/= (get@ #license.require-contributor-credit? commercial)
+ (bit;= (get@ #license.require-contributor-credit? commercial)
(present? commercial.require-contributor-attribution)))
(_.test "Anti-endorsement condition is present."
- (bit/= (not (get@ #license.allow-contributor-endorsement? commercial))
+ (bit;= (not (get@ #license.allow-contributor-endorsement? commercial))
(present? commercial.disallow-contributor-endorsement)))
))
@@ -210,11 +210,11 @@
(Concern Extension)
($_ _.and
(_.test "The license is viral."
- (bit/= (get@ #license.same-license? extension)
+ (bit;= (get@ #license.same-license? extension)
(and (list.every? present? extension.sharing-requirement)
(list.every? present? extension.license-conflict-resolution))))
(_.test "Extensions must be distinguishable from the original work."
- (bit/= (get@ #license.must-be-distinguishable? extension)
+ (bit;= (get@ #license.must-be-distinguishable? extension)
(present? extension.distinctness-requirement)))
(_.test "The community must be notified of new extensions."
(case (get@ #license.notification-period extension)
@@ -224,7 +224,7 @@
#.None
true))
(_.test "Must describe modifications."
- (bit/= (get@ #license.must-describe-modifications? extension)
+ (bit;= (get@ #license.must-describe-modifications? extension)
(present? extension.description-requirement)))
))
@@ -236,14 +236,14 @@
(_.test "The attribution phrase is present."
(|> attribution
(get@ #license.phrase)
- (maybe/map present?)
+ (maybe;map present?)
(maybe.default true)))
(_.test "The attribution URL is present."
(present? (get@ #license.url attribution)))
(_.test "The attribution image is present."
(|> attribution
(get@ #license.image)
- (maybe/map present?)
+ (maybe;map present?)
(maybe.default true)))
))
@@ -296,7 +296,7 @@
yes)
every-entity-is-mentioned? (|> black-list
(get@ #license.entities)
- (list/map black-list.entity)
+ (list;map black-list.entity)
(list.every? present?))]
(and black-list-is-justified?
every-entity-is-mentioned?)))
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index 85ed47228..d6d667d72 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -20,7 +20,7 @@
["." i64]]]
["." function]
["." math
- ["r" random (#+ Random) ("#/." functor)]]
+ ["r" random (#+ Random) ("#;." functor)]]
["_" test (#+ Test)]
## These modules do not need to be tested.
[type
@@ -295,8 +295,8 @@
Test
($_ _.and
(do r.monad
- [factor (r/map (|>> (n/% 10) (n/max 1)) r.nat)
- iterations (r/map (n/% 100) r.nat)
+ [factor (r;map (|>> (n/% 10) (n/max 1)) r.nat)
+ iterations (r;map (n/% 100) r.nat)
#let [expected (n/* factor iterations)]]
(_.test "Can write loops."
(n/= expected
@@ -396,13 +396,13 @@
(..conversion <gen> <forward> <backward> <=>))]
["Int -> Nat"
- i/= .nat .int (r/map (i/% +1,000,000) r.int)]
+ i/= .nat .int (r;map (i/% +1,000,000) r.int)]
["Nat -> Int"
- n/= .int .nat (r/map (n/% 1,000,000) r.nat)]
+ n/= .int .nat (r;map (n/% 1,000,000) r.nat)]
["Int -> Frac"
- i/= int-to-frac frac-to-int (r/map (i/% +1,000,000) r.int)]
+ i/= int-to-frac frac-to-int (r;map (i/% +1,000,000) r.int)]
["Frac -> Int"
- f/= frac-to-int int-to-frac (r/map math.floor r.frac)]
+ f/= frac-to-int int-to-frac (r;map math.floor r.frac)]
["Rev -> Frac"
r/= rev-to-frac frac-to-rev frac-rev]
)))))
diff --git a/stdlib/source/test/lux/cli.lux b/stdlib/source/test/lux/cli.lux
index 8c04a119d..c59c47faf 100644
--- a/stdlib/source/test/lux/cli.lux
+++ b/stdlib/source/test/lux/cli.lux
@@ -7,8 +7,8 @@
[data
["." error]
[number
- ["." nat ("#/." decimal)]]
- ["." text ("#/." equivalence)
+ ["." nat ("#;." decimal)]]
+ ["." text ("#;." equivalence)
format]
[collection
["." list]]]
@@ -22,9 +22,9 @@
Test
(do r.monad
[num-args (|> r.nat (:: @ map (n/% 10)))
- #let [gen-arg (:: @ map nat/encode r.nat)]
+ #let [gen-arg (:: @ map nat;encode r.nat)]
yes gen-arg
- #let [gen-ignore (r.filter (|>> (text/= yes) not)
+ #let [gen-ignore (r.filter (|>> (text;= yes) not)
(r.unicode 5))]
no gen-ignore
pre-ignore (r.list 5 gen-ignore)
@@ -36,7 +36,7 @@
#0
(#error.Success arg)
- (text/= arg yes))))
+ (text;= arg yes))))
(_.test "Can test tokens."
(and (|> (/.run (list yes) (/.this yes))
(case> (#error.Failure _)
@@ -51,12 +51,12 @@
(#error.Success _)
#0))))
(_.test "Can use custom token parsers."
- (|> (/.run (list yes) (/.parse nat/decode))
+ (|> (/.run (list yes) (/.parse nat;decode))
(case> (#error.Failure _)
#0
(#error.Success parsed)
- (text/= (nat/encode parsed)
+ (text;= (nat;encode parsed)
yes))))
(_.test "Can query if there are any more inputs."
(and (|> (/.run (list) /.end)
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/case.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/case.lux
index a05eda326..5c47960c1 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/case.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/case.lux
@@ -6,12 +6,12 @@
[data
["." product]
["." maybe]
- ["." text ("#/." equivalence)]
+ ["." text ("#;." equivalence)]
[collection
- ["." list ("#/." monad)]
+ ["." list ("#;." monad)]
["." set]]]
[math
- ["r" random ("#/." monad)]]
+ ["r" random ("#;." monad)]]
["." type
["." check]]
[macro
@@ -35,7 +35,7 @@
#.Nil
(#.Cons head+ #.Nil)
- (list/map (|>> list) head+)
+ (list;map (|>> list) head+)
(#.Cons head+ tail++)
(do list.monad
@@ -47,7 +47,7 @@
(-> Bit (List [Code Code]) Code (r.Random (List Code)))
(case inputC
[_ (#.Bit _)]
- (r/wrap (list (' #1) (' #0)))
+ (r;wrap (list (' #1) (' #0)))
(^template [<tag> <gen> <wrapper>]
[_ (<tag> _)]
@@ -62,7 +62,7 @@
#.None
(wrap (list (' _)))))
- (r/wrap (list (' _)))))
+ (r;wrap (list (' _)))))
([#.Nat r.nat code.nat]
[#.Int r.int code.int]
[#.Rev r.rev code.rev]
@@ -70,26 +70,26 @@
[#.Text (r.unicode 5) code.text])
(^ [_ (#.Tuple (list))])
- (r/wrap (list (' [])))
+ (r;wrap (list (' [])))
(^ [_ (#.Record (list))])
- (r/wrap (list (' {})))
+ (r;wrap (list (' {})))
[_ (#.Tuple members)]
(do r.monad
[member-wise-patterns (monad.map @ (exhaustive-branches allow-literals? variantTC) members)]
(wrap (|> member-wise-patterns
exhaustive-weaving
- (list/map code.tuple))))
+ (list;map code.tuple))))
[_ (#.Record kvs)]
(do r.monad
- [#let [ks (list/map product.left kvs)
- vs (list/map product.right kvs)]
+ [#let [ks (list;map product.left kvs)
+ vs (list;map product.right kvs)]
member-wise-patterns (monad.map @ (exhaustive-branches allow-literals? variantTC) vs)]
(wrap (|> member-wise-patterns
exhaustive-weaving
- (list/map (|>> (list.zip2 ks) code.record)))))
+ (list;map (|>> (list.zip2 ks) code.record)))))
(^ [_ (#.Form (list [_ (#.Tag _)] _))])
(do r.monad
@@ -97,13 +97,13 @@
(function (_ [_tag _code])
(do @
[v-branches (exhaustive-branches allow-literals? variantTC _code)]
- (wrap (list/map (function (_ pattern) (` ((~ _tag) (~ pattern))))
+ (wrap (list;map (function (_ pattern) (` ((~ _tag) (~ pattern))))
v-branches))))
variantTC)]
- (wrap (list/join bundles)))
+ (wrap (list;join bundles)))
_
- (r/wrap (list))
+ (r;wrap (list))
))
(def: #export (input variant-tags record-tags primitivesC)
@@ -111,7 +111,7 @@
(r.rec
(function (_ input)
($_ r.either
- (r/map product.right _primitive.primitive)
+ (r;map product.right _primitive.primitive)
(do r.monad
[choice (|> r.nat (:: @ map (n/% (list.size variant-tags))))
#let [choiceT (maybe.assume (list.nth choice variant-tags))
@@ -121,7 +121,7 @@
[size (|> r.nat (:: @ map (n/% 3)))
elems (r.list size input)]
(wrap (code.tuple elems)))
- (r/wrap (code.record (list.zip2 record-tags primitivesC)))
+ (r;wrap (code.record (list.zip2 record-tags primitivesC)))
))))
(def: (branch body pattern)
@@ -136,16 +136,16 @@
(do @
[module-name (r.unicode 5)
variant-name (r.unicode 5)
- record-name (|> (r.unicode 5) (r.filter (|>> (text/= variant-name) not)))
+ record-name (|> (r.unicode 5) (r.filter (|>> (text;= variant-name) not)))
size (|> r.nat (:: @ map (|>> (n/% 10) (n/max 2))))
variant-tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list))
record-tags (|> (r.set text.hash size (r.unicode 5)) (:: @ map set.to-list))
primitivesTC (r.list size _primitive.primitive)
- #let [primitivesT (list/map product.left primitivesTC)
- primitivesC (list/map product.right primitivesTC)
+ #let [primitivesT (list;map product.left primitivesTC)
+ primitivesC (list;map product.right primitivesTC)
code-tag (|>> [module-name] code.tag)
- variant-tags+ (list/map code-tag variant-tags)
- record-tags+ (list/map code-tag record-tags)
+ variant-tags+ (list;map code-tag variant-tags)
+ record-tags+ (list;map code-tag record-tags)
variantTC (list.zip2 variant-tags+ primitivesC)]
inputC (input variant-tags+ record-tags+ primitivesC)
[outputT outputC] _primitive.primitive
@@ -155,11 +155,11 @@
redundant-patterns (exhaustive-branches #0 variantTC inputC)
redundancy-idx (|> r.nat (:: @ map (n/% (list.size redundant-patterns))))
heterogeneous-idx (|> r.nat (:: @ map (n/% (list.size exhaustive-patterns))))
- #let [exhaustive-branchesC (list/map (branch outputC)
+ #let [exhaustive-branchesC (list;map (branch outputC)
exhaustive-patterns)
non-exhaustive-branchesC (list.take (dec (list.size exhaustive-branchesC))
exhaustive-branchesC)
- redundant-branchesC (<| (list/map (branch outputC))
+ redundant-branchesC (<| (list;map (branch outputC))
list.concat
(list (list.take redundancy-idx redundant-patterns)
(list (maybe.assume (list.nth redundancy-idx redundant-patterns)))
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/function.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/function.lux
index 829f83713..acdb9e7ff 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/function.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/function.lux
@@ -7,10 +7,10 @@
["." error]
["." maybe]
["." product]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]
["." type]
@@ -48,7 +48,7 @@
(<| (times 100)
(do @
[func-name (r.unicode 5)
- arg-name (|> (r.unicode 5) (r.filter (|>> (text/= func-name) not)))
+ arg-name (|> (r.unicode 5) (r.filter (|>> (text;= func-name) not)))
[outputT outputC] _primitive.primitive
[inputT _] _primitive.primitive
#let [g!arg (code.local-identifier arg-name)]]
@@ -80,8 +80,8 @@
partial-args (|> r.nat (:: @ map (n/% full-args)))
var-idx (|> r.nat (:: @ map (|>> (n/% full-args) (n/max 1))))
inputsTC (r.list full-args _primitive.primitive)
- #let [inputsT (list/map product.left inputsTC)
- inputsC (list/map product.right inputsTC)]
+ #let [inputsT (list;map product.left inputsTC)
+ inputsC (list;map product.right inputsTC)]
[outputT outputC] _primitive.primitive
#let [funcT (type.function inputsT outputT)
partialT (type.function (list.drop partial-args inputsT) outputT)
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/primitive.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/primitive.lux
index b73e4f81c..0c716dd3f 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/primitive.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/primitive.lux
@@ -9,8 +9,8 @@
[text
format]]
[math
- ["r" random ("#/." monad)]]
- ["." type ("#/." equivalence)]
+ ["r" random ("#;." monad)]]
+ ["." type ("#;." equivalence)]
[macro
["." code]]
[compiler
@@ -35,13 +35,13 @@
(def: unit
(r.Random Code)
- (r/wrap (' [])))
+ (r;wrap (' [])))
(def: #export primitive
(r.Random [Type Code])
(`` ($_ r.either
(~~ (do-template [<type> <code-wrapper> <value-gen>]
- [(r.and (r/wrap <type>) (r/map <code-wrapper> <value-gen>))]
+ [(r.and (r;wrap <type>) (r;map <code-wrapper> <value-gen>))]
[Any code.tuple (r.list 0 ..unit)]
[Bit code.bit r.bit]
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/procedure/common.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/procedure/common.lux
index 5464981a1..7d83f00c8 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/procedure/common.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/procedure/common.lux
@@ -13,7 +13,7 @@
format]]
[math
["r" random]]
- ["." type ("#/." equivalence)]
+ ["." type ("#;." equivalence)]
[macro
["." code]]
[compiler
@@ -51,7 +51,7 @@
(do @
[[primT primC] _primitive.primitive
[antiT antiC] (|> _primitive.primitive
- (r.filter (|>> product.left (type/= primT) not)))]
+ (r.filter (|>> product.left (type;= primT) not)))]
($_ seq
(test "Can test for reference equality."
(check-success+ "lux is" (list primC primC) Bit))
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/reference.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/reference.lux
index b2f64ac19..4cf1f9da0 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/reference.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/reference.lux
@@ -5,11 +5,11 @@
pipe]
[data
["." error (#+ Error)]
- ["." name ("#/." equivalence)]
- ["." text ("#/." equivalence)]]
+ ["." name ("#;." equivalence)]
+ ["." text ("#;." equivalence)]]
[math
["r" random]]
- ["." type ("#/." equivalence)]
+ ["." type ("#;." equivalence)]
[macro
["." code]]
[compiler
@@ -70,7 +70,7 @@
scope-name (r.unicode 5)
var-name (r.unicode 5)
dependent-module (|> (r.unicode 5)
- (r.filter (|>> (text/= def-module) not)))]
+ (r.filter (|>> (text;= def-module) not)))]
($_ seq
(test "Can analyse variable."
(|> (scope.with-scope scope-name
@@ -79,7 +79,7 @@
(_primitive.phase (code.local-identifier var-name)))))
(phase.run _primitive.state)
(case> (^ (#error.Success [inferredT (#analysis.Reference (reference.local var))]))
- (and (type/= expectedT inferredT)
+ (and (type;= expectedT inferredT)
(n/= 0 var))
_
@@ -93,8 +93,8 @@
(module.with-module 0 def-module)
(phase.run _primitive.state)
(case> (^ (#error.Success [_ inferredT (#analysis.Reference (reference.constant constant-name))]))
- (and (type/= expectedT inferredT)
- (name/= def-name constant-name))
+ (and (type;= expectedT inferredT)
+ (name;= def-name constant-name))
_
#0))))
diff --git a/stdlib/source/test/lux/compiler/default/phase/analysis/structure.lux b/stdlib/source/test/lux/compiler/default/phase/analysis/structure.lux
index 34a43c042..6d575fd08 100644
--- a/stdlib/source/test/lux/compiler/default/phase/analysis/structure.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/analysis/structure.lux
@@ -4,17 +4,17 @@
[monad (#+ do)]
pipe]
[data
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
["e" error]
["." product]
["." maybe]
["." text]
[collection
- ["." list ("#/." functor)]
+ ["." list ("#;." functor)]
["." set]]]
[math
["r" random]]
- ["." type ("#/." equivalence)
+ ["." type ("#;." equivalence)
["." check]]
[macro
["." code]]
@@ -53,7 +53,7 @@
(inc (get@ #analysis.lefts variant))
(get@ #analysis.lefts variant))]
(|> size dec (n/= tag)
- (bit/= (get@ #analysis.right? variant))
+ (bit;= (get@ #analysis.right? variant))
(and (n/= tag variant-tag)))))
(def: (check-sum type size tag analysis)
@@ -101,7 +101,7 @@
(tagged module tags type)
(phase.run _primitive.state)
(case> (#e.Success [_ productT productA])
- (and (type/= type productT)
+ (and (type;= type productT)
(right-size? size productA))
_
@@ -115,14 +115,14 @@
primitives (r.list size _primitive.primitive)
+choice (|> r.nat (:: @ map (n/% (inc size))))
[_ +valueC] _primitive.primitive
- #let [variantT (type.variant (list/map product.left primitives))
+ #let [variantT (type.variant (list;map product.left primitives))
[valueT valueC] (maybe.assume (list.nth choice primitives))
+size (inc size)
+primitives (list.concat (list (list.take choice primitives)
(list [(#.Parameter 1) +valueC])
(list.drop choice primitives)))
[+valueT +valueC] (maybe.assume (list.nth +choice +primitives))
- +variantT (type.variant (list/map product.left +primitives))]]
+ +variantT (type.variant (list;map product.left +primitives))]]
($_ seq
(test "Can analyse sum."
(check-sum variantT size choice
@@ -166,16 +166,16 @@
primitives (r.list size _primitive.primitive)
choice (|> r.nat (:: @ map (n/% size)))
[_ +valueC] _primitive.primitive
- #let [tupleT (type.tuple (list/map product.left primitives))
+ #let [tupleT (type.tuple (list;map product.left primitives))
[singletonT singletonC] (|> primitives (list.nth choice) maybe.assume)
+primitives (list.concat (list (list.take choice primitives)
(list [(#.Parameter 1) +valueC])
(list.drop choice primitives)))
- +tupleT (type.tuple (list/map product.left +primitives))]]
+ +tupleT (type.tuple (list;map product.left +primitives))]]
($_ seq
(test "Can analyse product."
(|> (typeA.with-type tupleT
- (/.product _primitive.phase (list/map product.right primitives)))
+ (/.product _primitive.phase (list;map product.right primitives)))
(phase.run _primitive.state)
(case> (#e.Success tupleA)
(right-size? size tupleA)
@@ -184,10 +184,10 @@
#0)))
(test "Can infer product."
(|> (typeA.with-inference
- (/.product _primitive.phase (list/map product.right primitives)))
+ (/.product _primitive.phase (list;map product.right primitives)))
(phase.run _primitive.state)
(case> (#e.Success [_type tupleA])
- (and (type/= tupleT _type)
+ (and (type;= tupleT _type)
(right-size? size tupleA))
_
@@ -200,9 +200,9 @@
(|> (do phase.monad
[[_ varT] (typeA.with-env check.var)
_ (typeA.with-env
- (check.check varT (type.tuple (list/map product.left primitives))))]
+ (check.check varT (type.tuple (list;map product.left primitives))))]
(typeA.with-type varT
- (/.product _primitive.phase (list/map product.right primitives))))
+ (/.product _primitive.phase (list;map product.right primitives))))
(phase.run _primitive.state)
(case> (#e.Success tupleA)
(right-size? size tupleA)
@@ -211,11 +211,11 @@
#0)))
(test "Can analyse product through existential quantification."
(|> (typeA.with-type (type.ex-q 1 +tupleT)
- (/.product _primitive.phase (list/map product.right +primitives)))
+ (/.product _primitive.phase (list;map product.right +primitives)))
check-succeeds))
(test "Cannot analyse product through universal quantification."
(|> (typeA.with-type (type.univ-q 1 +tupleT)
- (/.product _primitive.phase (list/map product.right +primitives)))
+ (/.product _primitive.phase (list;map product.right +primitives)))
check-fails))
))))
@@ -230,7 +230,7 @@
module-name (r.unicode 5)
type-name (r.unicode 5)
#let [varT (#.Parameter 1)
- primitivesT (list/map product.left primitives)
+ primitivesT (list;map product.left primitives)
[choiceT choiceC] (maybe.assume (list.nth choice primitives))
[other-choiceT other-choiceC] (maybe.assume (list.nth other-choice primitives))
variantT (type.variant primitivesT)
@@ -268,9 +268,9 @@
type-name (r.unicode 5)
choice (|> r.nat (:: @ map (n/% size)))
#let [varT (#.Parameter 1)
- tagsC (list/map (|>> [module-name] code.tag) tags)
- primitivesT (list/map product.left primitives)
- primitivesC (list/map product.right primitives)
+ tagsC (list;map (|>> [module-name] code.tag) tags)
+ primitivesT (list;map product.left primitives)
+ primitivesC (list;map product.right primitives)
tupleT (type.tuple primitivesT)
namedT (#.Named [module-name type-name] tupleT)
recordC (list.zip2 tagsC primitivesC)
diff --git a/stdlib/source/test/lux/compiler/default/phase/synthesis/case.lux b/stdlib/source/test/lux/compiler/default/phase/synthesis/case.lux
index 7a67e4bfa..9a635eb9e 100644
--- a/stdlib/source/test/lux/compiler/default/phase/synthesis/case.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/synthesis/case.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]
pipe]
[data
- ["." error ("#/." functor)]]
+ ["." error ("#;." functor)]]
[compiler
[default
["." reference]
@@ -33,7 +33,7 @@
(|> maskA
expression.phase
(phase.run [bundle.empty //.init])
- (error/map (//primitive.corresponds? maskedA))
+ (error;map (//primitive.corresponds? maskedA))
(error.default #0))))))
(context: "Let expressions."
diff --git a/stdlib/source/test/lux/compiler/default/phase/synthesis/function.lux b/stdlib/source/test/lux/compiler/default/phase/synthesis/function.lux
index 4866086aa..9d7edb358 100644
--- a/stdlib/source/test/lux/compiler/default/phase/synthesis/function.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/synthesis/function.lux
@@ -11,12 +11,12 @@
[text
format]
[collection
- ["." list ("#/." functor fold)]
+ ["." list ("#;." functor fold)]
["dict" dictionary (#+ Dictionary)]
["." set]]]
[compiler
[default
- ["." reference (#+ Variable) ("variable/." equivalence)]
+ ["." reference (#+ Variable) ("variable;." equivalence)]
["." phase
["." analysis (#+ Arity Analysis)]
["//" synthesis (#+ Synthesis)
@@ -53,13 +53,13 @@
(do r.monad
[num-locals (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10))))
#let [indices (list.n/range 0 (dec num-locals))
- local-env (list/map (|>> #reference.Local) indices)
- foreign-env (list/map (|>> #reference.Foreign) indices)]
+ local-env (list;map (|>> #reference.Local) indices)
+ foreign-env (list;map (|>> #reference.Foreign) indices)]
[arity bodyA predictionA] (: (r.Random [Arity Analysis Variable])
(loop [arity 1
current-env foreign-env]
(let [current-env/size (list.size current-env)
- resolver (list/fold (function (_ [idx var] resolver)
+ resolver (list;fold (function (_ [idx var] resolver)
(dict.put idx var resolver))
(: (Dictionary Nat Variable)
(dict.new number.hash))
@@ -72,10 +72,10 @@
picks (|> (r.set number.hash num-picks (pick current-env/size))
(:: @ map set.to-list))
[arity bodyA predictionA] (recur (inc arity)
- (list/map (function (_ pick)
+ (list;map (function (_ pick)
(maybe.assume (list.nth pick current-env)))
picks))
- #let [picked-env (list/map (|>> #reference.Foreign) picks)]]
+ #let [picked-env (list;map (|>> #reference.Foreign) picks)]]
(wrap [arity
(#analysis.Function picked-env bodyA)
predictionA]))
diff --git a/stdlib/source/test/lux/compiler/default/phase/synthesis/structure.lux b/stdlib/source/test/lux/compiler/default/phase/synthesis/structure.lux
index 97d4c037d..d24131f04 100644
--- a/stdlib/source/test/lux/compiler/default/phase/synthesis/structure.lux
+++ b/stdlib/source/test/lux/compiler/default/phase/synthesis/structure.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]
pipe]
[data
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
["." product]
["." error]
[collection
@@ -40,7 +40,7 @@
(case> (^ (#error.Success (//.variant [leftsS right?S valueS])))
(let [tagS (if right?S (inc leftsS) leftsS)]
(and (n/= tagA tagS)
- (|> tagS (n/= (dec size)) (bit/= right?S))
+ (|> tagS (n/= (dec size)) (bit;= right?S))
(//primitive.corresponds? memberA valueS)))
_
diff --git a/stdlib/source/test/lux/compiler/default/syntax.lux b/stdlib/source/test/lux/compiler/default/syntax.lux
index 6f1d2152d..530bbfbad 100644
--- a/stdlib/source/test/lux/compiler/default/syntax.lux
+++ b/stdlib/source/test/lux/compiler/default/syntax.lux
@@ -11,7 +11,7 @@
["." list]
["." dictionary (#+ Dictionary)]]]
[math
- ["r" random ("#/." monad)]]
+ ["r" random ("#;." monad)]]
[macro
["." code]]
[compiler
@@ -48,18 +48,18 @@
(r.Random Code)
(let [numeric^ (: (r.Random Code)
($_ r.either
- (|> r.bit (r/map code.bit))
- (|> r.nat (r/map code.nat))
- (|> r.int (r/map code.int))
- (|> r.rev (r/map code.rev))
- (|> r.frac (r/map code.frac))))
+ (|> r.bit (r;map code.bit))
+ (|> r.nat (r;map code.nat))
+ (|> r.int (r;map code.int))
+ (|> r.rev (r;map code.rev))
+ (|> r.frac (r;map code.frac))))
textual^ (: (r.Random Code)
($_ r.either
(do r.monad
- [size (|> r.nat (r/map (n/% 20)))]
- (|> (r.unicode size) (r/map code.text)))
- (|> name^ (r/map code.identifier))
- (|> name^ (r/map code.tag))))
+ [size (|> r.nat (r;map (n/% 20)))]
+ (|> (r.unicode size) (r;map code.text)))
+ (|> name^ (r;map code.identifier))
+ (|> name^ (r;map code.tag))))
simple^ (: (r.Random Code)
($_ r.either
numeric^
@@ -67,16 +67,16 @@
(r.rec
(function (_ code^)
(let [multi^ (do r.monad
- [size (|> r.nat (r/map (n/% 3)))]
+ [size (|> r.nat (r;map (n/% 3)))]
(r.list size code^))
composite^ (: (r.Random Code)
($_ r.either
- (|> multi^ (r/map code.form))
- (|> multi^ (r/map code.tuple))
+ (|> multi^ (r;map code.form))
+ (|> multi^ (r;map code.tuple))
(do r.monad
- [size (|> r.nat (r/map (n/% 3)))]
+ [size (|> r.nat (r;map (n/% 3)))]
(|> (r.list size (r.and code^ code^))
- (r/map code.record)))))]
+ (r;map code.record)))))]
(r.either simple^
composite^))))))
@@ -118,7 +118,7 @@
(r.Random Text)
(let [char-gen (|> r.nat (r.filter (|>> (n/= (`` (char (~~ (static text.new-line))))) not)))]
(do r.monad
- [size (|> r.nat (r/map (n/% 20)))]
+ [size (|> r.nat (r;map (n/% 20)))]
(r.text char-gen size))))
(def: comment^
diff --git a/stdlib/source/test/lux/control/apply.lux b/stdlib/source/test/lux/control/apply.lux
index 42d2fa8b9..1cd756509 100644
--- a/stdlib/source/test/lux/control/apply.lux
+++ b/stdlib/source/test/lux/control/apply.lux
@@ -2,7 +2,9 @@
[lux #*
[control
[monad (#+ do)]]
- data/text/format
+ [data
+ [text
+ format]]
["." function]
[math
["r" random]]
@@ -12,36 +14,36 @@
[//
[functor (#+ Injection Comparison)]])
-(def: (identity injection comparison (^open "_/."))
+(def: (identity injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Apply f) Test))
(do r.monad
[sample (:: @ map injection r.nat)]
(_.test "Identity."
((comparison n/=)
- (_/apply (injection function.identity) sample)
+ (_;apply (injection function.identity) sample)
sample))))
-(def: (homomorphism injection comparison (^open "_/."))
+(def: (homomorphism injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Apply f) Test))
(do r.monad
[sample r.nat
increase (:: @ map n/+ r.nat)]
(_.test "Homomorphism."
((comparison n/=)
- (_/apply (injection increase) (injection sample))
+ (_;apply (injection increase) (injection sample))
(injection (increase sample))))))
-(def: (interchange injection comparison (^open "_/."))
+(def: (interchange injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Apply f) Test))
(do r.monad
[sample r.nat
increase (:: @ map n/+ r.nat)]
(_.test "Interchange."
((comparison n/=)
- (_/apply (injection increase) (injection sample))
- (_/apply (injection (function (_ f) (f sample))) (injection increase))))))
+ (_;apply (injection increase) (injection sample))
+ (_;apply (injection (function (_ f) (f sample))) (injection increase))))))
-(def: (composition injection comparison (^open "_/."))
+(def: (composition injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Apply f) Test))
(do r.monad
[sample r.nat
@@ -49,12 +51,12 @@
decrease (:: @ map n/- r.nat)]
(_.test "Composition."
((comparison n/=)
- (_$ _/apply
+ (_$ _;apply
(injection function.compose)
(injection increase)
(injection decrease)
(injection sample))
- ($_ _/apply
+ ($_ _;apply
(injection increase)
(injection decrease)
(injection sample))))))
diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux
index 90c88744c..014e4d758 100644
--- a/stdlib/source/test/lux/control/concurrency/actor.lux
+++ b/stdlib/source/test/lux/control/concurrency/actor.lux
@@ -6,7 +6,7 @@
["M" monad (#+ do Monad)]
["ex" exception]
[concurrency
- ["." promise ("#/." monad)]]]
+ ["." promise ("#;." monad)]]]
[data
["." error]
[text
@@ -27,14 +27,14 @@
(wrap output)))
((stop cause state)
- (promise/wrap (log! (if (ex.match? /.poisoned cause)
+ (promise;wrap (log! (if (ex.match? /.poisoned cause)
(format "Counter was poisoned: " (%n state))
cause)))))
(message: #export Counter
(count! {increment Nat} state self Nat)
(let [state' (n/+ increment state)]
- (promise/wrap (#error.Success [state' state']))))
+ (promise;wrap (#error.Success [state' state']))))
(def: #export test
Test
diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux
index b49a9e649..ea4d7adad 100644
--- a/stdlib/source/test/lux/control/concurrency/frp.lux
+++ b/stdlib/source/test/lux/control/concurrency/frp.lux
@@ -5,13 +5,13 @@
[control
["." monad (#+ do)]
[concurrency
- ["." promise ("#/." monad)]
+ ["." promise ("#;." monad)]
["." atom (#+ Atom atom)]]]
[data
[number
["." nat]]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]]
{1
@@ -19,7 +19,7 @@
(def: #export test
Test
- (let [(^open "list/.") (list.equivalence nat.equivalence)]
+ (let [(^open "list;.") (list.equivalence nat.equivalence)]
(do r.monad
[inputs (r.list 5 r.nat)
sample r.nat]
@@ -30,7 +30,7 @@
(/.filter n/even?)
/.consume)]
(_.assert "Can filter a channel's elements."
- (list/= (list.filter n/even? inputs)
+ (list;= (list.filter n/even? inputs)
output))))
(wrap (do promise.monad
[output (|> inputs
@@ -38,22 +38,22 @@
(:: /.functor map inc)
/.consume)]
(_.assert "Functor goes over every element in a channel."
- (list/= (list/map inc inputs)
+ (list;= (list;map inc inputs)
output))))
(wrap (do promise.monad
[output (/.consume (:: /.apply apply
(/.sequential 0 (list inc))
(/.sequential 0 (list sample))))]
(_.assert "Apply works over all channel values."
- (list/= (list (inc sample))
+ (list;= (list (inc sample))
output))))
(wrap (do promise.monad
[output (/.consume
(do /.monad
- [f (/.from-promise (promise/wrap inc))
- a (/.from-promise (promise/wrap sample))]
+ [f (/.from-promise (promise;wrap inc))
+ a (/.from-promise (promise;wrap sample))]
(wrap (f a))))]
(_.assert "Valid monad."
- (list/= (list (inc sample))
+ (list;= (list (inc sample))
output))))
))))
diff --git a/stdlib/source/test/lux/control/concurrency/promise.lux b/stdlib/source/test/lux/control/concurrency/promise.lux
index e50320901..295c26e20 100644
--- a/stdlib/source/test/lux/control/concurrency/promise.lux
+++ b/stdlib/source/test/lux/control/concurrency/promise.lux
@@ -5,7 +5,7 @@
["M" monad (#+ Monad do)]
pipe
[concurrency
- ["&" promise ("&/." monad)]]]
+ ["&" promise ("&;." monad)]]]
[math
["r" random]]]
lux/test)
@@ -50,7 +50,7 @@
(and ?left (not ?right)))))
(test "Can poll a promise for its value."
- (and (|> (&.poll (&/wrap #1))
+ (and (|> (&.poll (&;wrap #1))
(case> (#.Some #1) #1 _ #0))
(|> (&.poll (&.delay 200 #1))
(case> #.None #1 _ #0))))
diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux
index 3ceac16b7..4aa4b08a5 100644
--- a/stdlib/source/test/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux
@@ -8,10 +8,10 @@
["." atom (#+ Atom)]]]
[data
["." maybe]
- ["." text ("#/." equivalence monoid)
+ ["." text ("#;." equivalence monoid)
format]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
["." io]
[math
["r" random]]]
@@ -74,7 +74,7 @@
## (/.signal semaphore))
## _ blocked]
## (assert "A blocked process can be un-blocked by a signal somewhere else."
-## (text/= "BA"
+## (text;= "BA"
## (io.run (atom.read resource)))))))
## ))))
@@ -108,9 +108,9 @@
## _ processB
## #let [outcome (io.run (atom.read resource))]]
## (assert "Mutexes only allow one process to execute at a time."
-## (or (text/= (format expected-As expected-Bs)
+## (or (text;= (format expected-As expected-Bs)
## outcome)
-## (text/= (format expected-Bs expected-As)
+## (text;= (format expected-Bs expected-As)
## outcome))))))
## ))))
@@ -128,7 +128,7 @@
## ($_ seq
## (wrap (do promise.monad
## [#let [ids (list.n/range 0 (dec limit))
-## waiters (list/map (function (_ id)
+## waiters (list;map (function (_ id)
## (let [process (waiter resource barrier id)]
## (exec (io.run (atom.update (|>> (format "_")) resource))
## process)))
diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux
index 869a995b0..6e386c630 100644
--- a/stdlib/source/test/lux/control/concurrency/stm.lux
+++ b/stdlib/source/test/lux/control/concurrency/stm.lux
@@ -12,7 +12,7 @@
[data
["." number]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]]
lux/test)
@@ -65,7 +65,7 @@
(do promise.monad
[_ (|> process.parallelism
(list.n/range 1)
- (list/map (function (_ _)
+ (list;map (function (_ _)
(|> iterations-per-process
(list.n/range 1)
(M.map @ (function (_ _) (&.commit (&.update inc _concurrency-var)))))))
diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux
index ec4495a20..cb238cd88 100644
--- a/stdlib/source/test/lux/control/continuation.lux
+++ b/stdlib/source/test/lux/control/continuation.lux
@@ -34,12 +34,12 @@
(<| (_.context (%name (name-of /.Cont)))
(do r.monad
[sample r.nat
- #let [(^open "_/.") /.apply
- (^open "_/.") /.monad]
+ #let [(^open "_;.") /.apply
+ (^open "_;.") /.monad]
elems (r.list 3 r.nat)]
($_ _.and
(_.test "Can run continuations to compute their values."
- (n/= sample (/.run (_/wrap sample))))
+ (n/= sample (/.run (_;wrap sample))))
(functorT.laws ..injection ..comparison /.functor)
(applyT.laws ..injection ..comparison /.apply)
@@ -67,14 +67,14 @@
(wrap output))))))
(_.test "Can use delimited continuations with shifting."
- (let [(^open "_/.") /.monad
- (^open "list/.") (list.equivalence nat.equivalence)
+ (let [(^open "_;.") /.monad
+ (^open "list;.") (list.equivalence nat.equivalence)
visit (: (-> (List Nat)
(Cont (List Nat) (List Nat)))
(function (visit xs)
(case xs
#.Nil
- (_/wrap #.Nil)
+ (_;wrap #.Nil)
(#.Cons x xs')
(do /.monad
@@ -83,6 +83,6 @@
[tail (k xs')]
(wrap (#.Cons x tail)))))]
(visit output)))))]
- (list/= elems
+ (list;= elems
(/.run (/.reset (visit elems))))))
))))
diff --git a/stdlib/source/test/lux/control/equivalence.lux b/stdlib/source/test/lux/control/equivalence.lux
index 714905c41..4e7992d58 100644
--- a/stdlib/source/test/lux/control/equivalence.lux
+++ b/stdlib/source/test/lux/control/equivalence.lux
@@ -3,13 +3,15 @@
["_" test (#+ Test)]
[control
[monad (#+ do)]]
- data/text/format
+ [data
+ [text
+ format]]
[math
["r" random (#+ Random)]]]
{1
["." / (#+ Equivalence)]})
-(def: #export (test (^open "_/.") generator)
+(def: #export (test (^open "_;.") generator)
(All [a] (-> (Equivalence a) (Random a) Test))
(do r.monad
[left generator
@@ -17,8 +19,8 @@
(<| (_.context (%name (name-of /.Equivalence)))
($_ _.and
(_.test "Reflexivity."
- (_/= left left))
+ (_;= left left))
(_.test "Symmetry."
- (if (_/= left right)
- (_/= right left)
- (not (_/= right left))))))))
+ (if (_;= left right)
+ (_;= right left)
+ (not (_;= right left))))))))
diff --git a/stdlib/source/test/lux/control/functor.lux b/stdlib/source/test/lux/control/functor.lux
index ea0525e04..08b706b03 100644
--- a/stdlib/source/test/lux/control/functor.lux
+++ b/stdlib/source/test/lux/control/functor.lux
@@ -2,7 +2,9 @@
[lux #*
[control
[monad (#+ do)]]
- data/text/format
+ [data
+ [text
+ format]]
["." function]
[math
["r" random]]
@@ -18,26 +20,26 @@
(-> (-> a a Bit)
(-> (f a) (f a) Bit))))
-(def: (identity injection comparison (^open "_/."))
+(def: (identity injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Functor f) Test))
(do r.monad
[sample (:: @ map injection r.nat)]
(_.test "Identity."
((comparison n/=)
- (_/map function.identity sample)
+ (_;map function.identity sample)
sample))))
-(def: (homomorphism injection comparison (^open "_/."))
+(def: (homomorphism injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Functor f) Test))
(do r.monad
[sample r.nat
increase (:: @ map n/+ r.nat)]
(_.test "Homomorphism."
((comparison n/=)
- (_/map increase (injection sample))
+ (_;map increase (injection sample))
(injection (increase sample))))))
-(def: (composition injection comparison (^open "_/."))
+(def: (composition injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Functor f) Test))
(do r.monad
[sample (:: @ map injection r.nat)
@@ -45,8 +47,8 @@
decrease (:: @ map n/- r.nat)]
(_.test "Composition."
((comparison n/=)
- (|> sample (_/map increase) (_/map decrease))
- (|> sample (_/map (|>> increase decrease)))))))
+ (|> sample (_;map increase) (_;map decrease))
+ (|> sample (_;map (|>> increase decrease)))))))
(def: #export (laws injection comparison functor)
(All [f] (-> (Injection f) (Comparison f) (Functor f) Test))
diff --git a/stdlib/source/test/lux/control/interval.lux b/stdlib/source/test/lux/control/interval.lux
index 4874d3742..dbac4cc8e 100644
--- a/stdlib/source/test/lux/control/interval.lux
+++ b/stdlib/source/test/lux/control/interval.lux
@@ -15,7 +15,7 @@
[math
["r" random (#+ Random)]]]
{1
- ["." / (#+ Interval) ("_/." equivalence)]}
+ ["." / (#+ Interval) ("_;." equivalence)]}
{0
[test
[lux
@@ -80,7 +80,7 @@
right-outer ..outer]
($_ _.and
(_.test "The union of an interval to itself yields the same interval."
- (_/= some-interval (/.union some-interval some-interval)))
+ (_;= some-interval (/.union some-interval some-interval)))
(_.test "The union of 2 inner intervals is another inner interval."
(/.inner? (/.union left-inner right-inner)))
(_.test "The union of 2 outer intervals yields an inner interval when their complements don't overlap, and an outer when they do."
@@ -101,7 +101,7 @@
right-outer ..outer]
($_ _.and
(_.test "The intersection of an interval to itself yields the same interval."
- (_/= some-interval (/.intersection some-interval some-interval)))
+ (_;= some-interval (/.intersection some-interval some-interval)))
(_.test "The intersection of 2 inner intervals yields an inner interval when they overlap, and an outer when they don't."
(if (/.overlaps? left-inner right-inner)
(/.inner? (/.intersection left-inner right-inner))
@@ -116,7 +116,7 @@
[some-interval ..interval]
($_ _.and
(_.test "The complement of a complement is the same as the original."
- (_/= some-interval (|> some-interval /.complement /.complement)))
+ (_;= some-interval (|> some-interval /.complement /.complement)))
(_.test "The complement of an interval does not overlap it."
(not (/.overlaps? some-interval (/.complement some-interval))))
)))
diff --git a/stdlib/source/test/lux/control/monad.lux b/stdlib/source/test/lux/control/monad.lux
index 5cb498222..2edcd1705 100644
--- a/stdlib/source/test/lux/control/monad.lux
+++ b/stdlib/source/test/lux/control/monad.lux
@@ -1,6 +1,8 @@
(.module:
[lux #*
- data/text/format
+ [data
+ [text
+ format]]
["." function]
[math
["r" random]]
@@ -10,41 +12,41 @@
[//
[functor (#+ Injection Comparison)]])
-(def: (left-identity injection comparison (^open "_/."))
+(def: (left-identity injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Monad f) Test))
(do r.monad
[sample r.nat
morphism (:: @ map (function (_ diff)
- (|>> (n/+ diff) _/wrap))
+ (|>> (n/+ diff) _;wrap))
r.nat)]
(_.test "Left identity."
((comparison n/=)
- (|> (injection sample) (_/map morphism) _/join)
+ (|> (injection sample) (_;map morphism) _;join)
(morphism sample)))))
-(def: (right-identity injection comparison (^open "_/."))
+(def: (right-identity injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Monad f) Test))
(do r.monad
[sample r.nat]
(_.test "Right identity."
((comparison n/=)
- (|> (injection sample) (_/map _/wrap) _/join)
+ (|> (injection sample) (_;map _;wrap) _;join)
(injection sample)))))
-(def: (associativity injection comparison (^open "_/."))
+(def: (associativity injection comparison (^open "_;."))
(All [f] (-> (Injection f) (Comparison f) (Monad f) Test))
(do r.monad
[sample r.nat
increase (:: @ map (function (_ diff)
- (|>> (n/+ diff) _/wrap))
+ (|>> (n/+ diff) _;wrap))
r.nat)
decrease (:: @ map (function (_ diff)
- (|>> (n/- diff) _/wrap))
+ (|>> (n/- diff) _;wrap))
r.nat)]
(_.test "Associativity."
((comparison n/=)
- (|> (injection sample) (_/map increase) _/join (_/map decrease) _/join)
- (|> (injection sample) (_/map (|>> increase (_/map decrease) _/join)) _/join)))))
+ (|> (injection sample) (_;map increase) _;join (_;map decrease) _;join)
+ (|> (injection sample) (_;map (|>> increase (_;map decrease) _;join)) _;join)))))
(def: #export (laws injection comparison monad)
(All [f] (-> (Injection f) (Comparison f) (Monad f) Test))
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux
index 47740098d..58c2a98d0 100644
--- a/stdlib/source/test/lux/control/parser.lux
+++ b/stdlib/source/test/lux/control/parser.lux
@@ -13,10 +13,10 @@
["." error (#+ Error)]
[number
["." nat]]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]
[macro
@@ -29,7 +29,7 @@
(All [a] (-> Text (Error a) Bit))
(case input
(#error.Failure actual)
- (text/= expected actual)
+ (text;= expected actual)
_
#0))
@@ -90,16 +90,16 @@
#1))))
(_.test "Can apply a parser 0 or more times."
(and (|> (/.some s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) = expected+ actual)))
(|> (/.some s.nat)
- (/.run (list/map (|>> .int code.int) expected+))
+ (/.run (list;map (|>> .int code.int) expected+))
(match #.Nil
#1))))
(_.test "Can apply a parser 1 or more times."
(and (|> (/.many s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) = expected+ actual)))
(|> (/.many s.nat)
@@ -107,7 +107,7 @@
(match (list actual)
(n/= expected0 actual)))
(|> (/.many s.nat)
- (/.run (list/map (|>> .int code.int) expected+))
+ (/.run (list;map (|>> .int code.int) expected+))
fails?)))
(_.test "Can use either parser."
(let [even (/.filter n/even? s.nat)
@@ -145,63 +145,63 @@
(should-fail failure)))
(_.test "Can apply a parser N times."
(and (|> (/.exactly times s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) =
(list.take times expected+)
actual)))
(|> (/.exactly (inc variadic) s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
fails?)))
(_.test "Can apply a parser at-least N times."
(and (|> (/.at-least times s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) =
expected+
actual)))
(|> (/.at-least (inc variadic) s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
fails?)))
(_.test "Can apply a parser at-most N times."
(and (|> (/.at-most times s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) =
(list.take times expected+)
actual)))
(|> (/.at-most (inc variadic) s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) =
expected+
actual)))))
(_.test "Can apply a parser between N and M times."
(and (|> (/.between times variadic s.nat)
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence nat.equivalence) =
expected+
actual)))
(|> (/.between times variadic s.nat)
- (/.run (list/map code.nat (list.take times expected+)))
+ (/.run (list;map code.nat (list.take times expected+)))
(match actual
(:: (list.equivalence nat.equivalence) =
(list.take times expected+)
actual)))))
(_.test "Can parse while taking separators into account."
(|> (/.sep-by (s.this (code.text separator)) s.nat)
- (/.run (list.interpose (code.text separator) (list/map code.nat expected+)))
+ (/.run (list.interpose (code.text separator) (list;map code.nat expected+)))
(match actual
(:: (list.equivalence nat.equivalence) =
expected+
actual))))
(_.test "Can obtain the whole of the remaining input."
(|> /.remaining
- (/.run (list/map code.nat expected+))
+ (/.run (list;map code.nat expected+))
(match actual
(:: (list.equivalence code.equivalence) =
- (list/map code.nat expected+)
+ (list;map code.nat expected+)
actual))))
)))
diff --git a/stdlib/source/test/lux/control/pipe.lux b/stdlib/source/test/lux/control/pipe.lux
index 371021ddd..fda914291 100644
--- a/stdlib/source/test/lux/control/pipe.lux
+++ b/stdlib/source/test/lux/control/pipe.lux
@@ -5,7 +5,7 @@
[monad (#+ do)]]
[data
["." identity]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -32,7 +32,7 @@
(let> x [(n/+ x x)]))))
(_.test "'Conditional' branching."
- (text/= (cond (n/= 0 sample) "zero"
+ (text;= (cond (n/= 0 sample) "zero"
(n/even? sample) "even"
"odd")
(|> sample
@@ -41,7 +41,7 @@
[(new> "odd" [])]))))
(_.test "'If' branching."
- (text/= (if (n/even? sample)
+ (text;= (if (n/even? sample)
"even"
"odd")
(|> sample
@@ -84,10 +84,10 @@
[%n]))]
(and (n/= (inc sample) left)
(n/= (dec sample) middle)
- (text/= (%n sample) right))))
+ (text;= (%n sample) right))))
(_.test "Pattern-matching."
- (text/= (case (n/% 10 sample)
+ (text;= (case (n/% 10 sample)
0 "zero"
1 "one"
2 "two"
diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux
index 2d83244d6..7cdd022bb 100644
--- a/stdlib/source/test/lux/control/reader.lux
+++ b/stdlib/source/test/lux/control/reader.lux
@@ -44,11 +44,11 @@
(applyT.laws ..injection ..comparison /.apply)
(monadT.laws ..injection ..comparison /.monad)
- (let [(^open "io/.") io.monad]
+ (let [(^open "io;.") io.monad]
(_.test "Can add reader functionality to any monad."
(|> (: (/.Reader Any (IO Nat))
(do (/.with io.monad)
- [a (/.lift (io/wrap sample))
+ [a (/.lift (io;wrap sample))
b (wrap factor)]
(wrap (n/* b a))))
(/.run [])
diff --git a/stdlib/source/test/lux/control/security/integrity.lux b/stdlib/source/test/lux/control/security/integrity.lux
index 7998ba83d..c57d9fde5 100644
--- a/stdlib/source/test/lux/control/security/integrity.lux
+++ b/stdlib/source/test/lux/control/security/integrity.lux
@@ -11,7 +11,7 @@
[".T" monad]]}]
[data
["." error]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -36,7 +36,7 @@
#let [dirty (/.taint raw)]]
($_ _.and
(_.test "Can clean a dirty value by trusting it."
- (text/= raw (/.trust dirty)))
+ (text;= raw (/.trust dirty)))
(_.test "Can validate a dirty value."
(case (/.validate (function (_ value)
(if (|> value text.size (n/> 0))
@@ -44,7 +44,7 @@
(#error.Failure "Empty text is invalid.")))
dirty)
(#error.Success clean)
- (text/= raw clean)
+ (text;= raw clean)
(#error.Failure error)
false))
diff --git a/stdlib/source/test/lux/control/security/privacy.lux b/stdlib/source/test/lux/control/security/privacy.lux
index fc229d07b..e624ace99 100644
--- a/stdlib/source/test/lux/control/security/privacy.lux
+++ b/stdlib/source/test/lux/control/security/privacy.lux
@@ -12,7 +12,7 @@
[".T" apply]
[".T" monad]]}]
[data
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -53,7 +53,7 @@
(structure
(def: &equivalence
(structure (def: (= reference sample)
- (text/= (!.use %/can-reveal reference)
+ (text;= (!.use %/can-reveal reference)
(!.use %/can-reveal sample)))))
(def: hash
(|>> (!.use %/can-reveal)
diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux
index 49cbbcb15..75dd43212 100644
--- a/stdlib/source/test/lux/control/state.lux
+++ b/stdlib/source/test/lux/control/state.lux
@@ -67,10 +67,7 @@
Test
(do r.monad
[state r.nat
- value r.nat
- #let [(^open "&/.") /.functor
- (^open "&/.") /.apply
- (^open "&/.") /.monad]]
+ value r.nat]
($_ _.and
(functorT.laws ..injection (..comparison state) /.functor)
(applyT.laws ..injection (..comparison state) /.apply)
@@ -105,11 +102,11 @@
[state r.nat
left r.nat
right r.nat]
- (let [(^open "io/.") io.monad]
+ (let [(^open "io;.") io.monad]
(_.test "Can add state functionality to any monad."
(|> (: (/.State' io.IO Nat Nat)
(do (/.with io.monad)
- [a (/.lift io.monad (io/wrap left))
+ [a (/.lift io.monad (io;wrap left))
b (wrap right)]
(wrap (n/+ a b))))
(/.run' state)
diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux
index bed2d68d1..49610dafe 100644
--- a/stdlib/source/test/lux/control/writer.lux
+++ b/stdlib/source/test/lux/control/writer.lux
@@ -13,7 +13,7 @@
[".T" monad]]}]
[data
["." product]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -38,7 +38,7 @@
(<| (_.context (%name (name-of /.Writer)))
($_ _.and
(_.test "Can write any value."
- (text/= log
+ (text;= log
(product.left (/.write log))))
(functorT.laws (..injection text.monoid) ..comparison /.functor)
@@ -46,10 +46,10 @@
(monadT.laws (..injection text.monoid) ..comparison (/.monad text.monoid))
(let [lift (/.lift text.monoid io.monad)
- (^open "io/.") io.monad]
+ (^open "io;.") io.monad]
(_.test "Can add writer functionality to any monad."
(|> (io.run (do (/.with text.monoid io.monad)
- [a (lift (io/wrap left))
+ [a (lift (io;wrap left))
b (wrap right)]
(wrap (n/+ a b))))
product.right
diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux
index b3a275238..80d673574 100644
--- a/stdlib/source/test/lux/data/collection/dictionary.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary.lux
@@ -8,7 +8,7 @@
["." maybe]
[collection
["&" dictionary]
- ["." list ("#/." fold functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]]
lux/test)
@@ -100,7 +100,7 @@
(test "If you merge, and the second dict has overlapping keys, it should overwrite yours."
(let [dict' (|> dict &.entries
- (list/map (function (_ [k v]) [k (inc v)]))
+ (list;map (function (_ [k v]) [k (inc v)]))
(&.from-list number.hash))
(^open ".") (&.equivalence number.equivalence)]
(= dict' (&.merge dict' dict))))
diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
index 233afe569..2d1f5a0ba 100644
--- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
@@ -10,7 +10,7 @@
["s" set]
["dict" dictionary
["&" ordered]]
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
["r" random]]]
lux/test)
@@ -29,8 +29,8 @@
sorted-pairs (list.sort (function (_ [left _] [right _])
(n/< left right))
pairs)
- sorted-values (list/map product.right sorted-pairs)
- (^open "&/.") (&.equivalence number.nat-equivalence)]]
+ sorted-values (list;map product.right sorted-pairs)
+ (^open "&;.") (&.equivalence number.nat-equivalence)]]
($_ seq
(test "Can query the size of a dictionary."
(n/= size (&.size sample)))
@@ -60,14 +60,14 @@
(test "Converting dictionaries to/from lists cannot change their values."
(|> sample
&.entries (&.from-list number.nat-order)
- (&/= sample)))
+ (&;= sample)))
(test "Order is preserved."
- (let [(^open "list/.") (list.equivalence (: (Equivalence [Nat Nat])
+ (let [(^open "list;.") (list.equivalence (: (Equivalence [Nat Nat])
(function (_ [kr vr] [ks vs])
(and (n/= kr ks)
(n/= vr vs)))))]
- (list/= (&.entries sample)
+ (list;= (&.entries sample)
sorted-pairs)))
(test "Every key in a dictionary must be identifiable."
diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux
index 9919f3dd1..e5ec2b5b2 100644
--- a/stdlib/source/test/lux/data/collection/list.lux
+++ b/stdlib/source/test/lux/data/collection/list.lux
@@ -30,7 +30,7 @@
other-sample (r.list other-size r.nat)
separator r.nat
#let [(^open ".") (&.equivalence number.equivalence)
- (^open "&/.") &.functor]]
+ (^open "&;.") &.functor]]
($_ seq
(test "The size function should correctly portray the size of the list."
(n/= size (&.size sample)))
@@ -76,7 +76,7 @@
other-sample (r.list other-size r.nat)
separator r.nat
#let [(^open ".") (&.equivalence number.equivalence)
- (^open "&/.") &.functor]]
+ (^open "&;.") &.functor]]
($_ seq
(test "Appending the head and the tail should yield the original list."
(let [head (maybe.assume (&.head sample))
@@ -139,7 +139,7 @@
from (|> r.nat (:: @ map (n/% 10)))
to (|> r.nat (:: @ map (n/% 10)))
#let [(^open ".") (&.equivalence number.equivalence)
- (^open "&/.") &.functor]]
+ (^open "&;.") &.functor]]
($_ seq
(test "If you zip 2 lists, the result's size will be that of the smaller list."
(n/= (&.size (&.zip2 sample other-sample))
@@ -211,28 +211,28 @@
(test "Can enumerate all elements in a list."
(let [enum-sample (&.enumerate sample)]
(and (= (&.indices (&.size enum-sample))
- (&/map product.left enum-sample))
+ (&;map product.left enum-sample))
(= sample
- (&/map product.right enum-sample)))))
+ (&;map product.right enum-sample)))))
(test "Ranges can be constructed forward and backwards."
- (and (let [(^open "list/.") (&.equivalence number.equivalence)]
- (list/= (&.n/range from to)
+ (and (let [(^open "list;.") (&.equivalence number.equivalence)]
+ (list;= (&.n/range from to)
(&.reverse (&.n/range to from))))
- (let [(^open "list/.") (&.equivalence number.equivalence)
+ (let [(^open "list;.") (&.equivalence number.equivalence)
from (.int from)
to (.int to)]
- (list/= (&.i/range from to)
+ (list;= (&.i/range from to)
(&.reverse (&.i/range to from))))))
))))
## TODO: Add again once new-luxc becomes the standard compiler.
(context: "Monad transformer"
(let [lift (&.lift io.monad)
- (^open "io/.") io.monad]
+ (^open "io;.") io.monad]
(test "Can add list functionality to any monad."
(|> (io.run (do (&.ListT io.monad)
- [a (lift (io/wrap +123))
+ [a (lift (io;wrap +123))
b (wrap +456)]
(wrap (i/+ a b))))
(case> (^ (list +579)) #1
diff --git a/stdlib/source/test/lux/data/collection/queue.lux b/stdlib/source/test/lux/data/collection/queue.lux
index 4f4f12ef0..f84246a7f 100644
--- a/stdlib/source/test/lux/data/collection/queue.lux
+++ b/stdlib/source/test/lux/data/collection/queue.lux
@@ -30,10 +30,10 @@
(n/= size (&.size (&.pop (&.push non-member sample))))))
(test "Transforming to/from list can't change the queue."
- (let [(^open "&/.") (&.equivalence number.equivalence)]
+ (let [(^open "&;.") (&.equivalence number.equivalence)]
(|> sample
&.to-list &.from-list
- (&/= sample))))
+ (&;= sample))))
(test "I can always peek at a non-empty queue."
(case (&.peek sample)
diff --git a/stdlib/source/test/lux/data/collection/row.lux b/stdlib/source/test/lux/data/collection/row.lux
index dd70b7272..f4c7ad3a0 100644
--- a/stdlib/source/test/lux/data/collection/row.lux
+++ b/stdlib/source/test/lux/data/collection/row.lux
@@ -7,7 +7,7 @@
["." maybe]
[collection
["&" row]
- ["." list ("#/." fold)]]]
+ ["." list ("#;." fold)]]]
[math
["r" random]]]
lux/test)
@@ -20,11 +20,11 @@
sample (r.row size r.nat)
other-sample (r.row size r.nat)
non-member (|> r.nat (r.filter (|>> (&.member? number.equivalence sample) not)))
- #let [(^open "&/.") (&.equivalence number.equivalence)
- (^open "&/.") &.apply
- (^open "&/.") &.monad
- (^open "&/.") &.fold
- (^open "&/.") &.monoid]]
+ #let [(^open "&;.") (&.equivalence number.equivalence)
+ (^open "&;.") &.apply
+ (^open "&;.") &.monad
+ (^open "&;.") &.fold
+ (^open "&;.") &.monoid]]
($_ seq
(test "Can query size of row."
(if (&.empty? sample)
@@ -50,33 +50,33 @@
(n/= (inc non-member))))
(test "Can safely transform to/from lists."
- (|> sample &.to-list &.from-list (&/= sample)))
+ (|> sample &.to-list &.from-list (&;= sample)))
(test "Can identify members of a row."
(and (not (&.member? number.equivalence sample non-member))
(&.member? number.equivalence (&.add non-member sample) non-member)))
(test "Can fold over elements of row."
- (n/= (list/fold n/+ 0 (&.to-list sample))
- (&/fold n/+ 0 sample)))
+ (n/= (list;fold n/+ 0 (&.to-list sample))
+ (&;fold n/+ 0 sample)))
(test "Functor goes over every element."
- (let [there (&/map inc sample)
- back-again (&/map dec there)]
- (and (not (&/= sample there))
- (&/= sample back-again))))
+ (let [there (&;map inc sample)
+ back-again (&;map dec there)]
+ (and (not (&;= sample there))
+ (&;= sample back-again))))
(test "Apply allows you to create singleton rows, and apply rows of functions to rows of values."
- (and (&/= (&.row non-member) (&/wrap non-member))
- (&/= (&/map inc sample) (&/apply (&/wrap inc) sample))))
+ (and (&;= (&.row non-member) (&;wrap non-member))
+ (&;= (&;map inc sample) (&;apply (&;wrap inc) sample))))
(test "Row concatenation is a monad."
- (&/= (&/compose sample other-sample)
- (&/join (&.row sample other-sample))))
+ (&;= (&;compose sample other-sample)
+ (&;join (&.row sample other-sample))))
(test "Can reverse."
- (and (not (&/= sample
+ (and (not (&;= sample
(&.reverse sample)))
- (not (&/= sample
+ (not (&;= sample
(&.reverse (&.reverse sample))))))
))))
diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux
index 6e806e629..90971d2e9 100644
--- a/stdlib/source/test/lux/data/collection/sequence.lux
+++ b/stdlib/source/test/lux/data/collection/sequence.lux
@@ -6,8 +6,8 @@
[data
["." maybe]
[number
- ["." nat ("#/." codec)]]
- ["." text ("#/." monoid)]
+ ["." nat ("#;." codec)]]
+ ["." text ("#;." monoid)]
[collection
["." list]
["&" sequence]]]
@@ -24,29 +24,29 @@
elem r.nat
cycle-seed (r.list size r.nat)
cycle-sample-idx (|> r.nat (:: @ map (n/% 1000)))
- #let [(^open "List/.") (list.equivalence number.equivalence)
+ #let [(^open "List;.") (list.equivalence number.equivalence)
sample0 (&.iterate inc 0)
sample1 (&.iterate inc offset)]]
($_ seq
(test "Can move along a sequence and take slices off it."
- (and (and (List/= (list.n/range 0 (dec size))
+ (and (and (List;= (list.n/range 0 (dec size))
(&.take size sample0))
- (List/= (list.n/range offset (dec (n/+ offset size)))
+ (List;= (list.n/range offset (dec (n/+ offset size)))
(&.take size (&.drop offset sample0)))
(let [[drops takes] (&.split size sample0)]
- (and (List/= (list.n/range 0 (dec size))
+ (and (List;= (list.n/range 0 (dec size))
drops)
- (List/= (list.n/range size (dec (n/* 2 size)))
+ (List;= (list.n/range size (dec (n/* 2 size)))
(&.take size takes)))))
- (and (List/= (list.n/range 0 (dec size))
+ (and (List;= (list.n/range 0 (dec size))
(&.take-while (n/< size) sample0))
- (List/= (list.n/range offset (dec (n/+ offset size)))
+ (List;= (list.n/range offset (dec (n/+ offset size)))
(&.take-while (n/< (n/+ offset size))
(&.drop-while (n/< offset) sample0)))
(let [[drops takes] (&.split-while (n/< size) sample0)]
- (and (List/= (list.n/range 0 (dec size))
+ (and (List;= (list.n/range 0 (dec size))
drops)
- (List/= (list.n/range size (dec (n/* 2 size)))
+ (List;= (list.n/range size (dec (n/* 2 size)))
(&.take-while (n/< (n/* 2 size)) takes)))))
))
@@ -55,7 +55,7 @@
(test "Can obtain the head & tail of a sequence."
(and (n/= offset (&.head sample1))
- (List/= (list.n/range (inc offset) (n/+ offset size))
+ (List;= (list.n/range (inc offset) (n/+ offset size))
(&.take size (&.tail sample1)))))
(test "Can filter sequences."
@@ -69,29 +69,29 @@
(&.nth offset odds))))))
(test "Functor goes over 'all' elements in a sequence."
- (let [(^open "&/.") &.functor
- there (&/map (n/* factor) sample0)
- back-again (&/map (n// factor) there)]
- (and (not (List/= (&.take size sample0)
+ (let [(^open "&;.") &.functor
+ there (&;map (n/* factor) sample0)
+ back-again (&;map (n// factor) there)]
+ (and (not (List;= (&.take size sample0)
(&.take size there)))
- (List/= (&.take size sample0)
+ (List;= (&.take size sample0)
(&.take size back-again)))))
(test "CoMonad produces a value for every element in a sequence."
- (let [(^open "&/.") &.functor]
- (List/= (&.take size (&/map (n/* factor) sample1))
+ (let [(^open "&;.") &.functor]
+ (List;= (&.take size (&;map (n/* factor) sample1))
(&.take size
(be &.comonad
[inputs sample1]
(n/* factor (&.head inputs)))))))
(test "'unfold' generalizes 'iterate'."
- (let [(^open "&/.") &.functor
- (^open "List/.") (list.equivalence text.equivalence)]
- (List/= (&.take size
- (&/map nat/encode (&.iterate inc offset)))
+ (let [(^open "&;.") &.functor
+ (^open "List;.") (list.equivalence text.equivalence)]
+ (List;= (&.take size
+ (&;map nat;encode (&.iterate inc offset)))
(&.take size
- (&.unfold (function (_ n) [(inc n) (nat/encode n)])
+ (&.unfold (function (_ n) [(inc n) (nat;encode n)])
offset)))))
(test "Can cycle over the same elements as an infinite sequence."
diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux
index bbdc945f7..b383f32c2 100644
--- a/stdlib/source/test/lux/data/collection/set.lux
+++ b/stdlib/source/test/lux/data/collection/set.lux
@@ -25,7 +25,7 @@
setR (r.set number.hash sizeR gen-nat)
non-member (|> gen-nat
(r.filter (|>> (&.member? setL) not)))
- #let [(^open "&/.") &.equivalence]]
+ #let [(^open "&;.") &.equivalence]]
($_ seq
(test "I can query the size of a set."
(and (n/= sizeL (&.size setL))
@@ -34,7 +34,7 @@
(test "Converting sets to/from lists can't change their values."
(|> setL
&.to-list (&.from-list number.hash)
- (&/= setL)))
+ (&;= setL)))
(test "Every set is a sub-set of the union of itself with another."
(let [setLR (&.union setL setR)]
@@ -47,13 +47,13 @@
(&.super? setLR setR))))
(test "Union with the empty set leaves a set unchanged."
- (&/= setL
+ (&;= setL
(&.union (&.new number.hash)
setL)))
(test "Intersection with the empty set results in the empty set."
(let [empty-set (&.new number.hash)]
- (&/= empty-set
+ (&;= empty-set
(&.intersection empty-set setL))))
(test "After substracting a set A from another B, no member of A can be a member of B."
diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux
index 384a0506b..78d096cef 100644
--- a/stdlib/source/test/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/set/ordered.lux
@@ -26,7 +26,7 @@
sizeR gen-nat
listL (|> (r.set number.hash sizeL gen-nat) (:: @ map set.to-list))
listR (|> (r.set number.hash sizeR gen-nat) (:: @ map set.to-list))
- #let [(^open "&/.") &.equivalence
+ #let [(^open "&;.") &.equivalence
setL (&.from-list number.order listL)
setR (&.from-list number.order listR)
sortedL (list.sort n/< listL)
@@ -61,7 +61,7 @@
(test "Converting sets to/from lists can't change their values."
(|> setL
&.to-list (&.from-list number.order)
- (&/= setL)))
+ (&;= setL)))
(test "Order is preserved."
(let [listL (&.to-list setL)
@@ -80,13 +80,13 @@
(&.super? setLR setR))))
(test "Union with the empty set leaves a set unchanged."
- (&/= setL
+ (&;= setL
(&.union (&.new number.order)
setL)))
(test "Intersection with the empty set results in the empty set."
(let [empty-set (&.new number.order)]
- (&/= empty-set
+ (&;= empty-set
(&.intersection empty-set setL))))
(test "After substracting a set A from another B, no member of A can be a member of B."
diff --git a/stdlib/source/test/lux/data/collection/tree/rose.lux b/stdlib/source/test/lux/data/collection/tree/rose.lux
index 388065ef0..f4ddee14e 100644
--- a/stdlib/source/test/lux/data/collection/tree/rose.lux
+++ b/stdlib/source/test/lux/data/collection/tree/rose.lux
@@ -5,10 +5,10 @@
[data
["." product]
["." number]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]
[collection
- ["." list ("#/." functor fold)]
+ ["." list ("#;." functor fold)]
[tree
["&" rose]]]]
[math
@@ -24,8 +24,8 @@
[value r.nat
num-children (|> r.nat (:: @ map (n/% 3)))
children' (r.list num-children gen-tree)
- #let [size' (list/fold n/+ 0 (list/map product.left children'))
- children (list/map product.right children')]]
+ #let [size' (list;fold n/+ 0 (list;map product.left children'))
+ children (list;map product.right children')]]
(wrap [(inc size')
(&.branch value children)]))
))))
@@ -34,18 +34,18 @@
(<| (times 100)
(do @
[[size sample] gen-tree
- #let [(^open "&/.") (&.equivalence number.equivalence)
- (^open "&/.") &.fold
+ #let [(^open "&;.") (&.equivalence number.equivalence)
+ (^open "&;.") &.fold
concat (function (_ addition partial) (format partial (%n addition)))]]
($_ seq
(test "Can compare trees for equivalence."
- (&/= sample sample))
+ (&;= sample sample))
(test "Can flatten a tree to get all the nodes as a flat tree."
(n/= size
(list.size (&.flatten sample))))
(test "Can fold trees."
- (text/= (&/fold concat "" sample)
- (list/fold concat "" (&.flatten sample))))
+ (text;= (&;fold concat "" sample)
+ (list;fold concat "" (&.flatten sample))))
))))
diff --git a/stdlib/source/test/lux/data/collection/tree/rose/zipper.lux b/stdlib/source/test/lux/data/collection/tree/rose/zipper.lux
index 3abf1dd26..769e11293 100644
--- a/stdlib/source/test/lux/data/collection/tree/rose/zipper.lux
+++ b/stdlib/source/test/lux/data/collection/tree/rose/zipper.lux
@@ -41,7 +41,7 @@
pre-val r.nat
post-val r.nat
#let [(^open "tree/.") (rose.equivalence number.equivalence)
- (^open "list/.") (list.equivalence number.equivalence)]]
+ (^open "list;.") (list.equivalence number.equivalence)]]
($_ seq
(test "Trees can be converted to/from zippers."
(|> sample
@@ -102,7 +102,7 @@
(|> sample &.zip (&.set new-val) &.value (n/= new-val)))
(test "Zipper traversal follows the outline of the tree depth-first."
- (list/= (rose.flatten sample)
+ (list;= (rose.flatten sample)
(loop [zipper (&.zip sample)]
(if (&.end? zipper)
(list (&.value zipper))
@@ -110,7 +110,7 @@
(recur (&.next zipper)))))))
(test "Backwards zipper traversal yield reverse tree flatten."
- (list/= (list.reverse (rose.flatten sample))
+ (list;= (list.reverse (rose.flatten sample))
(loop [zipper (to-end (&.zip sample))]
(if (&.root? zipper)
(list (&.value zipper))
diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux
index 24ed8f615..5546a9d90 100644
--- a/stdlib/source/test/lux/data/color.lux
+++ b/stdlib/source/test/lux/data/color.lux
@@ -5,7 +5,7 @@
[data
["@" color]
[number
- ["." frac ("#/." number)]]]
+ ["." frac ("#;." number)]]]
["." math
["r" random]]]
lux/test)
@@ -95,6 +95,6 @@
(saturation gray'ed))
(|> (luminance gray'ed)
(f/- (luminance mediocre))
- frac/abs
+ frac;abs
(f/<= error-margin)))))
))))
diff --git a/stdlib/source/test/lux/data/error.lux b/stdlib/source/test/lux/data/error.lux
index 7f491dc2c..78e63338e 100644
--- a/stdlib/source/test/lux/data/error.lux
+++ b/stdlib/source/test/lux/data/error.lux
@@ -9,25 +9,25 @@
lux/test)
(context: "Errors"
- (let [(^open "//.") /.apply
- (^open "//.") /.monad]
+ (let [(^open "&;.") /.apply
+ (^open "&;.") /.monad]
($_ seq
(test "Functor correctly handles both cases."
(and (|> (: (Error Int) (#/.Success +10))
- (//map inc)
+ (&;map inc)
(case> (#/.Success +11) #1 _ #0))
(|> (: (Error Int) (#/.Failure "YOLO"))
- (//map inc)
+ (&;map inc)
(case> (#/.Failure "YOLO") #1 _ #0))
))
(test "Apply correctly handles both cases."
- (and (|> (//wrap +20)
+ (and (|> (&;wrap +20)
(case> (#/.Success +20) #1 _ #0))
- (|> (//apply (//wrap inc) (//wrap +10))
+ (|> (&;apply (&;wrap inc) (&;wrap +10))
(case> (#/.Success +11) #1 _ #0))
- (|> (//apply (//wrap inc) (#/.Failure "YOLO"))
+ (|> (&;apply (&;wrap inc) (#/.Failure "YOLO"))
(case> (#/.Failure "YOLO") #1 _ #0))))
(test "Monad correctly handles both cases."
@@ -48,10 +48,10 @@
(context: "Monad transformer"
(let [lift (/.lift io.monad)
- (^open "io/.") io.monad]
+ (^open "io;.") io.monad]
(test "Can add error functionality to any monad."
(|> (io.run (do (/.ErrorT io.monad)
- [a (lift (io/wrap +123))
+ [a (lift (io;wrap +123))
b (wrap +456)]
(wrap (i/+ a b))))
(case> (#/.Success +579)
diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux
index 05784915f..35e7dc4a1 100644
--- a/stdlib/source/test/lux/data/format/xml.lux
+++ b/stdlib/source/test/lux/data/format/xml.lux
@@ -8,15 +8,15 @@
["." name]
["E" error]
["." maybe]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]
[format
["&" xml]]
[collection
["dict" dictionary]
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[math
- ["r" random ("#/." monad)]]]
+ ["r" random ("#;." monad)]]]
lux/test)
(def: char-range
@@ -34,7 +34,7 @@
(def: (size^ bottom top)
(-> Nat Nat (r.Random Nat))
(let [constraint (|>> (n/% top) (n/max bottom))]
- (r/map constraint r.nat)))
+ (r;map constraint r.nat)))
(def: (xml-text^ bottom top)
(-> Nat Nat (r.Random Text))
@@ -62,16 +62,16 @@
(<| (times 100)
(do @
[sample gen-xml
- #let [(^open "&/.") &.equivalence
- (^open "&/.") &.codec]]
+ #let [(^open "&;.") &.equivalence
+ (^open "&;.") &.codec]]
($_ seq
(test "Every XML is equal to itself."
- (&/= sample sample))
+ (&;= sample sample))
(test "Can encode/decode XML."
- (|> sample &/encode &/decode
+ (|> sample &;encode &;decode
(case> (#.Right result)
- (&/= sample result)
+ (&;= sample result)
(#.Left error)
#0)))
@@ -88,21 +88,21 @@
value (xml-text^ 1 10)
#let [node (#&.Node tag
(dict.put attr value &.attrs)
- (list/map (|>> #&.Text) children))]]
+ (list;map (|>> #&.Text) children))]]
($_ seq
(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 (|> (&.attr attr)
(p.before &.ignore)
(&.run 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 22511e7b3..293f5d075 100644
--- a/stdlib/source/test/lux/data/identity.lux
+++ b/stdlib/source/test/lux/data/identity.lux
@@ -5,32 +5,32 @@
comonad]
[data
["&" identity]
- ["." text ("#/." monoid equivalence)]]]
+ ["." text ("#;." monoid equivalence)]]]
lux/test)
(context: "Identity"
- (let [(^open "&/.") &.apply
- (^open "&/.") &.monad
- (^open "&/.") &.comonad]
+ (let [(^open "&;.") &.apply
+ (^open "&;.") &.monad
+ (^open "&;.") &.comonad]
($_ seq
(test "Functor does not affect values."
- (text/= "yololol" (&/map (text/compose "yolo") "lol")))
+ (text;= "yololol" (&;map (text;compose "yolo") "lol")))
(test "Apply does not affect values."
- (and (text/= "yolo" (&/wrap "yolo"))
- (text/= "yololol" (&/apply (&/wrap (text/compose "yolo")) (&/wrap "lol")))))
+ (and (text;= "yolo" (&;wrap "yolo"))
+ (text;= "yololol" (&;apply (&;wrap (text;compose "yolo")) (&;wrap "lol")))))
(test "Monad does not affect values."
- (text/= "yololol" (do &.monad
- [f (wrap text/compose)
+ (text;= "yololol" (do &.monad
+ [f (wrap text;compose)
a (wrap "yolo")
b (wrap "lol")]
(wrap (f a b)))))
(test "CoMonad does not affect values."
- (and (text/= "yololol" (&/unwrap "yololol"))
- (text/= "yololol" (be &.comonad
- [f text/compose
+ (and (text;= "yololol" (&;unwrap "yololol"))
+ (text;= "yololol" (be &.comonad
+ [f text;compose
a "yolo"
b "lol"]
(f a b)))))
diff --git a/stdlib/source/test/lux/data/lazy.lux b/stdlib/source/test/lux/data/lazy.lux
index f00b572ab..5fe6464ff 100644
--- a/stdlib/source/test/lux/data/lazy.lux
+++ b/stdlib/source/test/lux/data/lazy.lux
@@ -46,9 +46,9 @@
(n/= (inc sample))))
(test "Apply apply."
- (let [(^open "&/.") &.monad
- (^open "&/.") &.apply]
- (|> (&/apply (&/wrap inc) (&/wrap sample))
+ (let [(^open "&;.") &.monad
+ (^open "&;.") &.apply]
+ (|> (&;apply (&;wrap inc) (&;wrap sample))
&.thaw
(n/= (inc sample)))))
))))
diff --git a/stdlib/source/test/lux/data/maybe.lux b/stdlib/source/test/lux/data/maybe.lux
index a6ec17131..f42be25bf 100644
--- a/stdlib/source/test/lux/data/maybe.lux
+++ b/stdlib/source/test/lux/data/maybe.lux
@@ -4,42 +4,42 @@
["M" monad (#+ Monad do)]
pipe]
[data
- ["&" maybe ("#/." monoid)]
- ["." text ("#/." monoid)]]
- ["." io ("#/." monad)]]
+ ["&" maybe ("#;." monoid)]
+ ["." text ("#;." monoid)]]
+ ["." io ("#;." monad)]]
lux/test)
(context: "Maybe"
- (let [(^open "&/.") &.apply
- (^open "&/.") &.monad
- (^open "&/.") (&.equivalence text.equivalence)]
+ (let [(^open "&;.") &.apply
+ (^open "&;.") &.monad
+ (^open "&;.") (&.equivalence text.equivalence)]
($_ seq
(test "Can compare Maybe values."
- (and (&/= #.None #.None)
- (&/= (#.Some "yolo") (#.Some "yolo"))
- (not (&/= (#.Some "yolo") (#.Some "lol")))
- (not (&/= (#.Some "yolo") #.None))))
+ (and (&;= #.None #.None)
+ (&;= (#.Some "yolo") (#.Some "yolo"))
+ (not (&;= (#.Some "yolo") (#.Some "lol")))
+ (not (&;= (#.Some "yolo") #.None))))
(test "Monoid respects Maybe."
- (and (&/= #.None &/identity)
- (&/= (#.Some "yolo") (&/compose (#.Some "yolo") (#.Some "lol")))
- (&/= (#.Some "yolo") (&/compose (#.Some "yolo") #.None))
- (&/= (#.Some "lol") (&/compose #.None (#.Some "lol")))
- (&/= #.None (: (Maybe Text) (&/compose #.None #.None)))))
+ (and (&;= #.None &;identity)
+ (&;= (#.Some "yolo") (&;compose (#.Some "yolo") (#.Some "lol")))
+ (&;= (#.Some "yolo") (&;compose (#.Some "yolo") #.None))
+ (&;= (#.Some "lol") (&;compose #.None (#.Some "lol")))
+ (&;= #.None (: (Maybe Text) (&;compose #.None #.None)))))
(test "Functor respects Maybe."
- (and (&/= #.None (&/map (text/compose "yolo") #.None))
- (&/= (#.Some "yololol") (&/map (text/compose "yolo") (#.Some "lol")))))
+ (and (&;= #.None (&;map (text;compose "yolo") #.None))
+ (&;= (#.Some "yololol") (&;map (text;compose "yolo") (#.Some "lol")))))
(test "Apply respects Maybe."
- (and (&/= (#.Some "yolo") (&/wrap "yolo"))
- (&/= (#.Some "yololol")
- (&/apply (&/wrap (text/compose "yolo")) (&/wrap "lol")))))
+ (and (&;= (#.Some "yolo") (&;wrap "yolo"))
+ (&;= (#.Some "yololol")
+ (&;apply (&;wrap (text;compose "yolo")) (&;wrap "lol")))))
(test "Monad respects Maybe."
- (&/= (#.Some "yololol")
+ (&;= (#.Some "yololol")
(do &.monad
- [f (wrap text/compose)
+ [f (wrap text;compose)
a (wrap "yolo")
b (wrap "lol")]
(wrap (f a b)))))
@@ -59,7 +59,7 @@
(let [lift (&.lift io.monad)]
(test "Can add maybe functionality to any monad."
(|> (io.run (do (&.MaybeT io.monad)
- [a (lift (io/wrap +123))
+ [a (lift (io;wrap +123))
b (wrap +456)]
(wrap (i/+ a b))))
(case> (#.Some +579)
diff --git a/stdlib/source/test/lux/data/name.lux b/stdlib/source/test/lux/data/name.lux
index 57d4d9a1e..32744ad5f 100644
--- a/stdlib/source/test/lux/data/name.lux
+++ b/stdlib/source/test/lux/data/name.lux
@@ -5,7 +5,7 @@
pipe]
[data
["&" name]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -30,44 +30,44 @@
module2 (gen-part sizeM2)
short2 (gen-part sizeN2)
#let [name2 [module2 short2]]
- #let [(^open "&/.") &.equivalence
- (^open "&/.") &.codec]]
+ #let [(^open "&;.") &.equivalence
+ (^open "&;.") &.codec]]
($_ seq
(test "Can get the module & short parts of an name."
(and (is? module1 (&.module name1))
(is? short1 (&.short name1))))
(test "Can compare names for equivalence."
- (and (&/= name1 name1)
- (if (&/= name1 name2)
- (and (text/= module1 module2)
- (text/= short1 short2))
- (or (not (text/= module1 module2))
- (not (text/= short1 short2))))))
+ (and (&;= name1 name1)
+ (if (&;= name1 name2)
+ (and (text;= module1 module2)
+ (text;= short1 short2))
+ (or (not (text;= module1 module2))
+ (not (text;= short1 short2))))))
(test "Can encode names as text."
(|> name1
- &/encode &/decode
- (case> (#.Right dec-name) (&/= name1 dec-name)
+ &;encode &;decode
+ (case> (#.Right dec-name) (&;= name1 dec-name)
_ #0)))
(test "Encoding an name without a module component results in text equal to the short of the name."
(if (text.empty? module1)
- (text/= short1 (&/encode name1))
+ (text;= short1 (&;encode name1))
#1))
))))
(context: "Name-related macros."
- (let [(^open "&/.") &.equivalence]
+ (let [(^open "&;.") &.equivalence]
($_ seq
(test "Can obtain Name from identifier."
- (and (&/= ["lux" "yolo"] (name-of .yolo))
- (&/= ["test/lux/data/name" "yolo"] (name-of ..yolo))
- (&/= ["" "yolo"] (name-of yolo))
- (&/= ["lux/test" "yolo"] (name-of lux/test.yolo))))
+ (and (&;= ["lux" "yolo"] (name-of .yolo))
+ (&;= ["test/lux/data/name" "yolo"] (name-of ..yolo))
+ (&;= ["" "yolo"] (name-of yolo))
+ (&;= ["lux/test" "yolo"] (name-of lux/test.yolo))))
(test "Can obtain Name from tag."
- (and (&/= ["lux" "yolo"] (name-of #.yolo))
- (&/= ["test/lux/data/name" "yolo"] (name-of #..yolo))
- (&/= ["" "yolo"] (name-of #yolo))
- (&/= ["lux/test" "yolo"] (name-of #lux/test.yolo)))))))
+ (and (&;= ["lux" "yolo"] (name-of #.yolo))
+ (&;= ["test/lux/data/name" "yolo"] (name-of #..yolo))
+ (&;= ["" "yolo"] (name-of #yolo))
+ (&;= ["lux/test" "yolo"] (name-of #lux/test.yolo)))))))
diff --git a/stdlib/source/test/lux/data/number.lux b/stdlib/source/test/lux/data/number.lux
index 9460b149b..7b57ffc63 100644
--- a/stdlib/source/test/lux/data/number.lux
+++ b/stdlib/source/test/lux/data/number.lux
@@ -5,7 +5,7 @@
pipe]
[data
number
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]]
@@ -37,11 +37,11 @@
(^open ".") <Order>]]
(test "" (and (>= x (abs x))
## abs(0.0) == 0.0 && negate(abs(0.0)) == -0.0
- (or (text/= "Frac" category)
+ (or (text;= "Frac" category)
(not (= x (negate x))))
(= x (negate (negate x)))
## There is loss of precision when multiplying
- (or (text/= "Rev" category)
+ (or (text;= "Rev" category)
(= x (* (signum x)
(abs x)))))))))]
diff --git a/stdlib/source/test/lux/data/number/complex.lux b/stdlib/source/test/lux/data/number/complex.lux
index a622ef6b3..106edf33d 100644
--- a/stdlib/source/test/lux/data/number/complex.lux
+++ b/stdlib/source/test/lux/data/number/complex.lux
@@ -5,10 +5,10 @@
pipe]
[data
["." number
- ["." frac ("#/." number)]
+ ["." frac ("#;." number)]
["&" complex]]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
["." math
["r" random]]]
lux/test)
@@ -17,9 +17,9 @@
(def: (within? margin standard value)
(-> Frac &.Complex &.Complex Bit)
- (let [real-dist (frac/abs (f/- (get@ #&.real standard)
+ (let [real-dist (frac;abs (f/- (get@ #&.real standard)
(get@ #&.real value)))
- imgn-dist (frac/abs (f/- (get@ #&.imaginary standard)
+ imgn-dist (frac;abs (f/- (get@ #&.imaginary standard)
(get@ #&.imaginary value)))]
(and (f/< margin real-dist)
(f/< margin imgn-dist))))
@@ -64,8 +64,8 @@
(test "Absolute value of complex >= absolute value of any of the parts."
(let [r+i (&.complex real imaginary)
abs (get@ #&.real (&.abs r+i))]
- (and (f/>= (frac/abs real) abs)
- (f/>= (frac/abs imaginary) abs))))
+ (and (f/>= (frac;abs real) abs)
+ (f/>= (frac;abs imaginary) abs))))
(test "The absolute value of a complex number involving a NaN on either dimension, results in a NaN value."
(and (number.not-a-number? (get@ #&.real (&.abs (&.complex number.not-a-number imaginary))))
@@ -131,7 +131,7 @@
(let [cx (&.conjugate x)]
(and (f/= (get@ #&.real x)
(get@ #&.real cx))
- (f/= (frac/negate (get@ #&.imaginary x))
+ (f/= (frac;negate (get@ #&.imaginary x))
(get@ #&.imaginary cx)))))
(test "The reciprocal functions is its own inverse."
@@ -198,5 +198,5 @@
(test "Can calculate the N roots for any complex number."
(|> sample
(&.roots degree)
- (list/map (&.pow' (|> degree .int int-to-frac)))
+ (list;map (&.pow' (|> degree .int int-to-frac)))
(list.every? (within? margin-of-error sample)))))))
diff --git a/stdlib/source/test/lux/data/number/ratio.lux b/stdlib/source/test/lux/data/number/ratio.lux
index 63d1e5fc8..a68e5abca 100644
--- a/stdlib/source/test/lux/data/number/ratio.lux
+++ b/stdlib/source/test/lux/data/number/ratio.lux
@@ -5,7 +5,7 @@
pipe]
[data
[number
- ["&" ratio ("&/." number)]]]
+ ["&" ratio ("&;." number)]]]
[math
["r" random]]]
lux/test)
@@ -77,16 +77,16 @@
[sample gen-ratio]
($_ seq
(test "Negation is it's own inverse."
- (let [there (&/negate sample)
- back-again (&/negate there)]
+ (let [there (&;negate sample)
+ back-again (&;negate there)]
(and (not (&.= there sample))
(&.= back-again sample))))
(test "All ratios are already at their absolute value."
- (|> sample &/abs (&.= sample)))
+ (|> sample &;abs (&.= sample)))
(test "Signum is the identity."
- (|> sample (&.* (&/signum sample)) (&.= sample)))
+ (|> sample (&.* (&;signum sample)) (&.= sample)))
))))
(context: "Order"
@@ -106,9 +106,9 @@
(<| (times 100)
(do @
[sample gen-ratio
- #let [(^open "&/.") &.codec]]
+ #let [(^open "&;.") &.codec]]
(test "Can encode/decode ratios."
- (|> sample &/encode &/decode
+ (|> sample &;encode &;decode
(case> (#.Right output)
(&.= sample output)
diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux
index 01cd2220d..ea9a36fe2 100644
--- a/stdlib/source/test/lux/data/text.lux
+++ b/stdlib/source/test/lux/data/text.lux
@@ -114,30 +114,30 @@
parts (r.list sizeL part-gen)
#let [sample1 (&.concat (list.interpose sep1 parts))
sample2 (&.concat (list.interpose sep2 parts))
- (^open "&/.") &.equivalence]]
+ (^open "&;.") &.equivalence]]
($_ seq
(test "Can split text through a separator."
(n/= (list.size parts)
(list.size (&.split-all-with sep1 sample1))))
(test "Can replace occurrences of a piece of text inside a larger text."
- (&/= sample2
+ (&;= sample2
(&.replace-all sep1 sep2 sample1)))
))))
(context: "Structures"
- (let [(^open "&/.") &.order]
+ (let [(^open "&;.") &.order]
($_ seq
- (test "" (&/< "bcd" "abc"))
- (test "" (not (&/< "abc" "abc")))
- (test "" (not (&/< "abc" "bcd")))
- (test "" (&/<= "bcd" "abc"))
- (test "" (&/<= "abc" "abc"))
- (test "" (not (&/<= "abc" "bcd")))
- (test "" (&/> "abc" "bcd"))
- (test "" (not (&/> "abc" "abc")))
- (test "" (not (&/> "bcd" "abc")))
- (test "" (&/>= "abc" "bcd"))
- (test "" (&/>= "abc" "abc"))
- (test "" (not (&/>= "bcd" "abc")))
+ (test "" (&;< "bcd" "abc"))
+ (test "" (not (&;< "abc" "abc")))
+ (test "" (not (&;< "abc" "bcd")))
+ (test "" (&;<= "bcd" "abc"))
+ (test "" (&;<= "abc" "abc"))
+ (test "" (not (&;<= "abc" "bcd")))
+ (test "" (&;> "abc" "bcd"))
+ (test "" (not (&;> "abc" "abc")))
+ (test "" (not (&;> "bcd" "abc")))
+ (test "" (&;>= "abc" "bcd"))
+ (test "" (&;>= "abc" "abc"))
+ (test "" (not (&;>= "bcd" "abc")))
)))
diff --git a/stdlib/source/test/lux/data/text/format.lux b/stdlib/source/test/lux/data/text/format.lux
index d3bbafe7e..1a7ab01cf 100644
--- a/stdlib/source/test/lux/data/text/format.lux
+++ b/stdlib/source/test/lux/data/text/format.lux
@@ -8,14 +8,14 @@
lux/test)
(context: "Formatters"
- (let [(^open "&/.") text.equivalence]
+ (let [(^open "&;.") text.equivalence]
($_ seq
(test "Can format common values simply."
- (and (&/= "#1" (%b #1))
- (&/= "123" (%n 123))
- (&/= "+123" (%i +123))
- (&/= "+123.456" (%f +123.456))
- (&/= ".5" (%r .5))
- (&/= (format text.double-quote "YOLO" text.double-quote) (%t "YOLO"))
- (&/= "User-id: +123 -- Active: #1" (format "User-id: " (%i +123) " -- Active: " (%b #1)))))
+ (and (&;= "#1" (%b #1))
+ (&;= "123" (%n 123))
+ (&;= "+123" (%i +123))
+ (&;= "+123.456" (%f +123.456))
+ (&;= ".5" (%r .5))
+ (&;= (format text.double-quote "YOLO" text.double-quote) (%t "YOLO"))
+ (&;= "User-id: +123 -- Active: #1" (format "User-id: " (%i +123) " -- Active: " (%b #1)))))
)))
diff --git a/stdlib/source/test/lux/data/text/lexer.lux b/stdlib/source/test/lux/data/text/lexer.lux
index dc8cf75c9..77419362a 100644
--- a/stdlib/source/test/lux/data/text/lexer.lux
+++ b/stdlib/source/test/lux/data/text/lexer.lux
@@ -6,7 +6,7 @@
["p" parser]]
[data
["." error (#+ Error)]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format
["&" lexer]]
[collection
@@ -26,17 +26,17 @@
(-> Text (Error Text) Bit)
(case input
(#.Right output)
- (text/= test output)
+ (text;= test output)
_
#0))
(def: (should-passL test input)
(-> (List Text) (Error (List Text)) Bit)
- (let [(^open "list/.") (list.equivalence text.equivalence)]
+ (let [(^open "list;.") (list.equivalence text.equivalence)]
(case input
(#.Right output)
- (list/= test output)
+ (list;= test output)
_
#0)))
@@ -47,10 +47,10 @@
(#.Right output)
(case [test output]
[(#.Left test) (#.Left output)]
- (text/= test output)
+ (text;= test output)
[(#.Right test) (#.Right output)]
- (text/= test output)
+ (text;= test output)
_
#0)
@@ -78,7 +78,7 @@
[size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10))))
sample (r.unicode size)
non-sample (|> (r.unicode size)
- (r.filter (|>> (text/= sample) not)))]
+ (r.filter (|>> (text;= sample) not)))]
($_ seq
(test "Can find literal text fragments."
(and (|> (&.run sample
diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux
index cbb44f332..ffa5612da 100644
--- a/stdlib/source/test/lux/data/text/regex.lux
+++ b/stdlib/source/test/lux/data/text/regex.lux
@@ -6,7 +6,7 @@
["p" parser]]
[data
[number (#+ hex)]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format
["." lexer (#+ Lexer)]
["&" regex]]]
@@ -21,7 +21,7 @@
(-> (Lexer Text) Text Bit)
(|> (lexer.run input regex)
(case> (#.Right parsed)
- (text/= parsed input)
+ (text;= parsed input)
_
#0)))
@@ -30,7 +30,7 @@
(-> Text (Lexer Text) Text Bit)
(|> (lexer.run input regex)
(case> (#.Right parsed)
- (text/= test parsed)
+ (text;= test parsed)
_
#0)))
@@ -277,9 +277,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."
diff --git a/stdlib/source/test/lux/host.jvm.lux b/stdlib/source/test/lux/host.jvm.lux
index 318a66cec..20530d923 100644
--- a/stdlib/source/test/lux/host.jvm.lux
+++ b/stdlib/source/test/lux/host.jvm.lux
@@ -4,7 +4,7 @@
[monad (#+ Monad do)]
pipe]
[data
- ["." text ("#/." equivalence)]]
+ ["." text ("#;." equivalence)]]
[math
["r" random]]
["_" test (#+ Test)]]
@@ -94,7 +94,7 @@
(/.synchronized sample #1))
(_.test "Can access Class instances."
- (text/= "java.lang.Class" (Class::getName (/.class-for java/lang/Class))))
+ (text;= "java.lang.Class" (Class::getName (/.class-for java/lang/Class))))
(_.test "Can check if a value is null."
(and (/.null? (/.null))
diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux
index cc5997606..fa40f0fec 100644
--- a/stdlib/source/test/lux/macro/code.lux
+++ b/stdlib/source/test/lux/macro/code.lux
@@ -5,7 +5,7 @@
[monad (#+ do Monad)]]
[data
[number]
- ["." text ("#/." equivalence)
+ ["." text ("#;." equivalence)
format]]
[math
["r" random]]
@@ -17,7 +17,7 @@
(with-expansions
[<tests> (do-template [<expr> <text>]
[(test (format "Can produce Code node: " <text>)
- (and (text/= <text> (&.to-text <expr>))
+ (and (text;= <text> (&.to-text <expr>))
(:: &.equivalence = <expr> <expr>)))]
[(&.bit #1) "#1"]
diff --git a/stdlib/source/test/lux/macro/poly/equivalence.lux b/stdlib/source/test/lux/macro/poly/equivalence.lux
index a73d71112..63f9fa955 100644
--- a/stdlib/source/test/lux/macro/poly/equivalence.lux
+++ b/stdlib/source/test/lux/macro/poly/equivalence.lux
@@ -7,7 +7,7 @@
["." bit]
["." maybe]
[number
- ["." int ("#/." number)]]
+ ["." int ("#;." number)]]
["." text
format]
[collection
@@ -49,7 +49,7 @@
(r.Random Record)
(do r.monad
[size (:: @ map (n/% 2) r.nat)
- #let [gen-int (|> r.int (:: @ map (|>> int/abs (i/% +1,000,000))))]]
+ #let [gen-int (|> r.int (:: @ map (|>> int;abs (i/% +1,000,000))))]]
($_ r.and
r.bit
gen-int
@@ -67,6 +67,6 @@
(<| (times 100)
(do @
[sample gen-record
- #let [(^open "&/.") ..equivalence]]
+ #let [(^open "&;.") ..equivalence]]
(test "Every instance equals itself."
- (&/= sample sample)))))
+ (&;= sample sample)))))
diff --git a/stdlib/source/test/lux/math.lux b/stdlib/source/test/lux/math.lux
index 0ed9cab76..8b95691f6 100644
--- a/stdlib/source/test/lux/math.lux
+++ b/stdlib/source/test/lux/math.lux
@@ -3,9 +3,9 @@
[control
[monad (#+ Monad do)]]
[data
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
[number
- ["." frac ("#/." number)]]]
+ ["." frac ("#;." number)]]]
["&" math
infix
["r" random]]]
@@ -14,7 +14,7 @@
(def: (within? margin-of-error standard value)
(-> Frac Frac Frac Bit)
(f/< margin-of-error
- (frac/abs (f/- standard value))))
+ (frac;abs (f/- standard value))))
(def: margin Frac +0.0000001)
@@ -58,7 +58,7 @@
(test "The round will be an integer value, and will be < or > or = the original."
(let [round'd (&.round sample)]
(and (|> round'd frac-to-int int-to-frac (f/= round'd))
- (f/<= +1.0 (frac/abs (f/- sample round'd))))))
+ (f/<= +1.0 (frac;abs (f/- sample round'd))))))
))))
(context: "Exponentials and logarithms"
@@ -115,12 +115,12 @@
(infix [(n/* 3 9) &.n/gcd 450])))
(test "Can use non-numerical functions/macros as operators."
- (bit/= (and (n/< y x) (n/< z y))
+ (bit;= (and (n/< y x) (n/< z y))
(infix [[x n/< y] and [y n/< z]])))
(test "Can combine bit operations in special ways via special keywords."
- (and (bit/= (and (n/< y x) (n/< z y))
+ (and (bit;= (and (n/< y x) (n/< z y))
(infix [#and x n/< y n/< z]))
- (bit/= (and (n/< y x) (n/> z y))
+ (bit;= (and (n/< y x) (n/> z y))
(infix [#and x n/< y n/> z]))))
))))
diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux
index b64b3cb8c..aaacd32ef 100644
--- a/stdlib/source/test/lux/math/logic/fuzzy.lux
+++ b/stdlib/source/test/lux/math/logic/fuzzy.lux
@@ -3,7 +3,7 @@
[control
[monad (#+ do Monad)]]
[data
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
["." number]
[text
format]
@@ -45,12 +45,12 @@
(r/= _.false (&.membership top triangle))))
(test "Values within range, will have membership > 0."
- (bit/= (r/> _.false (&.membership sample triangle))
+ (bit;= (r/> _.false (&.membership sample triangle))
(and (<gt> bottom sample)
(<lt> top sample))))
(test "Values outside of range, will have membership = 0."
- (bit/= (r/= _.false (&.membership sample triangle))
+ (bit;= (r/= _.false (&.membership sample triangle))
(or (<lte> bottom sample)
(<gte> top sample))))
))))]
@@ -87,17 +87,17 @@
(r/= _.false (&.membership top trapezoid))))
(test "Values within inner range will have membership = 1"
- (bit/= (r/= _.true (&.membership sample trapezoid))
+ (bit;= (r/= _.true (&.membership sample trapezoid))
(and (<gte> middle-bottom sample)
(<lte> middle-top sample))))
(test "Values within range, will have membership > 0."
- (bit/= (r/> _.false (&.membership sample trapezoid))
+ (bit;= (r/> _.false (&.membership sample trapezoid))
(and (<gt> bottom sample)
(<lt> top sample))))
(test "Values outside of range, will have membership = 0."
- (bit/= (r/= _.false (&.membership sample trapezoid))
+ (bit;= (r/= _.false (&.membership sample trapezoid))
(or (<lte> bottom sample)
(<gte> top sample))))
))))]
@@ -141,7 +141,7 @@
(_.not (&.membership sample (&.complement left)))))
(test "Membership in the difference will never be higher than in the set being subtracted."
- (bit/= (r/> (&.membership sample right)
+ (bit;= (r/> (&.membership sample right)
(&.membership sample left))
(r/< (&.membership sample left)
(&.membership sample (&.difference left right)))))
@@ -155,12 +155,12 @@
($_ seq
(test (format "Values that satisfy a predicate have membership = 1."
"Values that don't have membership = 0.")
- (bit/= (r/= _.true (&.membership sample (&.from-predicate n/even?)))
+ (bit;= (r/= _.true (&.membership sample (&.from-predicate n/even?)))
(n/even? sample)))
(test (format "Values that belong to a set have membership = 1."
"Values that don't have membership = 0.")
- (bit/= (r/= _.true (&.membership sample (&.from-set set-10)))
+ (bit;= (r/= _.true (&.membership sample (&.from-set set-10)))
(set.member? set-10 sample)))
))))
@@ -174,10 +174,10 @@
member? (&.to-predicate threshold fuzzy)]]
($_ seq
(test "Can increase the threshold of membership of a fuzzy set."
- (bit/= (r/> _.false (&.membership sample vip-fuzzy))
+ (bit;= (r/> _.false (&.membership sample vip-fuzzy))
(r/> threshold (&.membership sample fuzzy))))
(test "Can turn fuzzy sets into predicates through a threshold."
- (bit/= (member? sample)
+ (bit;= (member? sample)
(r/> threshold (&.membership sample fuzzy))))
))))
diff --git a/stdlib/source/test/lux/math/modular.lux b/stdlib/source/test/lux/math/modular.lux
index 462fad44a..4f9449d2a 100644
--- a/stdlib/source/test/lux/math/modular.lux
+++ b/stdlib/source/test/lux/math/modular.lux
@@ -4,14 +4,14 @@
[monad (#+ do)]]
[data
["." product]
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
["." error]
[text
format]]
[math
["r" random]
["/" modular]]
- ["." type ("#/." equivalence)]]
+ ["." type ("#;." equivalence)]]
lux/test)
(def: %3 (/.modulus +3))
@@ -43,7 +43,7 @@
(-> Int Int Bit)
(-> (/.Mod m) (/.Mod m) Bit)))
(function (_ param subject)
- (bit/= (m/? param subject)
+ (bit;= (m/? param subject)
(i/? (value param)
(value subject)))))
@@ -71,11 +71,11 @@
#let [copyM (|> normalM /.to-int /.from-int error.assume)]]
($_ seq
(test "Every modulus has a unique type, even if the numeric value is the same as another."
- (and (type/= (:of normalM)
+ (and (type;= (:of normalM)
(:of normalM))
- (not (type/= (:of normalM)
+ (not (type;= (:of normalM)
(:of alternativeM)))
- (not (type/= (:of normalM)
+ (not (type;= (:of normalM)
(:of copyM)))))
(test "Can extract the original integer from the modulus."
@@ -91,11 +91,11 @@
((comparison /.m/>= i/>=) param subject)))
(test "Mod'ed values are ordered."
- (and (bit/= (/.m/< param subject)
+ (and (bit;= (/.m/< param subject)
(not (/.m/>= param subject)))
- (bit/= (/.m/> param subject)
+ (bit;= (/.m/> param subject)
(not (/.m/<= param subject)))
- (bit/= (/.m/= param subject)
+ (bit;= (/.m/= param subject)
(not (or (/.m/< param subject)
(/.m/> param subject))))))
@@ -145,6 +145,6 @@
(/.congruent? normalM _subject _subject))
(test "If 2 numbers are congruent under a modulus, then they must also be equal under the same modulus."
- (bit/= (/.congruent? normalM _param _subject)
+ (bit;= (/.congruent? normalM _param _subject)
(/.m/= param subject)))
))))
diff --git a/stdlib/source/test/lux/time/date.lux b/stdlib/source/test/lux/time/date.lux
index 2aee2dcb0..f9a90cb48 100644
--- a/stdlib/source/test/lux/time/date.lux
+++ b/stdlib/source/test/lux/time/date.lux
@@ -6,7 +6,7 @@
[data
["." error]]
[math
- ["r" random ("#/." monad)]]
+ ["r" random ("#;." monad)]]
[time
["@." instant]
["@" date]]]
@@ -16,18 +16,18 @@
(def: month
(r.Random @.Month)
- (r.either (r.either (r.either (r/wrap #@.January)
- (r.either (r/wrap #@.February)
- (r/wrap #@.March)))
- (r.either (r/wrap #@.April)
- (r.either (r/wrap #@.May)
- (r/wrap #@.June))))
- (r.either (r.either (r/wrap #@.July)
- (r.either (r/wrap #@.August)
- (r/wrap #@.September)))
- (r.either (r/wrap #@.October)
- (r.either (r/wrap #@.November)
- (r/wrap #@.December))))))
+ (r.either (r.either (r.either (r;wrap #@.January)
+ (r.either (r;wrap #@.February)
+ (r;wrap #@.March)))
+ (r.either (r;wrap #@.April)
+ (r.either (r;wrap #@.May)
+ (r;wrap #@.June))))
+ (r.either (r.either (r;wrap #@.July)
+ (r.either (r;wrap #@.August)
+ (r;wrap #@.September)))
+ (r.either (r;wrap #@.October)
+ (r.either (r;wrap #@.November)
+ (r;wrap #@.December))))))
(context: "(Month) Equivalence."
(<| (times 100)
@@ -64,13 +64,13 @@
(def: day
(r.Random @.Day)
- (r.either (r.either (r.either (r/wrap #@.Sunday)
- (r/wrap #@.Monday))
- (r.either (r/wrap #@.Tuesday)
- (r/wrap #@.Wednesday)))
- (r.either (r.either (r/wrap #@.Thursday)
- (r/wrap #@.Friday))
- (r/wrap #@.Saturday))))
+ (r.either (r.either (r.either (r;wrap #@.Sunday)
+ (r;wrap #@.Monday))
+ (r.either (r;wrap #@.Tuesday)
+ (r;wrap #@.Wednesday)))
+ (r.either (r.either (r;wrap #@.Thursday)
+ (r;wrap #@.Friday))
+ (r;wrap #@.Saturday))))
(context: "(Day) Equivalence."
(<| (times 100)
diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux
index b9a6f09e4..7f5d76730 100644
--- a/stdlib/source/test/lux/type.lux
+++ b/stdlib/source/test/lux/type.lux
@@ -27,13 +27,13 @@
(def: #export gen-type
(r.Random Type)
- (let [(^open "R/.") r.monad]
+ (let [(^open "R;.") r.monad]
(r.rec (function (_ gen-type)
(let [pairG (r.and gen-type gen-type)
idG r.nat
- quantifiedG (r.and (R/wrap (list)) gen-type)]
+ quantifiedG (r.and (R;wrap (list)) gen-type)]
($_ r.or
- (r.and gen-short (R/wrap (list)))
+ (r.and gen-short (R;wrap (list)))
pairG
pairG
pairG
@@ -97,15 +97,15 @@
#1)))
(list.repeat size)
(M.seq @))
- #let [(^open "&/.") &.equivalence
- (^open "L/.") (list.equivalence &.equivalence)]]
+ #let [(^open "&;.") &.equivalence
+ (^open "L;.") (list.equivalence &.equivalence)]]
(with-expansions
[<struct-tests> (do-template [<desc> <ctor> <dtor> <unit>]
[(test (format "Can build and tear-down " <desc> " types.")
(let [flat (|> members <ctor> <dtor>)]
- (or (L/= members flat)
- (and (L/= (list) members)
- (L/= (list <unit>) flat)))))]
+ (or (L;= members flat)
+ (and (L;= (list) members)
+ (L;= (list <unit>) flat)))))]
["variant" &.variant &.flatten-variant Nothing]
["tuple" &.tuple &.flatten-tuple Any]
@@ -127,13 +127,13 @@
_
#1))))
- #let [(^open "&/.") &.equivalence
- (^open "L/.") (list.equivalence &.equivalence)]]
+ #let [(^open "&;.") &.equivalence
+ (^open "L;.") (list.equivalence &.equivalence)]]
($_ seq
(test "Can build and tear-down function types."
(let [[inputs output] (|> (&.function members extra) &.flatten-function)]
- (and (L/= members inputs)
- (&/= extra output))))
+ (and (L;= members inputs)
+ (&;= extra output))))
(test "Can build and tear-down application types."
(let [[tfunc tparams] (|> extra (&.application members) &.flatten-application)]
@@ -152,13 +152,13 @@
_
#1))))
- #let [(^open "&/.") &.equivalence]]
+ #let [(^open "&;.") &.equivalence]]
(with-expansions
[<quant-tests> (do-template [<desc> <ctor> <dtor>]
[(test (format "Can build and tear-down " <desc> " types.")
(let [[flat-size flat-body] (|> extra (<ctor> size) <dtor>)]
(and (n/= size flat-size)
- (&/= extra flat-body))))]
+ (&;= extra flat-body))))]
["universally-quantified" &.univ-q &.flatten-univ-q]
["existentially-quantified" &.ex-q &.flatten-ex-q]
@@ -172,7 +172,7 @@
(_.test "Can extract types."
(let [example (: (Maybe Nat)
#.Nonae)]
- (type/= (type (List Nat))
+ (type;= (type (List Nat))
(:by-example [a]
{(Maybe a) example}
(List a))))))
diff --git a/stdlib/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux
index bd0b14167..45f1ce821 100644
--- a/stdlib/source/test/lux/type/check.lux
+++ b/stdlib/source/test/lux/type/check.lux
@@ -7,13 +7,13 @@
["." product]
["." maybe]
["." number]
- ["." text ("#/." equivalence)]
+ ["." text ("#;." equivalence)]
[collection
- ["." list ("#/." functor)]
+ ["." list ("#;." functor)]
["." set]]]
[math
["r" random]]
- ["." type ("#/." equivalence)
+ ["." type ("#;." equivalence)
["@" check]]]
lux/test
["." //])
@@ -112,7 +112,7 @@
(<| (times 100)
(do @
[nameL //.gen-short
- nameR (|> //.gen-short (r.filter (|>> (text/= nameL) not)))
+ nameR (|> //.gen-short (r.filter (|>> (text;= nameL) not)))
paramL //.gen-type
paramR (|> //.gen-type (r.filter (|>> (@.checks? paramL) not)))]
($_ seq
@@ -186,7 +186,7 @@
(test "Can create rings of variables."
(type-checks? (do @.monad
[[[head-id head-type] ids+types [tail-id tail-type]] (build-ring num-connections)
- #let [ids (list/map product.left ids+types)]
+ #let [ids (list;map product.left ids+types)]
headR (@.ring head-id)
tailR (@.ring tail-id)]
(@.assert ""
@@ -201,7 +201,7 @@
(test "When a var in a ring is bound, all the ring is bound."
(type-checks? (do @.monad
[[[head-id headT] ids+types tailT] (build-ring num-connections)
- #let [ids (list/map product.left ids+types)]
+ #let [ids (list;map product.left ids+types)]
_ (@.check headT boundT)
head-bound (@.read head-id)
tail-bound (monad.map @ @.read ids)
@@ -209,8 +209,8 @@
tailR+ (monad.map @ @.ring ids)]
(let [rings-were-erased? (and (set.empty? headR)
(list.every? set.empty? tailR+))
- same-types? (list.every? (type/= boundT) (list& (maybe.default headT head-bound)
- (list/map (function (_ [tail-id ?tailT])
+ same-types? (list.every? (type;= boundT) (list& (maybe.default headT head-bound)
+ (list;map (function (_ [tail-id ?tailT])
(maybe.default (#.Var tail-id) ?tailT))
(list.zip2 ids tail-bound))))]
(@.assert ""
diff --git a/stdlib/source/test/lux/type/implicit.lux b/stdlib/source/test/lux/type/implicit.lux
index 49c52aa48..dffd9496c 100644
--- a/stdlib/source/test/lux/type/implicit.lux
+++ b/stdlib/source/test/lux/type/implicit.lux
@@ -6,7 +6,7 @@
[functor]
[monad (#+ Monad do)]]
[data
- ["." bit ("#/." equivalence)]
+ ["." bit ("#;." equivalence)]
[number]
[collection [list]]]
[math
@@ -21,10 +21,10 @@
y r.nat]
($_ seq
(test "Can automatically select first-order structures."
- (let [(^open "list/.") (list.equivalence number.equivalence)]
- (and (bit/= (:: number.equivalence = x y)
+ (let [(^open "list;.") (list.equivalence number.equivalence)]
+ (and (bit;= (:: number.equivalence = x y)
(::: = x y))
- (list/= (list.n/range 1 10)
+ (list;= (list.n/range 1 10)
(::: map inc (list.n/range 0 9)))
)))
diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux
index 80d4a524b..deed8dbd2 100644
--- a/stdlib/source/test/lux/world/file.lux
+++ b/stdlib/source/test/lux/world/file.lux
@@ -19,7 +19,7 @@
["@" file (#+ Path File)]
["." binary (#+ Binary)]]
[math
- ["r" random ("#/." monad)]]]
+ ["r" random ("#;." monad)]]]
lux/test
[//
["_." binary]])
@@ -30,7 +30,7 @@
(def: (creation-and-deletion number)
(-> Nat Test)
- (r/wrap (do promise.monad
+ (r;wrap (do promise.monad
[#let [path (format "temp_file_" (%n number))]
result (promise.future
(do (error.ErrorT io.monad)
@@ -49,7 +49,7 @@
(def: (read-and-write number data)
(-> Nat Binary Test)
- (r/wrap (do promise.monad
+ (r;wrap (do promise.monad
[#let [path (format "temp_file_" (%n number))]
result (promise.future
(do (error.ErrorT io.monad)
diff --git a/stdlib/source/test/lux/world/net/tcp.lux b/stdlib/source/test/lux/world/net/tcp.lux
index 78be41610..43a304a58 100644
--- a/stdlib/source/test/lux/world/net/tcp.lux
+++ b/stdlib/source/test/lux/world/net/tcp.lux
@@ -8,7 +8,7 @@
["." taint]]]
[concurrency
["." promise (#+ Promise promise)]
- ["." frp ("#/." functor)]]
+ ["." frp ("#;." functor)]]
[data
["." error]
["." text
@@ -45,7 +45,7 @@
result (promise.future
(do io.monad
[[server-close server] (@.server port)
- #let [_ (frp/map (function (_ client)
+ #let [_ (frp;map (function (_ client)
(promise.future
(do @
[[trasmission-size transmission] (:: client read size)