diff options
Diffstat (limited to '')
24 files changed, 220 insertions, 220 deletions
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." |