diff options
Diffstat (limited to '')
35 files changed, 161 insertions, 158 deletions
diff --git a/stdlib/test/test/lux.lux b/stdlib/test/test/lux.lux index 788085db4..1f0a6e115 100644 --- a/stdlib/test/test/lux.lux +++ b/stdlib/test/test/lux.lux @@ -26,7 +26,7 @@                    (not (is? x y)))              )))) -(do-template [category rand-gen inc dec even? odd? = < >] +(do-template [category rand-gen even? odd? = < >]    [(context: (format "[" category "] " "Moving up-down or down-up should result in same value.")       (<| (times +100)           (do @ @@ -52,8 +52,8 @@                     (and (|> value inc even?)                          (|> value dec even?)))))))] -  ["Nat" r.nat n/inc n/dec n/even? n/odd? n/= n/< n/>] -  ["Int" r.int i/inc i/dec i/even? i/odd? i/= i/< i/>] +  ["Nat" r.nat n/even? n/odd? n/= n/< n/>] +  ["Int" r.int i/even? i/odd? i/= i/< i/>]    )  (do-template [category rand-gen = < > <= >= min max] @@ -86,7 +86,7 @@    ["Deg"  r.deg  d/= d/< d/> d/<= d/>= d/min d/max]    ) -(do-template [category rand-gen = + - * / <%> > <0> <1> <factor> %x <cap> <prep>] +(do-template [category rand-gen = + - * / <%> > <0> <1> <factor> <cap> <prep>]    [(context: (format "[" category "] " "Additive identity")       (<| (times +100)           (do @ @@ -136,10 +136,10 @@                           (|> x' (/ y) (* y) (= x'))))                   ))))] -  ["Nat"  r.nat  n/= n/+ n/- n/* n// n/% n/> +0  +1          +1000000     %n (n/% +1000) id] -  ["Int"  r.int  i/= i/+ i/- i/* i// i/% i/>  0   1           1000000     %i (i/%  1000) id] -  ["Frac" r.frac f/= f/+ f/- f/* f// f/% f/>  0.0 1.0         1000000.0   %r id          math.floor] -  ["Deg"  r.deg  d/= d/+ d/- d/* d// d/% d/>   .0 (:! Deg -1) (:! Deg -1) %f id          id] +  ["Nat"  r.nat  n/= n/+ n/- n/* n// n/% n/> +0  +1        +1_000_000   (n/% +1_000) id] +  ["Int"  r.int  i/= i/+ i/- i/* i// i/% i/>  0   1         1_000_000   (i/%  1_000) id] +  ["Frac" r.frac f/= f/+ f/- f/* f// f/% f/>  0.0 1.0       1_000_000.0 id           math.floor] +  ["Deg"  r.deg  d/= d/+ d/- d/* d// d/% d/>   .0 (.deg -1) (.deg -1)   id           id]    )  (def: frac-deg @@ -147,7 +147,7 @@    (|> r.deg        (:: r.Functor<Random> map (|>> (:! Nat) (bit.left-shift +11) (bit.right-shift +11) (:! Deg))))) -(do-template [category rand-gen -> <- = <cap> %a %z] +(do-template [category rand-gen -> <- = <cap>]    [(context: (format "[" category "] " "Numeric conversions")       (<| (times +100)           (do @ @@ -156,11 +156,11 @@             (test ""                   (|> value -> <- (= value))))))] -  ["Int->Nat"  r.int    int-to-nat  nat-to-int  i/= (i/%  1000000) %i %n] -  ["Nat->Int"  r.nat    nat-to-int  int-to-nat  n/= (n/% +1000000) %n %i] -  ["Int->Frac" r.int    int-to-frac frac-to-int i/= (i/%  1000000) %i %r] -  ["Frac->Int" r.frac   frac-to-int int-to-frac f/= math.floor     %r %i] -  ["Deg->Frac" frac-deg deg-to-frac frac-to-deg d/= id             %d %r] +  ["Int->Nat"  r.int    .nat        .int        i/= (i/%  1_000_000)] +  ["Nat->Int"  r.nat    .int        .nat        n/= (n/% +1_000_000)] +  ["Int->Frac" r.int    int-to-frac frac-to-int i/= (i/%  1_000_000)] +  ["Frac->Int" r.frac   frac-to-int int-to-frac f/= math.floor] +  ["Deg->Frac" frac-deg deg-to-frac frac-to-deg d/= id]    )  (context: "Simple macros and constructs" @@ -170,7 +170,7 @@                   (loop [counter 0                          value 1]                     (if (i/< 3 counter) -                     (recur (i/inc counter) (i/* 10 value)) +                     (recur (inc counter) (i/* 10 value))                       value))))        (test "Can create lists easily through macros." diff --git a/stdlib/test/test/lux/concurrency/atom.lux b/stdlib/test/test/lux/concurrency/atom.lux index 9063af2e7..a4856252a 100644 --- a/stdlib/test/test/lux/concurrency/atom.lux +++ b/stdlib/test/test/lux/concurrency/atom.lux @@ -25,8 +25,8 @@                         (n/= swap-value (io.run (&.read box)))))              (test "Can update the value of an atom." -                  (exec (io.run (&.update n/inc box)) -                    (n/= (n/inc swap-value) (io.run (&.read box))))) +                  (exec (io.run (&.update inc box)) +                    (n/= (inc swap-value) (io.run (&.read box)))))              (test "Can immediately set the value of an atom."                    (exec (io.run (&.write set-value box)) diff --git a/stdlib/test/test/lux/concurrency/frp.lux b/stdlib/test/test/lux/concurrency/frp.lux index 9630016e4..527fafb36 100644 --- a/stdlib/test/test/lux/concurrency/frp.lux +++ b/stdlib/test/test/lux/concurrency/frp.lux @@ -79,7 +79,7 @@                  [output (promise.future                           (do io.Monad<IO>                             [#let [inputs (: (Channel Int) (frp.channel [])) -                                  mapped (:: frp.Functor<Channel> map i/inc inputs)] +                                  mapped (:: frp.Functor<Channel> map inc inputs)]                              output (read! mapped)                              _ (write! (list 0 1 2 3 4 5) inputs)]                             (wrap output))) @@ -96,7 +96,7 @@                                    >a< (: (Channel Int) (frp.channel []))]                              output (read! (let [(^open) frp.Apply<Channel>]                                              (apply >f< >a<))) -                            _ (write! (list i/inc) >f<) +                            _ (write! (list inc) >f<)                              _ (write! (list 12345) >a<)]                             (wrap output)))                   _ (promise.wait +100) @@ -108,7 +108,7 @@          (wrap (do promise.Monad<Promise>                  [output (promise.future                           (read! (do frp.Monad<Channel> -                                  [f (frp.from-promise (promise.delay +100 i/inc)) +                                  [f (frp.from-promise (promise.delay +100 inc))                                     a (frp.from-promise (promise.delay +200 12345))]                                    (frp.from-promise (promise.delay +300 (f a))))))                   _ (promise.wait +700) diff --git a/stdlib/test/test/lux/concurrency/semaphore.lux b/stdlib/test/test/lux/concurrency/semaphore.lux index a41f06096..af025dbb5 100644 --- a/stdlib/test/test/lux/concurrency/semaphore.lux +++ b/stdlib/test/test/lux/concurrency/semaphore.lux @@ -18,7 +18,7 @@      (if (n/> +0 steps)        (do promise.Monad<Promise>          [_ (/.wait semaphore)] -        (recur (n/dec steps))) +        (recur (dec steps)))        (:: promise.Monad<Promise> wrap []))))  (context: "Semaphore." @@ -34,7 +34,7 @@              (let [semaphore (/.semaphore open-positions)]                (wrap (do promise.Monad<Promise>                        [result (<| (promise.time-out +100) -                                  (wait-many-times (n/inc open-positions) semaphore))] +                                  (wait-many-times (inc open-positions) semaphore))]                        (assert "Waiting on a semaphore more than the number of open positions blocks the process."                                (case result                                  (#.Some _) @@ -50,7 +50,7 @@                                  (do @                                    [_ (/.wait semaphore)                                     _ (/.signal semaphore)] -                                  (recur (n/dec steps))) +                                  (recur (dec steps)))                                  (wrap []))))]                        (assert "Signaling a semaphore replenishes its open positions."                                true)))) @@ -122,7 +122,7 @@          resource (atom.atom "")]      ($_ seq          (wrap (do promise.Monad<Promise> -                [#let [ids (list.n/range +0 (n/dec limit)) +                [#let [ids (list.n/range +0 (dec limit))                         waiters (list/map (function (_ id)                                             (let [process (waiter resource barrier id)]                                               (exec (io.run (atom.update (|>> (format "_")) resource)) diff --git a/stdlib/test/test/lux/concurrency/stm.lux b/stdlib/test/test/lux/concurrency/stm.lux index bf562c0fa..9f3c5bd7e 100644 --- a/stdlib/test/test/lux/concurrency/stm.lux +++ b/stdlib/test/test/lux/concurrency/stm.lux @@ -25,46 +25,49 @@                     channel)]      (wrap output))) -(def: iterations/processes Int 100) +(def: iterations-per-process Nat +100)  (context: "STM"    ($_ seq        (wrap (do promise.Monad<Promise> -              [output (&.commit (&.read (&.var 0)))] +              [output (&.commit (&.read (&.var +0)))]                (assert "Can read STM vars." -                      (i/= 0 output)))) +                      (n/= +0 output))))        (wrap (do promise.Monad<Promise> -              [#let [_var (&.var 0)] +              [#let [_var (&.var +0)]                 output (&.commit (do &.Monad<STM> -                                  [_ (&.write 5 _var)] +                                  [_ (&.write +5 _var)]                                    (&.read _var)))]                (assert "Can write STM vars." -                      (i/= 5 output)))) +                      (n/= +5 output))))        (wrap (do promise.Monad<Promise> -              [#let [_var (&.var 5)] +              [#let [_var (&.var +5)]                 output (&.commit (do &.Monad<STM> -                                  [_ (&.update (i/* 3) _var)] +                                  [_ (&.update (n/* +3) _var)]                                    (&.read _var)))]                (assert "Can update STM vars." -                      (i/= 15 output)))) +                      (n/= +15 output))))        (wrap (do promise.Monad<Promise> -              [#let [_var (&.var 0) +              [#let [_var (&.var +0)                       changes (io.run (read! (io.run (&.follow _var))))] -               _ (&.commit (&.write 5 _var)) -               _ (&.commit (&.update (i/* 3) _var)) +               _ (&.commit (&.write +5 _var)) +               _ (&.commit (&.update (n/* +3) _var))                 changes (promise.future (atom.read changes))]                (assert "Can follow all the changes to STM vars." -                      (:: (list.Eq<List> number.Eq<Int>) = -                          (list 5 15) +                      (:: (list.Eq<List> number.Eq<Nat>) = +                          (list +5 +15)                            (list.reverse changes))))) -      (wrap (let [_concurrency-var (&.var 0)] +      (wrap (let [_concurrency-var (&.var +0)]                (do promise.Monad<Promise> -                [_ (M.seq @ -                          (map (function (_ _) -                                 (M.map @ (function (_ _) (&.commit (&.update i/inc _concurrency-var))) -                                        (list.i/range 1 iterations/processes))) -                               (list.i/range 1 (nat-to-int promise.parallelism-level)))) +                [_ (|> promise.parallelism +                       (list.n/range +1) +                       (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." -                        (i/= (i/* iterations/processes (nat-to-int promise.parallelism-level)) -                             last-val))))))) +                        (|> promise.parallelism +                            (n/* iterations-per-process) +                            (n/= last-val)))))))) diff --git a/stdlib/test/test/lux/control/continuation.lux b/stdlib/test/test/lux/control/continuation.lux index 7f9ff00d9..ea43b511d 100644 --- a/stdlib/test/test/lux/control/continuation.lux +++ b/stdlib/test/test/lux/control/continuation.lux @@ -23,16 +23,16 @@                    (n/= sample (&.run (&/wrap sample))))              (test "Can use functor." -                  (n/= (n/inc sample) (&.run (&/map n/inc (&/wrap sample))))) +                  (n/= (inc sample) (&.run (&/map inc (&/wrap sample)))))              (test "Can use apply." -                  (n/= (n/inc sample) (&.run (&/apply (&/wrap n/inc) (&/wrap sample))))) +                  (n/= (inc sample) (&.run (&/apply (&/wrap inc) (&/wrap sample)))))              (test "Can use monad." -                  (n/= (n/inc sample) (&.run (do &.Monad<Cont> -                                               [func (wrap n/inc) -                                                arg (wrap sample)] -                                               (wrap (func arg)))))) +                  (n/= (inc sample) (&.run (do &.Monad<Cont> +                                             [func (wrap inc) +                                              arg (wrap sample)] +                                             (wrap (func arg))))))              (test "Can use the current-continuation as a escape hatch."                    (n/= (n/* +2 sample) @@ -52,7 +52,7 @@                         (&.run (do &.Monad<Cont>                                  [[restart [output idx]] (&.portal [sample +0])]                                  (if (n/< +10 idx) -                                  (restart [(n/+ +10 output) (n/inc idx)]) +                                  (restart [(n/+ +10 output) (inc idx)])                                    (wrap output))))))              (test "Can use delimited continuations with shifting." diff --git a/stdlib/test/test/lux/control/pipe.lux b/stdlib/test/test/lux/control/pipe.lux index 79e920468..d159cfeb9 100644 --- a/stdlib/test/test/lux/control/pipe.lux +++ b/stdlib/test/test/lux/control/pipe.lux @@ -17,7 +17,7 @@              (|> 20                  (i/* 3)                  (i/+ 4) -                (new> 0 i/inc) +                (new> 0 inc)                  (i/= 1)))        (test "Can give names to piped values within a pipeline's scope." @@ -44,7 +44,7 @@        (test "Can loop within pipelines."              (|> 1                  (loop> [(i/< 10)] -                       [i/inc]) +                       [inc])                  (i/= 10)))        (test "Can use monads within pipelines." @@ -52,7 +52,7 @@                  (do> Monad<Identity>                       [(i/* 3)]                       [(i/+ 4)] -                     [i/inc]) +                     [inc])                  (i/= 20)))        (test "Can pattern-match against piped values." diff --git a/stdlib/test/test/lux/control/reader.lux b/stdlib/test/test/lux/control/reader.lux index f84d8d16f..eba19b47b 100644 --- a/stdlib/test/test/lux/control/reader.lux +++ b/stdlib/test/test/lux/control/reader.lux @@ -15,7 +15,7 @@      ($_ seq          (test "" (i/= 123 (&.run 123 &.ask)))          (test "" (i/= 246 (&.run 123 (&.local (i/* 2) &.ask)))) -        (test "" (i/= 134 (&.run 123 (&/map i/inc (i/+ 10))))) +        (test "" (i/= 134 (&.run 123 (&/map inc (i/+ 10)))))          (test "" (i/= 10 (&.run 123 (&/wrap 10))))          (test "" (i/= 30 (&.run 123 (&/apply (&/wrap (i/+ 10)) (&/wrap 20)))))          (test "" (i/= 30 (&.run 123 (do &.Monad<Reader> diff --git a/stdlib/test/test/lux/control/region.lux b/stdlib/test/test/lux/control/region.lux index 429359057..a266218f9 100644 --- a/stdlib/test/test/lux/control/region.lux +++ b/stdlib/test/test/lux/control/region.lux @@ -35,7 +35,7 @@                        #let [@@ @                              count-clean-up (function (_ value)                                               (do @ -                                               [_ (thread.update n/inc clean-up-counter)] +                                               [_ (thread.update inc clean-up-counter)]                                                 (wrap (#e.Success []))))]                        outcome (/.run @                                       (do (/.Monad<Region> @) @@ -53,7 +53,7 @@                        #let [@@ @                              count-clean-up (function (_ value)                                               (do @ -                                               [_ (thread.update n/inc clean-up-counter)] +                                               [_ (thread.update inc clean-up-counter)]                                                 (wrap (#e.Success []))))]                        outcome (/.run @                                       (do (/.Monad<Region> @) @@ -72,7 +72,7 @@                        #let [@@ @                              count-clean-up (function (_ value)                                               (do @ -                                               [_ (thread.update n/inc clean-up-counter)] +                                               [_ (thread.update inc clean-up-counter)]                                                 (wrap (: (Error Top) (ex.throw oops [])))))]                        outcome (/.run @                                       (do (/.Monad<Region> @) diff --git a/stdlib/test/test/lux/control/state.lux b/stdlib/test/test/lux/control/state.lux index 33a318a2f..381a40b79 100644 --- a/stdlib/test/test/lux/control/state.lux +++ b/stdlib/test/test/lux/control/state.lux @@ -38,8 +38,8 @@                        [_ (&.update (n/* value))]                        &.get)))              (test "Can use the state." -                  (with-conditions [state (n/inc state)] -                    (&.use n/inc))) +                  (with-conditions [state (inc state)] +                    (&.use inc)))              (test "Can use a temporary (local) state."                    (with-conditions [state (n/* value state)]                      (&.local (n/* value) @@ -56,8 +56,8 @@                 (^open "&/") &.Monad<State>]]          ($_ seq              (test "Can use functor." -                  (with-conditions [state (n/inc state)] -                    (&/map n/inc &.get))) +                  (with-conditions [state (inc state)] +                    (&/map inc &.get)))              (test "Can use apply."                    (and (with-conditions [state value]                           (&/wrap value)) @@ -103,12 +103,12 @@                             (wrap (n/< limit state)))]]          ($_ seq              (test "'while' will only execute if the condition is true." -                  (|> (&.while condition (&.update n/inc)) +                  (|> (&.while condition (&.update inc))                        (&.run +0)                        (case> [state' output']                               (n/= limit state'))))              (test "'do-while' will execute at least once." -                  (|> (&.do-while condition (&.update n/inc)) +                  (|> (&.do-while condition (&.update inc))                        (&.run +0)                        (case> [state' output']                               (or (n/= limit state') diff --git a/stdlib/test/test/lux/control/writer.lux b/stdlib/test/test/lux/control/writer.lux index 09f37a957..49335de0d 100644 --- a/stdlib/test/test/lux/control/writer.lux +++ b/stdlib/test/test/lux/control/writer.lux @@ -14,7 +14,7 @@          (^open "&/") (&.Apply<Writer> text.Monoid<Text>)]      ($_ seq          (test "Functor respects Writer." -              (i/= 11 (product.right (&/map i/inc ["" 10])))) +              (i/= 11 (product.right (&/map inc ["" 10]))))          (test "Apply respects Writer."                (and (i/= 20 (product.right (&/wrap 20))) diff --git a/stdlib/test/test/lux/data/bit.lux b/stdlib/test/test/lux/data/bit.lux index 1b8110d31..9008f89cf 100644 --- a/stdlib/test/test/lux/data/bit.lux +++ b/stdlib/test/test/lux/data/bit.lux @@ -14,7 +14,7 @@           idx (:: @ map (n/% &.width) r.nat)]          ($_ seq              (test "Clearing and settings bits should alter the count." -                  (and (n/= (n/dec (&.count (&.set idx pattern))) +                  (and (n/= (dec (&.count (&.set idx pattern)))                              (&.count (&.clear idx pattern)))                         (|> (&.count pattern)                             (n/- (&.count (&.clear idx pattern))) @@ -66,7 +66,7 @@                             (&.rotate-right &.width)                             (n/= pattern))))              (test "Shift right respect the sign of ints." -                  (let [value (nat-to-int pattern)] +                  (let [value (.int pattern)]                      (if (i/< 0 value)                        (i/< 0 (&.arithmetic-right-shift idx value))                        (i/>= 0 (&.arithmetic-right-shift idx value))))) diff --git a/stdlib/test/test/lux/data/coll/array.lux b/stdlib/test/test/lux/data/coll/array.lux index 729f84221..125694cc7 100644 --- a/stdlib/test/test/lux/data/coll/array.lux +++ b/stdlib/test/test/lux/data/coll/array.lux @@ -39,7 +39,7 @@                    (exec (:: @.Fold<Array> fold                              (function (_ x idx)                                (exec (@.write idx x manual-copy) -                                (n/inc idx))) +                                (inc idx)))                              +0                              original)                      (:: (@.Eq<Array> number.Eq<Nat>) = original manual-copy))) @@ -109,8 +109,8 @@                        (and (= array copy)                             (not (is? array copy)))))                (test "Functor should go over all available array elements." -                    (let [there (map n/inc array) -                          back-again (map n/dec there)] +                    (let [there (map inc array) +                          back-again (map dec there)]                        (and (not (= array there))                             (= array back-again))))))))) diff --git a/stdlib/test/test/lux/data/coll/bits.lux b/stdlib/test/test/lux/data/coll/bits.lux index d33fa61b1..f416f9866 100644 --- a/stdlib/test/test/lux/data/coll/bits.lux +++ b/stdlib/test/test/lux/data/coll/bits.lux @@ -51,7 +51,7 @@                                             /.empty))                         (/.intersects? (/.set idx /.empty)                                        (/.set idx /.empty)) -                       (not (/.intersects? (/.set (n/inc idx) /.empty) +                       (not (/.intersects? (/.set (inc idx) /.empty)                                             (/.set idx /.empty)))))              (test "Cannot intersect with one's opposite."                    (not (/.intersects? sample (/.not sample)))) diff --git a/stdlib/test/test/lux/data/coll/dictionary/unordered.lux b/stdlib/test/test/lux/data/coll/dictionary/unordered.lux index 8c6ea275e..f0224a015 100644 --- a/stdlib/test/test/lux/data/coll/dictionary/unordered.lux +++ b/stdlib/test/test/lux/data/coll/dictionary/unordered.lux @@ -74,10 +74,10 @@              (test "Should be possible to update values via their keys."                    (let [base (&.put non-key test-val dict) -                        updt (&.update non-key n/inc base)] +                        updt (&.update non-key inc base)]                      (case [(&.get non-key base) (&.get non-key updt)]                        [(#.Some x) (#.Some y)] -                      (n/= (n/inc x) y) +                      (n/= (inc x) y)                        _                        false))) @@ -85,8 +85,8 @@              (test "Additions and removals to a Dict should affect its size."                    (let [plus (&.put non-key test-val dict)                          base (&.remove non-key plus)] -                    (and (n/= (n/inc (&.size dict)) (&.size plus)) -                         (n/= (n/dec (&.size plus)) (&.size base))))) +                    (and (n/= (inc (&.size dict)) (&.size plus)) +                         (n/= (dec (&.size plus)) (&.size base)))))              (test "A Dict should equal itself & going to<->from lists shouldn't change that."                    (let [(^open) (&.Eq<Dict> number.Eq<Nat>)] @@ -99,7 +99,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 (n/inc v)])) +                                  (list/map (function (_ [k v]) [k (inc v)]))                                    (&.from-list number.Hash<Nat>))                          (^open) (&.Eq<Dict> number.Eq<Nat>)]                      (= dict' (&.merge dict' dict)))) diff --git a/stdlib/test/test/lux/data/coll/list.lux b/stdlib/test/test/lux/data/coll/list.lux index 578b652da..73eb25d85 100644 --- a/stdlib/test/test/lux/data/coll/list.lux +++ b/stdlib/test/test/lux/data/coll/list.lux @@ -89,8 +89,8 @@              (test "Functor should go over every element of the list."                    (let [(^open) &.Functor<List> -                        there (map n/inc sample) -                        back-again (map n/dec there)] +                        there (map inc sample) +                        back-again (map dec there)]                      (and (not (= sample there))                           (= sample back-again)))) @@ -154,7 +154,7 @@                      (and (n/= size (&.size indices))                           (= indices                              (&.sort n/< indices)) -                         (&.every? (n/= (n/dec size)) +                         (&.every? (n/= (dec size))                                     (&.zip2-with n/+                                                  indices                                                  (&.sort n/> indices))) @@ -163,7 +163,7 @@              (test "The 'interpose' function places a value between every member of a list."                    (let [(^open) &.Functor<List>                          sample+ (&.interpose separator sample)] -                    (and (n/= (|> size (n/* +2) n/dec) +                    (and (n/= (|> size (n/* +2) dec)                                (&.size sample+))                           (|> sample+ &.as-pairs (map product.right) (&.every? (n/= separator)))))) @@ -179,8 +179,8 @@                    (let [(^open) &.Monad<List>                          (^open) &.Apply<List>]                      (and (= (list separator) (wrap separator)) -                         (= (map n/inc sample) -                            (apply (wrap n/inc) sample))))) +                         (= (map inc sample) +                            (apply (wrap inc) sample)))))              (test "List concatenation is a monad."                    (let [(^open) &.Monad<List> @@ -200,8 +200,8 @@                           (&.every? (bool.complement n/even?) sample))))              (test "You can iteratively construct a list, generating values until you're done." -                  (= (&.n/range +0 (n/dec size)) -                     (&.iterate (function (_ n) (if (n/< size n) (#.Some (n/inc n)) #.None)) +                  (= (&.n/range +0 (dec size)) +                     (&.iterate (function (_ n) (if (n/< size n) (#.Some (inc n)) #.None))                                  +0)))              (test "Can enumerate all elements in a list." @@ -216,8 +216,8 @@                           (list/= (&.n/range from to)                                   (&.reverse (&.n/range to from))))                         (let [(^open "list/") (&.Eq<List> number.Eq<Int>) -                             from (nat-to-int from) -                             to (nat-to-int to)] +                             from (.int from) +                             to (.int to)]                           (list/= (&.i/range from to)                                   (&.reverse (&.i/range to from))))))              )))) diff --git a/stdlib/test/test/lux/data/coll/queue.lux b/stdlib/test/test/lux/data/coll/queue.lux index 34330838b..7edcbf9b4 100644 --- a/stdlib/test/test/lux/data/coll/queue.lux +++ b/stdlib/test/test/lux/data/coll/queue.lux @@ -21,9 +21,9 @@                      (n/= size (&.size sample))))              (test "Enqueueing and dequeing affects the size of queues." -                  (and (n/= (n/inc size) (&.size (&.push non-member sample))) +                  (and (n/= (inc size) (&.size (&.push non-member sample)))                         (or (&.empty? sample) -                           (n/= (n/dec size) (&.size (&.pop sample)))) +                           (n/= (dec size) (&.size (&.pop sample))))                         (n/= size (&.size (&.pop (&.push non-member sample))))))              (test "Transforming to/from list can't change the queue." diff --git a/stdlib/test/test/lux/data/coll/queue/priority.lux b/stdlib/test/test/lux/data/coll/queue/priority.lux index 2ccb58ec4..38527523a 100644 --- a/stdlib/test/test/lux/data/coll/queue/priority.lux +++ b/stdlib/test/test/lux/data/coll/queue/priority.lux @@ -31,10 +31,10 @@                    (n/= size (&.size sample)))              (test "Enqueueing and dequeing affects the size of queues." -                  (and (n/= (n/inc size) +                  (and (n/= (inc size)                              (&.size (&.push non-member-priority non-member sample)))                         (or (n/= +0 (&.size sample)) -                           (n/= (n/dec size) +                           (n/= (dec size)                                  (&.size (&.pop sample))))))              (test "I can query whether an element belongs to a queue." diff --git a/stdlib/test/test/lux/data/coll/sequence.lux b/stdlib/test/test/lux/data/coll/sequence.lux index e1d561fb7..024e91c6b 100644 --- a/stdlib/test/test/lux/data/coll/sequence.lux +++ b/stdlib/test/test/lux/data/coll/sequence.lux @@ -30,8 +30,8 @@                      (n/= size (&.size sample))))              (test "Can add and remove elements to sequences." -                  (and (n/= (n/inc size) (&.size (&.add non-member sample))) -                       (n/= (n/dec size) (&.size (&.pop sample))))) +                  (and (n/= (inc size) (&.size (&.add non-member sample))) +                       (n/= (dec size) (&.size (&.pop sample)))))              (test "Can put and get elements into sequences."                    (|> sample @@ -42,9 +42,9 @@              (test "Can update elements of sequences."                    (|> sample -                      (&.put idx non-member) (&.update idx n/inc) +                      (&.put idx non-member) (&.update idx inc)                        (&.nth idx) maybe.assume -                      (n/= (n/inc non-member)))) +                      (n/= (inc non-member))))              (test "Can safely transform to/from lists."                    (|> sample &.to-list &.from-list (&/= sample))) @@ -58,14 +58,14 @@                         (&/fold n/+ +0 sample)))              (test "Functor goes over every element." -                  (let [there (&/map n/inc sample) -                        back-again (&/map n/dec there)] +                  (let [there (&/map inc sample) +                        back-again (&/map dec there)]                      (and (not (&/= sample there))                           (&/= sample back-again))))              (test "Apply allows you to create singleton sequences, and apply sequences of functions to sequences of values."                    (and (&/= (&.sequence non-member) (&/wrap non-member)) -                       (&/= (&/map n/inc sample)  (&/apply (&/wrap n/inc) sample)))) +                       (&/= (&/map inc sample)  (&/apply (&/wrap inc) sample))))              (test "Sequence concatenation is a monad."                    (&/= (&/compose sample other-sample) diff --git a/stdlib/test/test/lux/data/coll/stack.lux b/stdlib/test/test/lux/data/coll/stack.lux index 216c1a8c5..9a5b1b438 100644 --- a/stdlib/test/test/lux/data/coll/stack.lux +++ b/stdlib/test/test/lux/data/coll/stack.lux @@ -32,14 +32,14 @@              (test "Popping empty stacks doesn't change anything.                     But, if they're non-empty, the top of the stack is removed."                    (let [sample' (&.pop sample)] -                    (or (n/= (&.size sample) (n/inc (&.size sample'))) +                    (or (n/= (&.size sample) (inc (&.size sample')))                          (and (&.empty? sample) (&.empty? sample')))                      ))              (test "Pushing onto a stack always increases it by 1, adding a new value at the top."                    (and (is? sample                              (&.pop (&.push new-top sample))) -                       (n/= (n/inc (&.size sample)) (&.size (&.push new-top sample))) +                       (n/= (inc (&.size sample)) (&.size (&.push new-top sample)))                         (|> (&.push new-top sample) &.peek maybe.assume                             (is? new-top))))              )))) diff --git a/stdlib/test/test/lux/data/coll/stream.lux b/stdlib/test/test/lux/data/coll/stream.lux index cbdfcab49..9431e2a46 100644 --- a/stdlib/test/test/lux/data/coll/stream.lux +++ b/stdlib/test/test/lux/data/coll/stream.lux @@ -22,28 +22,28 @@           cycle-seed (r.list size r.nat)           cycle-sample-idx (|> r.nat (:: @ map (n/% +1000)))           #let [(^open "List/") (list.Eq<List> number.Eq<Nat>) -               sample0 (&.iterate n/inc +0) -               sample1 (&.iterate n/inc offset)]] +               sample0 (&.iterate inc +0) +               sample1 (&.iterate inc offset)]]          ($_ seq              (test "Can move along a stream and take slices off it." -                  (and (and (List/= (list.n/range +0 (n/dec size)) +                  (and (and (List/= (list.n/range +0 (dec size))                                      (&.take size sample0)) -                            (List/= (list.n/range offset (n/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 (n/dec size)) +                              (and (List/= (list.n/range +0 (dec size))                                             drops) -                                   (List/= (list.n/range size (n/dec (n/* +2 size))) +                                   (List/= (list.n/range size (dec (n/* +2 size)))                                             (&.take size takes))))) -                       (and (List/= (list.n/range +0 (n/dec size)) +                       (and (List/= (list.n/range +0 (dec size))                                      (&.take-while (n/< size) sample0)) -                            (List/= (list.n/range offset (n/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 (n/dec size)) +                              (and (List/= (list.n/range +0 (dec size))                                             drops) -                                   (List/= (list.n/range size (n/dec (n/* +2 size))) +                                   (List/= (list.n/range size (dec (n/* +2 size)))                                             (&.take-while (n/< (n/* +2 size)) takes)))))                         )) @@ -52,17 +52,17 @@              (test "Can obtain the head & tail of a stream."                    (and (n/= offset (&.head sample1)) -                       (List/= (list.n/range (n/inc offset) (n/+ offset size)) +                       (List/= (list.n/range (inc offset) (n/+ offset size))                                 (&.take size (&.tail sample1)))))              (test "Can filter streams."                    (and (n/= (n/* +2 offset)                              (&.nth offset                                     (&.filter n/even? sample0))) -                       (let [[evens odds] (&.partition n/even? (&.iterate n/inc +0))] +                       (let [[evens odds] (&.partition n/even? (&.iterate inc +0))]                           (and (n/= (n/* +2 offset)                                     (&.nth offset evens)) -                              (n/= (n/inc (n/* +2 offset)) +                              (n/= (inc (n/* +2 offset))                                     (&.nth offset odds))))))              (test "Functor goes over 'all' elements in a stream." @@ -86,9 +86,9 @@                    (let [(^open "&/") &.Functor<Stream>                          (^open "List/") (list.Eq<List> text.Eq<Text>)]                      (List/= (&.take size -                                    (&/map Nat/encode (&.iterate n/inc offset))) +                                    (&/map Nat/encode (&.iterate inc offset)))                              (&.take size -                                    (&.unfold (function (_ n) [(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 stream." diff --git a/stdlib/test/test/lux/data/coll/tree/rose.lux b/stdlib/test/test/lux/data/coll/tree/rose.lux index 1bf29d533..fdc385515 100644 --- a/stdlib/test/test/lux/data/coll/tree/rose.lux +++ b/stdlib/test/test/lux/data/coll/tree/rose.lux @@ -22,7 +22,7 @@                    children' (r.list num-children gen-tree)                    #let [size' (L/fold n/+ +0 (L/map product.left children'))                          children (L/map product.right children')]] -                 (wrap [(n/inc size') +                 (wrap [(inc size')                          (&.branch value children)]))                 )))) diff --git a/stdlib/test/test/lux/data/color.lux b/stdlib/test/test/lux/data/color.lux index b9290ed19..58bba6749 100644 --- a/stdlib/test/test/lux/data/color.lux +++ b/stdlib/test/test/lux/data/color.lux @@ -15,7 +15,7 @@  (def: scale    (-> Nat Frac) -  (|>> nat-to-int int-to-frac)) +  (|>> .int int-to-frac))  (def: square (-> Frac Frac) (math.pow 2.0)) diff --git a/stdlib/test/test/lux/data/error.lux b/stdlib/test/test/lux/data/error.lux index fb66bc7fe..ed7b6cc58 100644 --- a/stdlib/test/test/lux/data/error.lux +++ b/stdlib/test/test/lux/data/error.lux @@ -13,20 +13,20 @@      ($_ seq          (test "Functor correctly handles both cases."                (and (|> (: (&.Error Int) (#&.Success 10)) -                       (&/map i/inc) +                       (&/map inc)                         (case> (#&.Success 11) true _ false))                     (|> (: (&.Error Int) (#&.Error "YOLO")) -                       (&/map i/inc) +                       (&/map inc)                         (case> (#&.Error "YOLO") true _ false))                     ))          (test "Apply correctly handles both cases."                (and (|> (&/wrap 20)                         (case> (#&.Success 20) true _ false)) -                   (|> (&/apply (&/wrap i/inc) (&/wrap 10)) +                   (|> (&/apply (&/wrap inc) (&/wrap 10))                         (case> (#&.Success 11) true _ false)) -                   (|> (&/apply (&/wrap i/inc) (#&.Error "YOLO")) +                   (|> (&/apply (&/wrap inc) (#&.Error "YOLO"))                         (case> (#&.Error "YOLO") true _ false))))          (test "Monad correctly handles both cases." diff --git a/stdlib/test/test/lux/data/lazy.lux b/stdlib/test/test/lux/data/lazy.lux index 07513adec..da28003ba 100644 --- a/stdlib/test/test/lux/data/lazy.lux +++ b/stdlib/test/test/lux/data/lazy.lux @@ -31,22 +31,22 @@          ($_ seq              (test "Functor map."                    (|> (&.freeze sample) -                      (:: &.Functor<Lazy> map n/inc) +                      (:: &.Functor<Lazy> map inc)                        &.thaw -                      (n/= (n/inc sample)))) +                      (n/= (inc sample))))              (test "Monad."                    (|> (do &.Monad<Lazy> -                        [f (wrap n/inc) +                        [f (wrap inc)                           a (wrap sample)]                          (wrap (f a)))                        &.thaw -                      (n/= (n/inc sample)))) +                      (n/= (inc sample))))              (test "Apply apply."                    (let [(^open "&/") &.Monad<Lazy>                          (^open "&/") &.Apply<Lazy>] -                    (|> (&/apply (&/wrap n/inc) (&/wrap sample)) +                    (|> (&/apply (&/wrap inc) (&/wrap sample))                          &.thaw -                        (n/= (n/inc sample))))) +                        (n/= (inc sample)))))              )))) diff --git a/stdlib/test/test/lux/data/number.lux b/stdlib/test/test/lux/data/number.lux index 263dd346d..e6692fb3d 100644 --- a/stdlib/test/test/lux/data/number.lux +++ b/stdlib/test/test/lux/data/number.lux @@ -160,7 +160,7 @@        (do @          [raw r.frac           factor (|> r.nat (:: @ map (|>> (n/% +1000) (n/max +1)))) -         #let [sample (|> factor nat-to-int int-to-frac (f/* raw))]] +         #let [sample (|> factor .int int-to-frac (f/* raw))]]          (test "Can convert frac values to/from their bit patterns."                (|> sample frac-to-bits bits-to-frac (f/= sample)))))) diff --git a/stdlib/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux index 8369ad676..14ab1c76c 100644 --- a/stdlib/test/test/lux/data/number/complex.lux +++ b/stdlib/test/test/lux/data/number/complex.lux @@ -28,7 +28,7 @@    (do r.Monad<Random>      [factor (|> r.nat (:: @ map (|>> (n/% +1000) (n/max +1))))       measure (|> r.frac (r.filter (f/> 0.0)))] -    (wrap (f/* (|> factor nat-to-int int-to-frac) +    (wrap (f/* (|> factor .int int-to-frac)                 measure))))  (def: gen-complex @@ -196,6 +196,6 @@           degree (|> r.nat (:: @ map (|>> (n/max +1) (n/% +5))))]          (test "Can calculate the N roots for any complex number."                (|> sample -                  (&.nth-roots degree) -                  (list/map (&.pow' (|> degree nat-to-int int-to-frac))) +                  (&.roots degree) +                  (list/map (&.pow' (|> degree .int int-to-frac)))                    (list.every? (within? margin-of-error sample))))))) diff --git a/stdlib/test/test/lux/io.lux b/stdlib/test/test/lux/io.lux index 43841a708..faddcf42d 100644 --- a/stdlib/test/test/lux/io.lux +++ b/stdlib/test/test/lux/io.lux @@ -10,7 +10,7 @@  (context: "I/O"    ($_ seq        (test "" (Text/= "YOLO" (&.run (&.io "YOLO")))) -      (test "" (i/= 11 (&.run (:: &.Functor<IO> map i/inc (&.io 10))))) +      (test "" (i/= 11 (&.run (:: &.Functor<IO> map inc (&.io 10)))))        (test "" (i/= 10 (&.run (:: &.Monad<IO> wrap 10))))        (test "" (i/= 30 (&.run (let [(^open "&/") &.Apply<IO>                                      (^open "&/") &.Monad<IO>] diff --git a/stdlib/test/test/lux/lang/syntax.lux b/stdlib/test/test/lux/lang/syntax.lux index 68830f271..01679b27a 100644 --- a/stdlib/test/test/lux/lang/syntax.lux +++ b/stdlib/test/test/lux/lang/syntax.lux @@ -110,8 +110,8 @@  (context: "Frac special syntax."    (<| (times +100)        (do @ -        [numerator (|> r.nat (:: @ map (|>> (n/% +100) nat-to-frac))) -         denominator (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1) nat-to-frac))) +        [numerator (|> r.nat (:: @ map (|>> (n/% +100) .int int-to-frac))) +         denominator (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1) .int int-to-frac)))           signed? r.bool           #let [expected (|> numerator (f// denominator) (f/* (if signed? -1.0 1.0)))]]          (test "Can parse frac ratio syntax." @@ -201,7 +201,7 @@                                              (text.from-code y) "\n"                                              (text.from-code z))]                      (case (&.read "" (dict.new text.Hash<Text>) -                                  [(|> default-cursor (update@ #.column (n/+ (n/dec offset-size)))) +                                  [(|> default-cursor (update@ #.column (n/+ (dec offset-size))))                                     +0                                     (format "\"" good-input "\"")])                        (#e.Error error) diff --git a/stdlib/test/test/lux/lang/type/check.lux b/stdlib/test/test/lux/lang/type/check.lux index e10ac5514..517b2561b 100644 --- a/stdlib/test/test/lux/lang/type/check.lux +++ b/stdlib/test/test/lux/lang/type/check.lux @@ -216,7 +216,7 @@                                     tailR (@.ring tail-id)]                                    (@.assert ""                                              (let [same-rings? (:: set.Eq<Set> = headR tailR) -                                                  expected-size? (n/= (n/inc num-connections) (set.size headR)) +                                                  expected-size? (n/= (inc num-connections) (set.size headR))                                                    same-vars? (|> (set.to-list headR)                                                                   (list.sort n/<)                                                                   (:: (list.Eq<List> number.Eq<Nat>) = (list.sort n/< (#.Cons head-id ids))))] @@ -252,7 +252,7 @@                                     headRR-post (@.ring head-idR)]                                    (@.assert ""                                              (let [same-rings? (:: set.Eq<Set> = headRL-post headRR-post) -                                                  expected-size? (n/= (n/* +2 (n/inc num-connections)) +                                                  expected-size? (n/= (n/* +2 (inc num-connections))                                                                        (set.size headRL-post))                                                    union? (:: set.Eq<Set> = headRL-post (set.union headRL-pre headRR-pre))]                                                (and same-rings? diff --git a/stdlib/test/test/lux/type/implicit.lux b/stdlib/test/test/lux/type/implicit.lux index 2ae01ed1b..c07067b3e 100644 --- a/stdlib/test/test/lux/type/implicit.lux +++ b/stdlib/test/test/lux/type/implicit.lux @@ -22,7 +22,7 @@                      (and (bool/= (:: number.Eq<Nat> = x y)                                   (::: = x y))                           (list/= (list.n/range +1 +10) -                                 (::: map n/inc (list.n/range +0 +9))) +                                 (::: map inc (list.n/range +0 +9)))                           )))              (test "Can automatically select second-order structures." diff --git a/stdlib/test/test/lux/type/object/interface.lux b/stdlib/test/test/lux/type/object/interface.lux index 7def3113a..f74d32e2a 100644 --- a/stdlib/test/test/lux/type/object/interface.lux +++ b/stdlib/test/test/lux/type/object/interface.lux @@ -5,16 +5,16 @@  ## No parameters  (interface: Counter -  (inc [] @) -  (read [] Nat)) +  (inc! [] @) +  (read! [] Nat))  (class: NatC Counter    Nat -  (def: inc -    (update@Counter n/inc)) +  (def: inc! +    (update@Counter inc)) -  (def: read +  (def: read!      get@Counter))  (interface: Resettable-Counter @@ -56,28 +56,28 @@  ## Polymorphism  (def: (poly0 counter)    (-> Counter Nat) -  (read counter)) +  (read! counter))  (def: poly0-0 Nat (poly0 (new@NatC +0)))  (def: poly0-1 Nat (poly0 (new@NatRC +0 [])))  (def: (poly1 counter)    (-> Resettable-Counter Nat) -  (n/+ (read counter) -       (read (reset counter)))) +  (n/+ (read! counter) +       (read! (reset counter))))  (def: poly1-0 Nat (poly1 (new@NatRC +0 [])))  (def: (poly2 counter)    (-> NatC Nat) -  (read counter)) +  (read! counter))  (def: poly2-0 Nat (poly2 (new@NatC +0)))  (def: poly2-1 Nat (poly2 (new@NatRC +0 [])))  (def: (poly3 counter)    (-> NatRC Nat) -  (n/+ (read counter) -       (read (reset counter)))) +  (n/+ (read! counter) +       (read! (reset counter))))  (def: poly3-0 Nat (poly3 (new@NatRC +0 []))) diff --git a/stdlib/test/test/lux/type/object/protocol.lux b/stdlib/test/test/lux/type/object/protocol.lux index e5a8dda4b..fcb53d3b1 100644 --- a/stdlib/test/test/lux/type/object/protocol.lux +++ b/stdlib/test/test/lux/type/object/protocol.lux @@ -7,7 +7,7 @@  (def: (count [tick return] state)    (Class Nat (Method Top Nat)) -  (let [state' (n/inc state)] +  (let [state' (inc state)]      [(return state') state']))  (def: counter @@ -38,7 +38,7 @@           (#method2 [arg0 arg1 arg2] output)           (output (%n num-calls))) -       (recur (n/inc num-calls))]))) +       (recur (inc num-calls))])))  (def: _test1    [Nat Object0] diff --git a/stdlib/test/test/lux/world/blob.lux b/stdlib/test/test/lux/world/blob.lux index 37deb9d3b..1093f302f 100644 --- a/stdlib/test/test/lux/world/blob.lux +++ b/stdlib/test/test/lux/world/blob.lux @@ -29,14 +29,14 @@          (do r.Monad<Random>            [byte r.nat]            (exec (e.assume (/.write-8 idx byte output)) -            (recur (n/inc idx)))) +            (recur (inc idx))))          (:: r.Monad<Random> wrap output)))))  (def: (bits-io bytes read write value)    (-> Nat (-> Nat /.Blob (e.Error Nat)) (-> Nat Nat /.Blob (e.Error Top)) Nat Bool)    (let [blob (/.create +8)          bits (n/* +8 bytes) -        capped-value (|> +1 (bit.left-shift bits) n/dec (bit.and value))] +        capped-value (|> +1 (bit.left-shift bits) dec (bit.and value))]      (succeed       (do e.Monad<Error>         [_ (write +0 value blob) @@ -67,9 +67,9 @@              (test "Can read/write 64-bit values."                    (bits-io +8 /.read-64 /.write-64 value))              (test "Can slice blobs." -                  (let [slice-size (|> to (n/- from) n/inc) +                  (let [slice-size (|> to (n/- from) inc)                          random-slice (e.assume (/.slice from to random-blob)) -                        idxs (list.n/range +0 (n/dec slice-size)) +                        idxs (list.n/range +0 (dec slice-size))                          reader (function (_ blob idx) (/.read-8 idx blob))]                      (and (n/= slice-size (/.size random-slice))                           (case [(monad.map e.Monad<Error> (reader random-slice) idxs) diff --git a/stdlib/test/test/lux/world/file.lux b/stdlib/test/test/lux/world/file.lux index 6f4e26e6d..6d32a994b 100644 --- a/stdlib/test/test/lux/world/file.lux +++ b/stdlib/test/test/lux/world/file.lux @@ -73,8 +73,8 @@                              read-size (@.size file)                              _ (@.delete file)]                             (wrap (and (n/= (n/* +2 file-size) read-size) -                                      (:: blob.Eq<Blob> = dataL (e.assume (blob.slice +0 (n/dec file-size) output))) -                                      (:: blob.Eq<Blob> = dataR (e.assume (blob.slice file-size (n/dec read-size) output)))))))] +                                      (:: blob.Eq<Blob> = dataL (e.assume (blob.slice +0 (dec file-size) output))) +                                      (:: blob.Eq<Blob> = dataR (e.assume (blob.slice file-size (dec read-size) output)))))))]                  (assert "Can append to files."                          (e.default false result))))          (wrap (do P.Monad<Promise>  | 
