From e7fc42bbc7d0b56384864a6fcd1b1e0bf8cd880b Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 11 Jul 2018 07:36:33 -0400 Subject: - Improvements to import syntax [part 1]. --- stdlib/test/test/lux.lux | 2 +- stdlib/test/test/lux/cli.lux | 2 +- stdlib/test/test/lux/concurrency/actor.lux | 8 ++-- stdlib/test/test/lux/concurrency/frp.lux | 2 +- stdlib/test/test/lux/concurrency/promise.lux | 2 +- stdlib/test/test/lux/concurrency/semaphore.lux | 4 +- stdlib/test/test/lux/concurrency/stm.lux | 10 ++-- stdlib/test/test/lux/control/continuation.lux | 8 +--- stdlib/test/test/lux/control/parser.lux | 28 +++++------ stdlib/test/test/lux/control/pipe.lux | 2 +- stdlib/test/test/lux/control/reader.lux | 7 +-- stdlib/test/test/lux/control/state.lux | 5 +- stdlib/test/test/lux/control/writer.lux | 4 +- .../test/test/lux/data/collection/dictionary.lux | 2 +- .../lux/data/collection/dictionary/ordered.lux | 16 +++---- stdlib/test/test/lux/data/collection/row.lux | 2 +- stdlib/test/test/lux/data/collection/sequence.lux | 8 ++-- stdlib/test/test/lux/data/collection/set.lux | 2 +- .../test/test/lux/data/collection/set/ordered.lux | 2 +- stdlib/test/test/lux/data/collection/stack.lux | 7 +-- stdlib/test/test/lux/data/collection/tree/rose.lux | 12 ++--- .../test/lux/data/collection/tree/rose/zipper.lux | 2 +- stdlib/test/test/lux/data/color.lux | 2 +- stdlib/test/test/lux/data/format/xml.lux | 6 +-- stdlib/test/test/lux/data/ident.lux | 2 +- stdlib/test/test/lux/data/identity.lux | 18 +++---- stdlib/test/test/lux/data/maybe.lux | 2 +- stdlib/test/test/lux/data/number.lux | 6 +-- stdlib/test/test/lux/data/number/complex.lux | 4 +- stdlib/test/test/lux/data/number/ratio.lux | 2 +- stdlib/test/test/lux/data/product.lux | 12 ++--- stdlib/test/test/lux/data/sum.lux | 6 +-- stdlib/test/test/lux/data/text/lexer.lux | 2 +- stdlib/test/test/lux/data/text/regex.lux | 12 ++--- stdlib/test/test/lux/host.jvm.lux | 2 +- stdlib/test/test/lux/io.lux | 4 +- .../test/lux/language/compiler/analysis/case.lux | 29 +++++------ .../lux/language/compiler/analysis/function.lux | 8 ++-- .../lux/language/compiler/analysis/primitive.lux | 8 ++-- .../compiler/analysis/procedure/common.lux | 4 +- .../compiler/analysis/procedure/host.jvm.lux | 4 +- .../lux/language/compiler/analysis/reference.lux | 6 +-- .../lux/language/compiler/analysis/structure.lux | 8 ++-- .../test/lux/language/compiler/synthesis/case.lux | 4 +- .../lux/language/compiler/synthesis/function.lux | 4 +- .../lux/language/compiler/synthesis/structure.lux | 4 +- stdlib/test/test/lux/language/syntax.lux | 2 +- stdlib/test/test/lux/language/type.lux | 4 +- stdlib/test/test/lux/language/type/check.lux | 6 +-- stdlib/test/test/lux/macro/code.lux | 4 +- stdlib/test/test/lux/macro/poly/equivalence.lux | 2 +- stdlib/test/test/lux/macro/syntax.lux | 2 +- stdlib/test/test/lux/math.lux | 4 +- stdlib/test/test/lux/math/logic/fuzzy.lux | 56 +++++++++++----------- stdlib/test/test/lux/math/modular.lux | 4 +- stdlib/test/test/lux/time/date.lux | 46 +++++++++--------- stdlib/test/test/lux/time/instant.lux | 7 ++- stdlib/test/test/lux/type/implicit.lux | 2 +- stdlib/test/test/lux/world/net/tcp.lux | 2 +- 59 files changed, 203 insertions(+), 234 deletions(-) (limited to 'stdlib/test') diff --git a/stdlib/test/test/lux.lux b/stdlib/test/test/lux.lux index 4afb041fe..538a70b30 100644 --- a/stdlib/test/test/lux.lux +++ b/stdlib/test/test/lux.lux @@ -6,7 +6,7 @@ ["r" math/random] (data [maybe] [bit] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format) [macro] (macro ["s" syntax (#+ syntax:)]))) diff --git a/stdlib/test/test/lux/cli.lux b/stdlib/test/test/lux/cli.lux index f52f0d498..fc9ffa280 100644 --- a/stdlib/test/test/lux/cli.lux +++ b/stdlib/test/test/lux/cli.lux @@ -8,7 +8,7 @@ [sum] ["E" error] [number] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format (collection [list])) ["r" math/random] diff --git a/stdlib/test/test/lux/concurrency/actor.lux b/stdlib/test/test/lux/concurrency/actor.lux index 54f60b740..7895350e6 100644 --- a/stdlib/test/test/lux/concurrency/actor.lux +++ b/stdlib/test/test/lux/concurrency/actor.lux @@ -6,7 +6,7 @@ (data [number] text/format ["e" error]) - (concurrency ["P" promise "P/" Monad] + (concurrency ["P" promise ("promise/" Monad)] ["T" task] ["&" actor (#+ actor: message:)])) lux/test) @@ -22,9 +22,9 @@ (wrap output))) ((stop cause state) - (P/wrap (log! (if (ex.match? &.poisoned cause) - (format "Counter was poisoned: " (%n state)) - 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) diff --git a/stdlib/test/test/lux/concurrency/frp.lux b/stdlib/test/test/lux/concurrency/frp.lux index 6996997f1..637892e3b 100644 --- a/stdlib/test/test/lux/concurrency/frp.lux +++ b/stdlib/test/test/lux/concurrency/frp.lux @@ -5,7 +5,7 @@ (data [number] text/format (collection [list])) - (concurrency [promise "promise/" Monad] + (concurrency [promise ("promise/" Monad)] [frp (#+ Channel)] [atom (#+ Atom atom)])) lux/test) diff --git a/stdlib/test/test/lux/concurrency/promise.lux b/stdlib/test/test/lux/concurrency/promise.lux index 77f69dd46..b6540c145 100644 --- a/stdlib/test/test/lux/concurrency/promise.lux +++ b/stdlib/test/test/lux/concurrency/promise.lux @@ -5,7 +5,7 @@ pipe) (data [number] text/format) - (concurrency ["&" promise "&/" Monad]) + (concurrency ["&" promise ("&/" Monad)]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/concurrency/semaphore.lux b/stdlib/test/test/lux/concurrency/semaphore.lux index 6eb1752a6..c09b48545 100644 --- a/stdlib/test/test/lux/concurrency/semaphore.lux +++ b/stdlib/test/test/lux/concurrency/semaphore.lux @@ -2,9 +2,9 @@ lux (lux (control [monad (#+ do)]) (data [maybe] - [text "text/" Equivalence Monoid] + [text ("text/" Equivalence Monoid)] text/format - (collection [list "list/" Functor])) + (collection [list ("list/" Functor)])) (concurrency ["/" semaphore] [promise (#+ Promise)] [atom (#+ Atom)]) diff --git a/stdlib/test/test/lux/concurrency/stm.lux b/stdlib/test/test/lux/concurrency/stm.lux index a9c9f4420..c2d2dc8c0 100644 --- a/stdlib/test/test/lux/concurrency/stm.lux +++ b/stdlib/test/test/lux/concurrency/stm.lux @@ -4,7 +4,7 @@ (control ["M" monad (#+ do Monad)]) (data [number] [maybe] - (collection [list "" Functor]) + (collection [list ("list/" Functor)]) text/format) (concurrency [atom (#+ Atom atom)] ["&" stm] @@ -61,10 +61,10 @@ (do promise.Monad [_ (|> promise.parallelism (list.n/range +1) - (map (function (_ _) - (|> iterations-per-process - (list.n/range +1) - (M.map @ (function (_ _) (&.commit (&.update inc _concurrency-var))))))) + (list/map (function (_ _) + (|> iterations-per-process + (list.n/range +1) + (M.map @ (function (_ _) (&.commit (&.update inc _concurrency-var))))))) (M.seq @)) last-val (&.commit (&.read _concurrency-var))] (assert "Can modify STM vars concurrently from multiple threads." diff --git a/stdlib/test/test/lux/control/continuation.lux b/stdlib/test/test/lux/control/continuation.lux index 0df6d497d..cc8297cd7 100644 --- a/stdlib/test/test/lux/control/continuation.lux +++ b/stdlib/test/test/lux/control/continuation.lux @@ -1,12 +1,8 @@ (.module: lux - (lux [io] - (control ["M" monad (#+ do Monad)] + (lux (control ["M" monad (#+ do Monad)] ["&" continuation]) - (data [text "Text/" Monoid] - text/format - [number] - [product] + (data [number] (collection [list])) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/control/parser.lux b/stdlib/test/test/lux/control/parser.lux index 1f8e8ce73..805ec3126 100644 --- a/stdlib/test/test/lux/control/parser.lux +++ b/stdlib/test/test/lux/control/parser.lux @@ -1,16 +1,10 @@ (.module: lux (lux [io] - (control ["M" monad (#+ do Monad)] + (control ["M" monad (#+ do)] [equivalence (#+ Equivalence)] - ["&" parser] - pipe) - (data [text "Text/" Monoid] - text/format - [number] - [bool] - [ident] - ["E" error]) + ["&" parser]) + (data [error (#+ Error)]) ["r" math/random] [macro] (macro [code] @@ -19,15 +13,15 @@ ## [Utils] (def: (should-fail input) - (All [a] (-> (E.Error a) Bool)) + (All [a] (-> (Error a) Bool)) (case input - (#E.Error _) true - _ false)) + (#error.Error _) true + _ false)) (def: (enforced? parser input) (All [s] (-> (&.Parser s Any) s Bool)) (case (&.run input parser) - (#E.Success [_ []]) + (#error.Success [_ []]) true _ @@ -36,16 +30,16 @@ (def: (found? parser input) (All [s] (-> (&.Parser s Bool) s Bool)) (case (&.run input parser) - (#E.Success [_ true]) + (#error.Success [_ true]) true _ false)) (def: (fails? input) - (All [a] (-> (E.Error a) Bool)) + (All [a] (-> (Error a) Bool)) (case input - (#E.Error _) + (#error.Error _) true _ @@ -53,7 +47,7 @@ (syntax: (match pattern input) (wrap (list (` (case (~ input) - (^ (#E.Success [(~' _) (~ pattern)])) + (^ (#error.Success [(~' _) (~ pattern)])) true (~' _) diff --git a/stdlib/test/test/lux/control/pipe.lux b/stdlib/test/test/lux/control/pipe.lux index 081c4d308..317501109 100644 --- a/stdlib/test/test/lux/control/pipe.lux +++ b/stdlib/test/test/lux/control/pipe.lux @@ -7,7 +7,7 @@ [number] [product] identity - [text "text/" Equivalence]) + [text ("text/" Equivalence)]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/control/reader.lux b/stdlib/test/test/lux/control/reader.lux index 82fbb71c1..5259d1e51 100644 --- a/stdlib/test/test/lux/control/reader.lux +++ b/stdlib/test/test/lux/control/reader.lux @@ -1,12 +1,9 @@ (.module: lux (lux [io] - (control [monad (#+ do Monad)] + (control [monad (#+ do)] pipe - ["&" reader]) - (data [text "Text/" Monoid] - text/format - [number])) + ["&" reader])) lux/test) (context: "Readers" diff --git a/stdlib/test/test/lux/control/state.lux b/stdlib/test/test/lux/control/state.lux index 72fa13273..59f424be3 100644 --- a/stdlib/test/test/lux/control/state.lux +++ b/stdlib/test/test/lux/control/state.lux @@ -4,10 +4,7 @@ (control ["M" monad (#+ do Monad)] pipe ["&" state]) - (data [text "Text/" Monoid] - text/format - [number] - [product]) + (data [product]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/control/writer.lux b/stdlib/test/test/lux/control/writer.lux index 1b9cba738..49d6341e7 100644 --- a/stdlib/test/test/lux/control/writer.lux +++ b/stdlib/test/test/lux/control/writer.lux @@ -4,7 +4,7 @@ (control ["M" monad (#+ do Monad)] pipe ["&" writer]) - (data [text "Text/" Monoid Equivalence] + (data [text ("text/" Equivalence)] [number] [product])) lux/test) @@ -28,7 +28,7 @@ (wrap (f a b)))))) (test "Can log any value." - (Text/= "YOLO" (product.left (&.log "YOLO")))) + (text/= "YOLO" (product.left (&.log "YOLO")))) ))) (context: "Monad transformer" diff --git a/stdlib/test/test/lux/data/collection/dictionary.lux b/stdlib/test/test/lux/data/collection/dictionary.lux index 89121c106..db8c6ef5a 100644 --- a/stdlib/test/test/lux/data/collection/dictionary.lux +++ b/stdlib/test/test/lux/data/collection/dictionary.lux @@ -8,7 +8,7 @@ [number] [maybe] (collection ["&" dictionary] - [list "list/" Fold Functor])) + [list ("list/" Fold Functor)])) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/collection/dictionary/ordered.lux b/stdlib/test/test/lux/data/collection/dictionary/ordered.lux index a70244160..0c00a18be 100644 --- a/stdlib/test/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/test/test/lux/data/collection/dictionary/ordered.lux @@ -8,7 +8,7 @@ (collection ["s" set] ["dict" dictionary] (dictionary ["&" ordered]) - [list "L/" Functor])) + [list ("list/" Functor)])) ["r" math/random]) lux/test) @@ -26,7 +26,7 @@ sorted-pairs (list.sort (function (_ [left _] [right _]) (n/< left right)) pairs) - sorted-values (L/map product.right sorted-pairs) + sorted-values (list/map product.right sorted-pairs) (^open "&/") (&.Equivalence number.Equivalence)]] ($_ seq (test "Can query the size of a dictionary." @@ -60,12 +60,12 @@ (&/= sample))) (test "Order is preserved." - (let [(^open "L/") (list.Equivalence (: (Equivalence [Nat Nat]) - (function (_ [kr vr] [ks vs]) - (and (n/= kr ks) - (n/= vr vs)))))] - (L/= (&.entries sample) - sorted-pairs))) + (let [(^open "list/") (list.Equivalence (: (Equivalence [Nat Nat]) + (function (_ [kr vr] [ks vs]) + (and (n/= kr ks) + (n/= vr vs)))))] + (list/= (&.entries sample) + sorted-pairs))) (test "Every key in a dictionary must be identifiable." (list.every? (function (_ key) (&.contains? key sample)) diff --git a/stdlib/test/test/lux/data/collection/row.lux b/stdlib/test/test/lux/data/collection/row.lux index 0e861f0d8..8833c75d3 100644 --- a/stdlib/test/test/lux/data/collection/row.lux +++ b/stdlib/test/test/lux/data/collection/row.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do Monad)]) (data (collection ["&" row] - [list "list/" Fold]) + [list ("list/" Fold)]) [number] [maybe]) ["r" math/random]) diff --git a/stdlib/test/test/lux/data/collection/sequence.lux b/stdlib/test/test/lux/data/collection/sequence.lux index 9f45c36d6..48048216f 100644 --- a/stdlib/test/test/lux/data/collection/sequence.lux +++ b/stdlib/test/test/lux/data/collection/sequence.lux @@ -4,11 +4,11 @@ (control [monad (#+ do Monad)] comonad) (data [maybe] - [text "Text/" Monoid] + [text ("text/" Monoid)] text/format (collection [list] ["&" sequence]) - [number "Nat/" Codec]) + [number ("nat/" Codec)]) ["r" math/random]) lux/test) @@ -86,9 +86,9 @@ (let [(^open "&/") &.Functor (^open "List/") (list.Equivalence text.Equivalence)] (List/= (&.take size - (&/map Nat/encode (&.iterate inc offset))) + (&/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/test/test/lux/data/collection/set.lux b/stdlib/test/test/lux/data/collection/set.lux index 35a41b06d..41aaa88ff 100644 --- a/stdlib/test/test/lux/data/collection/set.lux +++ b/stdlib/test/test/lux/data/collection/set.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do Monad)]) (data (collection ["&" set (#+ Set)] - [list "" Fold]) + [list]) [number]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/collection/set/ordered.lux b/stdlib/test/test/lux/data/collection/set/ordered.lux index ab4cdd8d3..b99d5c225 100644 --- a/stdlib/test/test/lux/data/collection/set/ordered.lux +++ b/stdlib/test/test/lux/data/collection/set/ordered.lux @@ -4,7 +4,7 @@ (control [monad (#+ do Monad)]) (data (collection [set] (set ["&" ordered]) - [list "" Fold]) + [list]) [number] text/format) ["r" math/random]) diff --git a/stdlib/test/test/lux/data/collection/stack.lux b/stdlib/test/test/lux/data/collection/stack.lux index a60cc6004..faebac246 100644 --- a/stdlib/test/test/lux/data/collection/stack.lux +++ b/stdlib/test/test/lux/data/collection/stack.lux @@ -1,10 +1,7 @@ (.module: lux - (lux [io] - (control [monad (#+ do Monad)]) - (data (collection ["&" stack] - [list "" Fold]) - [number] + (lux (control [monad (#+ do)]) + (data (collection ["&" stack]) [maybe]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/collection/tree/rose.lux b/stdlib/test/test/lux/data/collection/tree/rose.lux index 282e1c009..211e0eb12 100644 --- a/stdlib/test/test/lux/data/collection/tree/rose.lux +++ b/stdlib/test/test/lux/data/collection/tree/rose.lux @@ -4,10 +4,10 @@ (control [monad (#+ do Monad)]) (data [product] [number] - [text "T/" Equivalence] + [text ("text/" Equivalence)] text/format (collection (tree ["&" rose]) - [list "L/" Monad Fold])) + [list ("list/" Functor Fold)])) ["r" math/random]) lux/test) @@ -20,8 +20,8 @@ [value r.nat num-children (|> r.nat (:: @ map (n/% +3))) children' (r.list num-children gen-tree) - #let [size' (L/fold n/+ +0 (L/map product.left children')) - children (L/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)])) )))) @@ -42,6 +42,6 @@ (list.size (&.flatten sample)))) (test "Can fold trees." - (T/= (&/fold concat "" sample) - (L/fold concat "" (&.flatten sample)))) + (text/= (&/fold concat "" sample) + (list/fold concat "" (&.flatten sample)))) )))) diff --git a/stdlib/test/test/lux/data/collection/tree/rose/zipper.lux b/stdlib/test/test/lux/data/collection/tree/rose/zipper.lux index 2a0b1f365..acd24c2c1 100644 --- a/stdlib/test/test/lux/data/collection/tree/rose/zipper.lux +++ b/stdlib/test/test/lux/data/collection/tree/rose/zipper.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do Monad)] pipe) - (data (collection [list "list/" Fold Functor] + (data (collection [list ("list/" Fold Functor)] (tree [rose] (rose ["&" zipper]))) [text] diff --git a/stdlib/test/test/lux/data/color.lux b/stdlib/test/test/lux/data/color.lux index c321d26d9..35b0db7d4 100644 --- a/stdlib/test/test/lux/data/color.lux +++ b/stdlib/test/test/lux/data/color.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do)]) (data ["@" color] - [number "frac/" Number]) + [number ("frac/" Number)]) [math] ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/format/xml.lux b/stdlib/test/test/lux/data/format/xml.lux index 4f14650b3..a96906f88 100644 --- a/stdlib/test/test/lux/data/format/xml.lux +++ b/stdlib/test/test/lux/data/format/xml.lux @@ -4,15 +4,15 @@ (control [monad (#+ do Monad)] ["p" parser] pipe) - (data [text "text/" Equivalence] + (data [text ("text/" Equivalence)] text/format [ident] ["E" error] [maybe] (format ["&" xml]) (collection ["dict" dictionary] - [list "list/" Functor])) - ["r" math/random "r/" Monad] + [list ("list/" Functor)])) + ["r" math/random ("r/" Monad)] test) ) diff --git a/stdlib/test/test/lux/data/ident.lux b/stdlib/test/test/lux/data/ident.lux index abb8a5d5c..57a6e5f4d 100644 --- a/stdlib/test/test/lux/data/ident.lux +++ b/stdlib/test/test/lux/data/ident.lux @@ -4,7 +4,7 @@ (control [monad (#+ do Monad)] pipe) (data ["&" ident] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/identity.lux b/stdlib/test/test/lux/data/identity.lux index df68144e4..7c82d700c 100644 --- a/stdlib/test/test/lux/data/identity.lux +++ b/stdlib/test/test/lux/data/identity.lux @@ -4,7 +4,7 @@ (control ["M" monad (#+ do Monad)] comonad) (data ["&" identity] - [text "Text/" Monoid Equivalence])) + [text ("text/" Monoid Equivalence)])) lux/test) (context: "Identity" @@ -13,23 +13,23 @@ (^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/test/test/lux/data/maybe.lux b/stdlib/test/test/lux/data/maybe.lux index 188db2b20..19af6ac6a 100644 --- a/stdlib/test/test/lux/data/maybe.lux +++ b/stdlib/test/test/lux/data/maybe.lux @@ -4,7 +4,7 @@ (control ["M" monad (#+ do Monad)] pipe) (data ["&" maybe] - [text "text/" Monoid] + [text ("text/" Monoid)] [number])) lux/test) diff --git a/stdlib/test/test/lux/data/number.lux b/stdlib/test/test/lux/data/number.lux index 7cdbe5848..e29521e87 100644 --- a/stdlib/test/test/lux/data/number.lux +++ b/stdlib/test/test/lux/data/number.lux @@ -4,7 +4,7 @@ (control ["M" monad (#+ do Monad)] pipe) (data number - [text "Text/" Monoid Equivalence] + [text ("text/" Equivalence)] text/format) ["r" math/random]) lux/test) @@ -35,11 +35,11 @@ (^open) ]] (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/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux index 17cd07278..11601933e 100644 --- a/stdlib/test/test/lux/data/number/complex.lux +++ b/stdlib/test/test/lux/data/number/complex.lux @@ -4,10 +4,10 @@ (control [monad (#+ do Monad)] pipe) (data [product] - [number "frac/" Number] + [number ("frac/" Number)] ["&" number/complex] text/format - (collection [list "list/" Functor])) + (collection [list ("list/" Functor)])) [math] ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/number/ratio.lux b/stdlib/test/test/lux/data/number/ratio.lux index 9802ac3b2..f0320a397 100644 --- a/stdlib/test/test/lux/data/number/ratio.lux +++ b/stdlib/test/test/lux/data/number/ratio.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do Monad)] pipe) - (data ["&" number/ratio "&/" Number]) + (data ["&" number/ratio ("&/" Number)]) ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/data/product.lux b/stdlib/test/test/lux/data/product.lux index 11e574cc2..309e8e311 100644 --- a/stdlib/test/test/lux/data/product.lux +++ b/stdlib/test/test/lux/data/product.lux @@ -1,20 +1,16 @@ (.module: lux - (lux [io] - (control ["M" monad (#+ do Monad)]) - (data product - [text "Text/" Monoid] - [number])) + (lux (data ["@" product])) lux/test) (context: "Products" ($_ seq (test "Can access the sides of a pair." - (and (i/= 1 (left [1 2])) - (i/= 2 (right [1 2])))) + (and (i/= 1 (@.left [1 2])) + (i/= 2 (@.right [1 2])))) (test "Can swap the sides of a pair." - (let [[_left _right] (swap [1 2])] + (let [[_left _right] (@.swap [1 2])] (and (i/= 2 _left) (i/= 1 _right)))) )) diff --git a/stdlib/test/test/lux/data/sum.lux b/stdlib/test/test/lux/data/sum.lux index 1b73fb627..04b295ccf 100644 --- a/stdlib/test/test/lux/data/sum.lux +++ b/stdlib/test/test/lux/data/sum.lux @@ -1,10 +1,8 @@ (.module: lux - (lux [io] - (control pipe) + (lux (control pipe) (data sum - [text "Text/" Monoid] - [number] + [text] (collection [list]))) lux/test) diff --git a/stdlib/test/test/lux/data/text/lexer.lux b/stdlib/test/test/lux/data/text/lexer.lux index b13605054..36b2eb1d9 100644 --- a/stdlib/test/test/lux/data/text/lexer.lux +++ b/stdlib/test/test/lux/data/text/lexer.lux @@ -5,7 +5,7 @@ ["p" parser]) [io] (data ["E" error] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format ["&" text/lexer] (collection [list])) diff --git a/stdlib/test/test/lux/data/text/regex.lux b/stdlib/test/test/lux/data/text/regex.lux index 7233c7308..581a9011f 100644 --- a/stdlib/test/test/lux/data/text/regex.lux +++ b/stdlib/test/test/lux/data/text/regex.lux @@ -5,7 +5,7 @@ pipe ["p" parser]) (data [product] - [text "T/" Equivalence] + [text ("text/" Equivalence)] text/format (text [lexer] ["&" regex])) @@ -20,7 +20,7 @@ (-> (lexer.Lexer Text) Text Bool) (|> (lexer.run input regex) (case> (#.Right parsed) - (T/= parsed input) + (text/= parsed input) _ false))) @@ -29,7 +29,7 @@ (-> Text (lexer.Lexer Text) Text Bool) (|> (lexer.run input regex) (case> (#.Right parsed) - (T/= test parsed) + (text/= test parsed) _ false))) @@ -276,9 +276,9 @@ (&.^regex "(.{3})-(.{3})-(.{4})" [_ match1 match2 match3]) (test "Can pattern-match using regular-expressions." - (and (T/= sample1 match1) - (T/= sample2 match2) - (T/= sample3 match3))) + (and (text/= sample1 match1) + (text/= sample2 match2) + (text/= sample3 match3))) _ (test "Cannot pattern-match using regular-expressions." diff --git a/stdlib/test/test/lux/host.jvm.lux b/stdlib/test/test/lux/host.jvm.lux index 5096f3200..13728b438 100644 --- a/stdlib/test/test/lux/host.jvm.lux +++ b/stdlib/test/test/lux/host.jvm.lux @@ -6,7 +6,7 @@ (data text/format [number] [product] - [text "text/" Equivalence]) + [text ("text/" Equivalence)]) ["&" host (#+ class: interface: object)] ["r" math/random]) lux/test) diff --git a/stdlib/test/test/lux/io.lux b/stdlib/test/test/lux/io.lux index f4c1bbf68..4257f8100 100644 --- a/stdlib/test/test/lux/io.lux +++ b/stdlib/test/test/lux/io.lux @@ -2,14 +2,14 @@ lux (lux ["&" io] (control ["M" monad (#+ do Monad)]) - (data [text "Text/" Monoid Equivalence] + (data [text ("text/" Equivalence)] text/format [number])) lux/test) (context: "I/O" ($_ seq - (test "" (Text/= "YOLO" (&.run (&.io "YOLO")))) + (test "" (text/= "YOLO" (&.run (&.io "YOLO")))) (test "" (i/= 11 (&.run (:: &.Functor map inc (&.io 10))))) (test "" (i/= 10 (&.run (:: &.Monad wrap 10)))) (test "" (i/= 30 (&.run (let [(^open "&/") &.Apply diff --git a/stdlib/test/test/lux/language/compiler/analysis/case.lux b/stdlib/test/test/lux/language/compiler/analysis/case.lux index e69e4d9d5..a2d54df8a 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/case.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/case.lux @@ -3,18 +3,15 @@ (lux [io] (control [monad (#+ do)] pipe) - (data [bool "B/" Equivalence] - ["R" error] - [product] + (data [product] [maybe] - [text "T/" Equivalence] - text/format - (collection [list "list/" Monad] + [text ("text/" Equivalence)] + (collection [list ("list/" Monad)] [set])) - ["r" math/random "r/" Monad] + ["r" math/random ("random/" Monad)] [macro (#+ Monad)] (macro [code]) - (language [type "type/" Equivalence] + (language [type] (type ["tc" check]) [".L" module] (compiler [analysis] @@ -43,7 +40,7 @@ (-> Bool (List [Code Code]) Code (r.Random (List Code))) (case inputC [_ (#.Bool _)] - (r/wrap (list (' true) (' false))) + (random/wrap (list (' true) (' false))) (^template [ ] [_ ( _)] @@ -58,7 +55,7 @@ #.None (wrap (list (' _))))) - (r/wrap (list (' _))))) + (random/wrap (list (' _))))) ([#.Nat r.nat code.nat] [#.Int r.int code.int] [#.Rev r.rev code.rev] @@ -66,10 +63,10 @@ [#.Text (r.unicode +5) code.text]) (^ [_ (#.Tuple (list))]) - (r/wrap (list (' []))) + (random/wrap (list (' []))) (^ [_ (#.Record (list))]) - (r/wrap (list (' {}))) + (random/wrap (list (' {}))) [_ (#.Tuple members)] (do r.Monad @@ -99,7 +96,7 @@ (wrap (list/join bundles))) _ - (r/wrap (list)) + (random/wrap (list)) )) (def: #export (input variant-tags record-tags primitivesC) @@ -107,7 +104,7 @@ (r.rec (function (_ input) ($_ r.either - (r/map product.right _primitive.primitive) + (random/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)) @@ -117,7 +114,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))) + (random/wrap (code.record (list.zip2 record-tags primitivesC))) )))) (def: (branch body pattern) @@ -132,7 +129,7 @@ (do @ [module-name (r.unicode +5) variant-name (r.unicode +5) - record-name (|> (r.unicode +5) (r.filter (|>> (T/= 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)) diff --git a/stdlib/test/test/lux/language/compiler/analysis/function.lux b/stdlib/test/test/lux/language/compiler/analysis/function.lux index a1b4dafe9..3de93fcc7 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/function.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/function.lux @@ -6,14 +6,14 @@ (data ["e" error] [maybe] [product] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format - (collection [list "list/" Functor])) - ["r" math/random "r/" Monad] + (collection [list ("list/" Functor)])) + ["r" math/random] [macro] (macro [code]) [language] - (language [type "type/" Equivalence] + (language [type ("type/" Equivalence)] [".L" reference] (compiler [".L" init] [".L" analysis (#+ Analysis)] diff --git a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux b/stdlib/test/test/lux/language/compiler/analysis/primitive.lux index 5a6e6cc69..1643786e3 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/primitive.lux @@ -6,11 +6,11 @@ ["ex" exception (#+ exception:)]) (data (text format) ["e" error]) - ["r" math/random "r/" Monad] + ["r" math/random ("random/" Monad)] [macro] (macro [code]) [language] - (language [".L" type "type/" Equivalence] + (language [".L" type ("type/" Equivalence)] (compiler [".L" init] [analysis (#+ Analysis)] (analysis [".A" type] @@ -21,13 +21,13 @@ (def: unit (r.Random Code) - (r/wrap (' []))) + (random/wrap (' []))) (def: #export primitive (r.Random [Type Code]) (`` ($_ r.either (~~ (do-template [ ] - [(r.seq (r/wrap ) (r/map ))] + [(r.seq (random/wrap ) (random/map ))] [Any code.tuple (r.list +0 ..unit)] [Bool code.bool r.bool] diff --git a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux b/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux index 656e0bdd6..ea7d8bdc2 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux @@ -8,11 +8,11 @@ ["e" error] [product] (collection [array])) - ["r" math/random "r/" Monad] + ["r" math/random] [macro (#+ Monad)] (macro [code]) [language] - (language [type "type/" Equivalence] + (language [type ("type/" Equivalence)] [".L" scope] (compiler [".L" init] (analysis [".A" type]))) diff --git a/stdlib/test/test/lux/language/compiler/analysis/procedure/host.jvm.lux b/stdlib/test/test/lux/language/compiler/analysis/procedure/host.jvm.lux index 72a1f0337..d33af651d 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/procedure/host.jvm.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/procedure/host.jvm.lux @@ -7,10 +7,10 @@ (data ["e" error] [product] [maybe] - [text "text/" Equivalence] + [text ("text/" Equivalence)] text/format (collection [array] - [list "list/" Fold] + [list ("list/" Fold)] ["dict" dictionary])) ["r" math/random "r/" Monad] [macro (#+ Monad)] diff --git a/stdlib/test/test/lux/language/compiler/analysis/reference.lux b/stdlib/test/test/lux/language/compiler/analysis/reference.lux index f91edb1ba..413a8fb01 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/reference.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/reference.lux @@ -4,13 +4,13 @@ (control [monad (#+ do)] pipe) (data ["e" error] - [ident "ident/" Equivalence] - [text "text/" Equivalence]) + [ident ("ident/" Equivalence)] + [text ("text/" Equivalence)]) ["r" math/random] [macro (#+ Monad)] (macro [code]) [language] - (language [type "type/" Equivalence] + (language [type ("type/" Equivalence)] [".L" scope] [".L" module] [".L" reference] diff --git a/stdlib/test/test/lux/language/compiler/analysis/structure.lux b/stdlib/test/test/lux/language/compiler/analysis/structure.lux index 95c19331b..dca02794d 100644 --- a/stdlib/test/test/lux/language/compiler/analysis/structure.lux +++ b/stdlib/test/test/lux/language/compiler/analysis/structure.lux @@ -3,19 +3,19 @@ (lux [io] (control [monad (#+ do)] pipe) - (data [bool "bool/" Equivalence] + (data [bool ("bool/" Equivalence)] ["e" error] [product] [maybe] [text] text/format - (collection [list "list/" Functor] + (collection [list ("list/" Functor)] [set])) - ["r" math/random "r/" Monad] + ["r" math/random] [macro] (macro [code]) [language] - (language [type "type/" Equivalence] + (language [type ("type/" Equivalence)] (type ["tc" check]) [".L" module] (compiler [".L" init] diff --git a/stdlib/test/test/lux/language/compiler/synthesis/case.lux b/stdlib/test/test/lux/language/compiler/synthesis/case.lux index b6d554604..7ae02d943 100644 --- a/stdlib/test/test/lux/language/compiler/synthesis/case.lux +++ b/stdlib/test/test/lux/language/compiler/synthesis/case.lux @@ -2,14 +2,14 @@ lux (lux (control [monad (#+ do)] pipe) - (data [error "error/" Functor]) + (data [error ("error/" Functor)]) (language ["///." reference] ["///." compiler] [".L" analysis (#+ Branch Analysis)] ["//" synthesis (#+ Synthesis)] (synthesis [".S" expression]) [".L" extension]) - ["r" math/random "r/" Monad] + ["r" math/random] test) [//primitive]) diff --git a/stdlib/test/test/lux/language/compiler/synthesis/function.lux b/stdlib/test/test/lux/language/compiler/synthesis/function.lux index 244692994..8bbc1401d 100644 --- a/stdlib/test/test/lux/language/compiler/synthesis/function.lux +++ b/stdlib/test/test/lux/language/compiler/synthesis/function.lux @@ -8,10 +8,10 @@ [error] [number] text/format - (collection [list "list/" Functor Fold] + (collection [list ("list/" Functor Fold)] ["dict" dictionary (#+ Dictionary)] [set])) - (language ["///." reference (#+ Variable) "variable/" Equivalence] + (language ["///." reference (#+ Variable) ("variable/" Equivalence)] ["///." compiler] [".L" analysis (#+ Arity Analysis)] ["//" synthesis (#+ Synthesis)] diff --git a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux b/stdlib/test/test/lux/language/compiler/synthesis/structure.lux index 125efdc49..8dba248e5 100644 --- a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux +++ b/stdlib/test/test/lux/language/compiler/synthesis/structure.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad (#+ do)] pipe) - (data [bool "bool/" Equivalence] + (data [bool ("bool/" Equivalence)] [product] [error] (collection [list])) @@ -12,7 +12,7 @@ ["//" synthesis (#+ Synthesis)] (synthesis [".S" expression]) [".L" extension]) - ["r" math/random "r/" Monad] + (math ["r" random]) test) [//primitive]) diff --git a/stdlib/test/test/lux/language/syntax.lux b/stdlib/test/test/lux/language/syntax.lux index 02bfee533..2a6e9ae5d 100644 --- a/stdlib/test/test/lux/language/syntax.lux +++ b/stdlib/test/test/lux/language/syntax.lux @@ -9,7 +9,7 @@ ["l" lexer]) (collection [list] ["dict" dictionary (#+ Dictionary)])) - ["r" math/random "r/" Monad] + ["r" math/random ("r/" Monad)] (macro [code]) (language ["&" syntax]) test)) diff --git a/stdlib/test/test/lux/language/type.lux b/stdlib/test/test/lux/language/type.lux index 7e4689a58..ccc315487 100644 --- a/stdlib/test/test/lux/language/type.lux +++ b/stdlib/test/test/lux/language/type.lux @@ -3,9 +3,7 @@ (lux [io] (control ["M" monad (#+ do Monad)] pipe) - (data [text "Text/" Monoid] - text/format - [number] + (data text/format [maybe] (collection [list])) ["r" math/random] diff --git a/stdlib/test/test/lux/language/type/check.lux b/stdlib/test/test/lux/language/type/check.lux index f1f464bf8..bc04f461b 100644 --- a/stdlib/test/test/lux/language/type/check.lux +++ b/stdlib/test/test/lux/language/type/check.lux @@ -6,12 +6,12 @@ (data [product] [maybe] [number] - [text "text/" Monoid Equivalence] + [text ("text/" Monoid Equivalence)] text/format - (collection [list "list/" Functor] + (collection [list ("list/" Functor)] [set])) ["r" math/random] - (language [type "type/" Equivalence] + (language [type ("type/" Equivalence)] (type ["@" check]))) lux/test) diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux index bc172def2..d1c7eb318 100644 --- a/stdlib/test/test/lux/macro/code.lux +++ b/stdlib/test/test/lux/macro/code.lux @@ -2,7 +2,7 @@ lux (lux [io] (control [monad (#+ do Monad)]) - (data [text "T/" Equivalence] + (data [text ("text/" Equivalence)] text/format [number]) ["r" math/random] @@ -13,7 +13,7 @@ (with-expansions [ (do-template [ ] [(test (format "Can produce Code node: " ) - (and (T/= (&.to-text )) + (and (text/= (&.to-text )) (:: &.Equivalence = )))] [(&.bool true) "true"] diff --git a/stdlib/test/test/lux/macro/poly/equivalence.lux b/stdlib/test/test/lux/macro/poly/equivalence.lux index a498478fd..30b41c6b0 100644 --- a/stdlib/test/test/lux/macro/poly/equivalence.lux +++ b/stdlib/test/test/lux/macro/poly/equivalence.lux @@ -5,7 +5,7 @@ [equivalence (#+ Equivalence)]) (data text/format [bool] - [number "int/" Number] + [number ("int/" Number)] [text] [maybe] (collection [list])) diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux index 258610aff..2b1fa4962 100644 --- a/stdlib/test/test/lux/macro/syntax.lux +++ b/stdlib/test/test/lux/macro/syntax.lux @@ -4,7 +4,7 @@ (control [monad (#+ do Monad)] [equivalence (#+ Equivalence)] ["p" parser]) - (data [text "Text/" Monoid] + (data [text] text/format [number] [bool] diff --git a/stdlib/test/test/lux/math.lux b/stdlib/test/test/lux/math.lux index 8fee2b105..2d13430ed 100644 --- a/stdlib/test/test/lux/math.lux +++ b/stdlib/test/test/lux/math.lux @@ -2,8 +2,8 @@ lux (lux [io] (control [monad (#+ do Monad)]) - (data [bool "bool/" Equivalence] - [number "frac/" Number]) + (data [bool ("bool/" Equivalence)] + [number ("frac/" Number)]) ["r" math/random] ["&" math]) lux/test) diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux index ed41fde5d..2c88469ce 100644 --- a/stdlib/test/test/lux/math/logic/fuzzy.lux +++ b/stdlib/test/test/lux/math/logic/fuzzy.lux @@ -4,7 +4,7 @@ (control [monad (#+ do Monad)]) (data (collection [list] [set]) - [bool "B/" Equivalence] + [bool ("bool/" Equivalence)] [number] text/format) ["r" math/random] @@ -40,14 +40,14 @@ (r/= ~false (&.membership top triangle)))) (test "Values within range, will have membership > 0." - (B/= (r/> ~false (&.membership sample triangle)) - (and ( bottom sample) - ( top sample)))) + (bool/= (r/> ~false (&.membership sample triangle)) + (and ( bottom sample) + ( top sample)))) (test "Values outside of range, will have membership = 0." - (B/= (r/= ~false (&.membership sample triangle)) - (or ( bottom sample) - ( top sample)))) + (bool/= (r/= ~false (&.membership sample triangle)) + (or ( bottom sample) + ( top sample)))) ))))] ["Rev" number.Hash r.rev &.triangle r/< r/<= r/> r/>=] @@ -82,19 +82,19 @@ (r/= ~false (&.membership top trapezoid)))) (test "Values within inner range will have membership = 1" - (B/= (r/= ~true (&.membership sample trapezoid)) - (and ( middle-bottom sample) - ( middle-top sample)))) + (bool/= (r/= ~true (&.membership sample trapezoid)) + (and ( middle-bottom sample) + ( middle-top sample)))) (test "Values within range, will have membership > 0." - (B/= (r/> ~false (&.membership sample trapezoid)) - (and ( bottom sample) - ( top sample)))) + (bool/= (r/> ~false (&.membership sample trapezoid)) + (and ( bottom sample) + ( top sample)))) (test "Values outside of range, will have membership = 0." - (B/= (r/= ~false (&.membership sample trapezoid)) - (or ( bottom sample) - ( top sample)))) + (bool/= (r/= ~false (&.membership sample trapezoid)) + (or ( bottom sample) + ( top sample)))) ))))] ["Rev" number.Hash r.rev &.trapezoid r/< r/<= r/> r/>=] @@ -136,10 +136,10 @@ (~not (&.membership sample (&.complement left))))) (test "Membership in the difference will never be higher than in the set being subtracted." - (B/= (r/> (&.membership sample right) - (&.membership sample left)) - (r/< (&.membership sample left) - (&.membership sample (&.difference left right))))) + (bool/= (r/> (&.membership sample right) + (&.membership sample left)) + (r/< (&.membership sample left) + (&.membership sample (&.difference left right))))) )))) (context: "From predicates and sets" @@ -150,13 +150,13 @@ ($_ seq (test "Values that satisfy a predicate have membership = 1. Values that don't have membership = 0." - (B/= (r/= ~true (&.membership sample (&.from-predicate n/even?))) - (n/even? sample))) + (bool/= (r/= ~true (&.membership sample (&.from-predicate n/even?))) + (n/even? sample))) (test "Values that belong to a set have membership = 1. Values that don't have membership = 0." - (B/= (r/= ~true (&.membership sample (&.from-set set-10))) - (set.member? set-10 sample))) + (bool/= (r/= ~true (&.membership sample (&.from-set set-10))) + (set.member? set-10 sample))) )))) (context: "Thresholds" @@ -169,10 +169,10 @@ member? (&.to-predicate threshold fuzzy)]] ($_ seq (test "Can increase the threshold of membership of a fuzzy set." - (B/= (r/> ~false (&.membership sample vip-fuzzy)) - (r/> threshold (&.membership sample fuzzy)))) + (bool/= (r/> ~false (&.membership sample vip-fuzzy)) + (r/> threshold (&.membership sample fuzzy)))) (test "Can turn fuzzy sets into predicates through a threshold." - (B/= (member? sample) - (r/> threshold (&.membership sample fuzzy)))) + (bool/= (member? sample) + (r/> threshold (&.membership sample fuzzy)))) )))) diff --git a/stdlib/test/test/lux/math/modular.lux b/stdlib/test/test/lux/math/modular.lux index b6778e2a0..afa6330d3 100644 --- a/stdlib/test/test/lux/math/modular.lux +++ b/stdlib/test/test/lux/math/modular.lux @@ -2,12 +2,12 @@ lux (lux (control [monad (#+ do)]) (data [product] - [bool "bool/" Equivalence] + [bool ("bool/" Equivalence)] ["e" error] text/format) (math ["r" random] ["/" modular]) - (language [type "type/" Equivalence])) + (language [type ("type/" Equivalence)])) lux/test) (def: %3 (/.modulus 3)) diff --git a/stdlib/test/test/lux/time/date.lux b/stdlib/test/test/lux/time/date.lux index 798bda645..93238bc11 100644 --- a/stdlib/test/test/lux/time/date.lux +++ b/stdlib/test/test/lux/time/date.lux @@ -3,8 +3,8 @@ (lux [io] (control [monad (#+ do Monad)] [pipe]) - (data ["E" error]) - (math ["r" random "r/" Monad]) + (data [error]) + (math ["r" random ("random/" Monad)]) (time ["@." instant] ["@" date])) lux/test @@ -12,18 +12,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 (random/wrap #@.January) + (r.either (random/wrap #@.February) + (random/wrap #@.March))) + (r.either (random/wrap #@.April) + (r.either (random/wrap #@.May) + (random/wrap #@.June)))) + (r.either (r.either (random/wrap #@.July) + (r.either (random/wrap #@.August) + (random/wrap #@.September))) + (r.either (random/wrap #@.October) + (r.either (random/wrap #@.November) + (random/wrap #@.December)))))) (context: "(Month) Equivalence." (<| (times +100) @@ -60,13 +60,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 (random/wrap #@.Sunday) + (random/wrap #@.Monday)) + (r.either (random/wrap #@.Tuesday) + (random/wrap #@.Wednesday))) + (r.either (r.either (random/wrap #@.Thursday) + (random/wrap #@.Friday)) + (random/wrap #@.Saturday)))) (context: "(Day) Equivalence." (<| (times +100) @@ -136,8 +136,8 @@ (|> sample @/encode @/decode - (pipe.case> (#E.Success decoded) + (pipe.case> (#error.Success decoded) (@/= sample decoded) - (#E.Error error) + (#error.Error error) false)))))) diff --git a/stdlib/test/test/lux/time/instant.lux b/stdlib/test/test/lux/time/instant.lux index e5bc7a7ea..c1e258566 100644 --- a/stdlib/test/test/lux/time/instant.lux +++ b/stdlib/test/test/lux/time/instant.lux @@ -5,8 +5,7 @@ pipe) (data [text] text/format - ["E" error] - [number "Int/" Number]) + [error]) (math ["r" random]) (time ["@" instant] ["@d" duration] @@ -88,8 +87,8 @@ ## (|> sample ## @/encode ## @/decode -## (case> (#E.Success decoded) +## (case> (#error.Success decoded) ## (@/= sample decoded) -## (#E.Error error) +## (#error.Error error) ## false)))))) diff --git a/stdlib/test/test/lux/type/implicit.lux b/stdlib/test/test/lux/type/implicit.lux index 94dcdad1e..680241dde 100644 --- a/stdlib/test/test/lux/type/implicit.lux +++ b/stdlib/test/test/lux/type/implicit.lux @@ -5,7 +5,7 @@ [functor] [monad (#+ do Monad)]) (data [number] - [bool "bool/" Equivalence] + [bool ("bool/" Equivalence)] (collection [list])) ["r" math/random] (type implicit)) diff --git a/stdlib/test/test/lux/world/net/tcp.lux b/stdlib/test/test/lux/world/net/tcp.lux index 7b232b7c6..7277a5b1c 100644 --- a/stdlib/test/test/lux/world/net/tcp.lux +++ b/stdlib/test/test/lux/world/net/tcp.lux @@ -5,7 +5,7 @@ ["ex" exception (#+ exception:)]) (concurrency ["P" promise] ["T" task] - [frp "frp/" Functor]) + [frp ("frp/" Functor)]) (data ["E" error] [text] text/format) -- cgit v1.2.3