From 78fd01f7e6688448bbd710336d4d7b1c35ae058a Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 25 Jul 2019 00:45:51 -0400 Subject: No more "i/"-prefixed functions. --- stdlib/source/lux.lux | 105 ++++------------- stdlib/source/lux/abstract/comonad.lux | 2 +- stdlib/source/lux/control/concatenative.lux | 24 ++-- stdlib/source/lux/control/contract.lux | 8 +- stdlib/source/lux/control/pipe.lux | 18 +-- stdlib/source/lux/data/collection/list.lux | 17 +-- stdlib/source/lux/data/format/css/selector.lux | 6 +- stdlib/source/lux/data/format/css/value.lux | 7 +- stdlib/source/lux/data/number/frac.lux | 4 +- stdlib/source/lux/data/number/int.lux | 110 ++++++++++++++---- stdlib/source/lux/data/number/rev.lux | 12 +- stdlib/source/lux/macro.lux | 5 +- stdlib/source/lux/math.lux | 3 +- stdlib/source/lux/math/infix.lux | 8 +- stdlib/source/lux/math/modular.lux | 62 +++++------ stdlib/source/lux/math/random.lux | 8 +- stdlib/source/lux/target/js.lux | 3 +- stdlib/source/lux/target/jvm/encoding/signed.lux | 9 +- stdlib/source/lux/target/jvm/instruction.lux | 5 +- stdlib/source/lux/target/lua.lux | 3 +- stdlib/source/lux/time/date.lux | 28 ++--- stdlib/source/lux/time/duration.lux | 36 +++--- stdlib/source/lux/time/instant.lux | 124 ++++++++++----------- .../tool/compiler/phase/generation/php/case.lux | 4 +- .../tool/compiler/phase/generation/python/case.lux | 4 +- .../tool/compiler/phase/generation/ruby/case.lux | 4 +- stdlib/source/lux/tool/compiler/synthesis.lux | 3 +- stdlib/source/lux/type/unit.lux | 31 +++--- stdlib/source/lux/world/db/sql.lux | 4 +- stdlib/source/lux/world/file.lux | 6 +- stdlib/source/lux/world/net/http/cookie.lux | 4 +- stdlib/source/program/licentia/input.lux | 6 +- .../source/spec/compositor/generation/common.lux | 20 ++-- .../spec/compositor/generation/structure.lux | 6 +- stdlib/source/test/lux.lux | 16 +-- stdlib/source/test/lux/data/number/frac.lux | 4 +- stdlib/source/test/lux/data/number/i64.lux | 10 +- stdlib/source/test/lux/data/number/int.lux | 6 +- stdlib/source/test/lux/data/product.lux | 13 ++- stdlib/source/test/lux/host.jvm.lux | 55 ++++----- stdlib/source/test/lux/host.old.lux | 10 +- stdlib/source/test/lux/macro/code.lux | 12 +- stdlib/source/test/lux/macro/poly/equivalence.lux | 4 +- stdlib/source/test/lux/math/modular.lux | 30 ++--- stdlib/source/test/lux/target/jvm.lux | 4 +- stdlib/source/test/lux/time/duration.lux | 7 +- stdlib/source/test/lux/time/instant.lux | 8 +- stdlib/source/test/lux/world/file.lux | 6 +- 48 files changed, 472 insertions(+), 412 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index 4f684d34d..05a4ece62 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -2179,7 +2179,7 @@ (text$ ($_ "lux text concat" "## By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary." __paragraph "(template [ ]" ..new-line - " " "[(def: #export (-> Int Int) (i/+ ))]" __paragraph + " " "[(def: #export (-> Int Int) (+ ))]" __paragraph " " "[inc +1]" ..new-line " " "[dec -1]"))]) ({(#Cons [[_ (#Tuple bindings)] (#Cons [[_ (#Tuple templates)] data])]) @@ -2203,47 +2203,6 @@ (fail "Wrong syntax for template")} tokens)) -(template [ - - <<-doc> <<=-doc> <>-doc> <>=-doc>] - [(def:''' #export ( reference sample) - (list [(tag$ ["lux" "doc"]) - (text$ )]) - (-> Bit) - ( reference sample)) - - (def:''' #export ( reference sample) - (list [(tag$ ["lux" "doc"]) - (text$ <<-doc>)]) - (-> Bit) - ( reference sample)) - - (def:''' #export ( reference sample) - (list [(tag$ ["lux" "doc"]) - (text$ <<=-doc>)]) - (-> Bit) - (if ( reference sample) - #1 - ( reference sample))) - - (def:''' #export ( reference sample) - (list [(tag$ ["lux" "doc"]) - (text$ <>-doc>)]) - (-> Bit) - ( sample reference)) - - (def:''' #export ( reference sample) - (list [(tag$ ["lux" "doc"]) - (text$ <>=-doc>)]) - (-> Bit) - (if ( sample reference) - #1 - ( reference sample)))] - - [ Int "lux i64 =" "lux i64 <" i/= i/< i/<= i/> i/>= - "Int(eger) equivalence." "Int(eger) less-than." "Int(eger) less-than-equal." "Int(eger) greater-than." "Int(eger) greater-than-equal."] - ) - (def:''' #export (n// param subject) (list [(tag$ ["lux" "doc"]) (text$ "Nat(ural) division.")]) @@ -2283,21 +2242,6 @@ ("lux coerce" Int (n// param subject)))] ("lux i64 -" flat subject))) -(template [ ] - [(def:''' #export ( param subject) - (list [(tag$ ["lux" "doc"]) - (text$ )]) - (-> Int Int Int) - ( param subject))] - - [i/+ "lux i64 +" "Int(eger) addition."] - [i/- "lux i64 -" "Int(eger) substraction."] - - [i/* "lux i64 *" "Int(eger) multiplication."] - [i// "lux i64 /" "Int(eger) division."] - [i/% "lux i64 %" "Int(eger) remainder."] - ) - (template [ ] [(def:''' #export ( left right) (list [(tag$ ["lux" "doc"]) @@ -2309,9 +2253,6 @@ [n/min Nat n/< "Nat(ural) minimum."] [n/max Nat n/> "Nat(ural) maximum."] - - [i/min Int i/< "Int(eger) minimum."] - [i/max Int i/> "Int(eger) maximum."] ) (def:''' (bit@encode x) @@ -2349,27 +2290,27 @@ (def:''' (int@abs value) #Nil (-> Int Int) - (if (i/< +0 value) - (i/* -1 value) + (if ("lux i64 <" +0 value) + ("lux i64 *" -1 value) value)) (def:''' (int@encode value) #Nil (-> Int Text) - (if (i/= +0 value) + (if ("lux i64 =" +0 value) "0" - (let' [sign (if (i/> +0 value) + (let' [sign (if ("lux i64 <" value +0) "" "-")] (("lux check" (-> Int Text Text) (function' recur [input output] - (if (i/= +0 input) + (if ("lux i64 =" +0 input) (text@compose sign output) - (recur (i// +10 input) - (text@compose (|> input (i/% +10) ("lux coerce" Nat) digit-to-text) + (recur ("lux i64 /" +10 input) + (text@compose (|> input ("lux i64 %" +10) ("lux coerce" Nat) digit-to-text) output))))) - (|> value (i// +10) int@abs) - (|> value (i/% +10) int@abs ("lux coerce" Nat) digit-to-text))))) + (|> value ("lux i64 /" +10) int@abs) + (|> value ("lux i64 %" +10) int@abs ("lux coerce" Nat) digit-to-text))))) (def:''' (frac@encode x) #Nil @@ -2904,7 +2845,7 @@ "## Allows the usage of macros within the patterns to provide custom syntax." ..new-line "(case (: (List Int) (list +1 +2 +3))" ..new-line " " "(#Cons x (#Cons y (#Cons z #Nil)))" ..new-line - " " "(#Some ($_ i/* x y z))" __paragraph + " " "(#Some ($_ * x y z))" __paragraph " " "_" ..new-line " " "#None)"))]) ({(#Cons value branches) @@ -2923,7 +2864,7 @@ "## It's a special macro meant to be used with 'case'." ..new-line "(case (: (List Int) (list +1 +2 +3))" ..new-line " (^ (list x y z))" ..new-line - " (#Some ($_ i/* x y z))" + " (#Some ($_ * x y z))" __paragraph " _" ..new-line " #None)"))]) @@ -3688,15 +3629,15 @@ "(structure: #export order (Order Int)" ..new-line " (def: &equivalence equivalence)" ..new-line " (def: (< test subject)" ..new-line - " (lux.i/< test subject))" ..new-line + " (< test subject))" ..new-line " (def: (<= test subject)" ..new-line - " (or (lux.i/< test subject)" ..new-line - " (lux.i/= test subject)))" ..new-line + " (or (< test subject)" ..new-line + " (= test subject)))" ..new-line " (def: (> test subject)" ..new-line - " (lux.i/> test subject))" ..new-line + " (> test subject))" ..new-line " (def: (>= test subject)" ..new-line - " (or (lux.i/> test subject)" ..new-line - " (lux.i/= test subject))))"))} + " (or (> test subject)" ..new-line + " (= test subject))))"))} (let [[exported? tokens'] (export^ tokens) ?parts (: (Maybe [Code (List Code) Code Code (List Code)]) (case tokens' @@ -5017,8 +4958,8 @@ (def: (repeat n x) (All [a] (-> Int a (List a))) - (if (i/> +0 n) - (#Cons x (repeat (i/+ -1 n) x)) + (if ("lux i64 <" n +0) + (#Cons x (repeat ("lux i64 +" -1 n) x)) #Nil)) (def: (cursor-padding baseline [_ old-line old-column] [_ new-line new-column]) @@ -5554,7 +5495,7 @@ (not ( n)))] [Nat n/even? n/odd? n/% n/= 0 2] - [Int i/even? i/odd? i/% i/= +0 +2]) + ) (def: (get-scope-type-vars state) (Meta (List Nat)) @@ -5607,7 +5548,7 @@ (is? value value)) "This one should fail:" - (is? +5 (i/+ +2 +3)))} + (is? +5 (+ +2 +3)))} (All [a] (-> a a Bit)) ("lux is" reference sample)) @@ -5760,7 +5701,7 @@ {#.doc (doc "Define macros in the style of template and ^template." "For simple macros that do not need any fancy features." (template: (square x) - (i/* x x)))} + (* x x)))} (do meta-monad [#let [[export? tokens] (export^ tokens)] name+args|tokens (parse-complex-declaration tokens) diff --git a/stdlib/source/lux/abstract/comonad.lux b/stdlib/source/lux/abstract/comonad.lux index 1d6ac49e5..cc5aaad91 100644 --- a/stdlib/source/lux/abstract/comonad.lux +++ b/stdlib/source/lux/abstract/comonad.lux @@ -26,7 +26,7 @@ (macro: #export (be tokens state) {#.doc (doc "A co-monadic parallel to the 'do' macro." - (let [square (function (_ n) (i/* n n))] + (let [square (function (_ n) (* n n))] (be comonad [inputs (iterate inc +2)] (square (head inputs)))))} diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux index 53ae6cd77..ea81bdf76 100644 --- a/stdlib/source/lux/control/concatenative.lux +++ b/stdlib/source/lux/control/concatenative.lux @@ -1,7 +1,6 @@ (.module: [lux (#- if loop when - n/+ n/- n/* n// n/% n/= n/< n/<= n/> n/>= - i/+ i/- i/* i// i/% i/= i/< i/<= i/> i/>=) + n/+ n/- n/* n// n/% n/= n/< n/<= n/> n/>=) [abstract ["." monad]] [data @@ -11,6 +10,7 @@ [collection ["." list ("#;." fold functor)]] [number + ["i" int] ["r" rev] ["f" frac]]] ["." macro (#+ with-gensyms) @@ -218,16 +218,16 @@ [Nat Bit n/> .n/>] [Nat Bit n/>= .n/>=] - [Int Int i/+ .i/+] - [Int Int i/- .i/-] - [Int Int i/* .i/*] - [Int Int i// .i//] - [Int Int i/% .i/%] - [Int Bit i/= .i/=] - [Int Bit i/< .i/<] - [Int Bit i/<= .i/<=] - [Int Bit i/> .i/>] - [Int Bit i/>= .i/>=] + [Int Int i/+ i.+] + [Int Int i/- i.-] + [Int Int i/* i.*] + [Int Int i// i./] + [Int Int i/% i.%] + [Int Bit i/= i.=] + [Int Bit i/< i.<] + [Int Bit i/<= i.<=] + [Int Bit i/> i.>] + [Int Bit i/>= i.>=] [Rev Rev r/+ r.+] [Rev Rev r/- r.-] diff --git a/stdlib/source/lux/control/contract.lux b/stdlib/source/lux/control/contract.lux index 4c402de24..3d1359fdf 100644 --- a/stdlib/source/lux/control/contract.lux +++ b/stdlib/source/lux/control/contract.lux @@ -6,6 +6,8 @@ [parser ["s" code]]] [data + [number + ["i" int]] [text ["%" format (#+ format)]]] [macro (#+ with-gensyms) @@ -22,7 +24,7 @@ {#.doc (doc "Pre-conditions." "Given a test and an expression to run, only runs the expression if the test passes." "Otherwise, an error is raised." - (pre (i/= +4 (i/+ +2 +2)) + (pre (i.= +4 (i.+ +2 +2)) (foo +123 +456 +789)))} (wrap (list (` (exec (assert! (~ (code.text (format "Pre-condition failed: " (%.code test)))) (~ test)) @@ -33,8 +35,8 @@ "Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate." "If the predicate returns #1, returns the value of the expression." "Otherwise, an error is raised." - (post i/even? - (i/+ +2 +2)))} + (post i.even? + (i.+ +2 +2)))} (with-gensyms [g!output] (wrap (list (` (let [(~ g!output) (~ expr)] (exec (assert! (~ (code.text (format "Post-condition failed: " (%.code test)))) diff --git a/stdlib/source/lux/control/pipe.lux b/stdlib/source/lux/control/pipe.lux index 929da9a46..0db424c1f 100644 --- a/stdlib/source/lux/control/pipe.lux +++ b/stdlib/source/lux/control/pipe.lux @@ -7,6 +7,8 @@ ["p" parser ["s" code (#+ Parser)]]] [data + [number + ["i" int]] [collection ["." list ("#;." fold monad)]]] [macro (#+ with-gensyms) @@ -49,8 +51,8 @@ {#.doc (doc "Branching for pipes." "Both the tests and the bodies are piped-code, and must be given inside a tuple." (|> +5 - (cond> [i/even?] [(i/* +2)] - [i/odd?] [(i/* +3)] + (cond> [i.even?] [(i.* +2)] + [i.odd?] [(i.* +3)] [(new> -1 [])])))} (with-gensyms [g!temp] (wrap (list (` (let [(~ g!temp) (~ prev)] @@ -76,7 +78,7 @@ {#.doc (doc "Loops for pipes." "Both the testing and calculating steps are pipes and must be given inside tuples." (|> +1 - (loop> [(i/< +10)] + (loop> [(i.< +10)] [inc])))} (with-gensyms [g!temp] (wrap (list (` (loop [(~ g!temp) (~ prev)] @@ -91,8 +93,8 @@ "Each steps in the monadic computation is a pipe and must be given inside a tuple." (|> +5 (do> monad - [(i/* +3)] - [(i/+ +4)] + [(i.* +3)] + [(i.+ +4)] [inc])))} (with-gensyms [g!temp] (case (list.reverse steps) @@ -114,7 +116,7 @@ "Will generate piped computations, but their results will not be used in the larger scope." (|> +5 (exec> [.nat %n log!]) - (i/* +10)))} + (i.* +10)))} (with-gensyms [g!temp] (wrap (list (` (let [(~ g!temp) (~ prev)] (exec (|> (~ g!temp) (~+ body)) @@ -125,8 +127,8 @@ {#.doc (doc "Parallel branching for pipes." "Allows to run multiple pipelines for a value and gives you a tuple of the outputs." (|> +5 - (tuple> [(i/* +10)] - [dec (i// +2)] + (tuple> [(i.* +10)] + [dec (i./ +2)] [Int/encode])) "Will become: [+50 +2 '+5']")} (with-gensyms [g!temp] diff --git a/stdlib/source/lux/data/collection/list.lux b/stdlib/source/lux/data/collection/list.lux index f03b2bf2e..abf9d3fe8 100644 --- a/stdlib/source/lux/data/collection/list.lux +++ b/stdlib/source/lux/data/collection/list.lux @@ -3,12 +3,12 @@ ["@" target] [abstract [monoid (#+ Monoid)] - ["." functor (#+ Functor)] [apply (#+ Apply)] - ["." monad (#+ do Monad)] [equivalence (#+ Equivalence)] [fold (#+ Fold)] - [predicate (#+ Predicate)]] + [predicate (#+ Predicate)] + ["." functor (#+ Functor)] + ["." monad (#+ do Monad)]] [data ["." bit] ["." product]]]) @@ -336,21 +336,22 @@ xs')] ($_ compose (sort < pre) (list x) (sort < post))))) -(template [ ] +(template [ ] [(def: #export ( from to) {#.doc "Generates an inclusive interval of values [from, to]."} (-> (List )) (cond ( to from) (list& from ( (inc from) to)) - ( to from) + ## > GT + ( from to) (list& from ( (dec from) to)) ## (= to from) (list from)))] - [i/range Int i/< i/>] - [n/range Nat n/< n/>] + [i/range Int "lux i64 <"] + [n/range Nat n/<] ) (def: #export (empty? xs) @@ -462,7 +463,7 @@ {#.doc (doc "Create list zippers with the specified number of input lists." (def: #export zip2-with (zip-with 2)) (def: #export zip3-with (zip-with 3)) - ((zip-with 2) i/+ xs ys))} + ((zip-with 2) + xs ys))} (case tokens (^ (list [_ (#.Nat num-lists)])) (if (n/> 0 num-lists) diff --git a/stdlib/source/lux/data/format/css/selector.lux b/stdlib/source/lux/data/format/css/selector.lux index 3961a9442..dd99a98c4 100644 --- a/stdlib/source/lux/data/format/css/selector.lux +++ b/stdlib/source/lux/data/format/css/selector.lux @@ -2,7 +2,9 @@ [lux (#- or and for is? not) [data ["." text - ["%" format (#+ format)]]] + ["%" format (#+ format)]] + [number + ["i" int]]] [type abstract] [macro @@ -184,7 +186,7 @@ (def: #export (formula input) (-> Formula Index) (let [(^slots [#constant #variable]) input] - (:abstraction (format (if (i/< +0 variable) + (:abstraction (format (if (i.< +0 variable) (%.int variable) (%.nat (.nat variable))) (%.int constant))))) diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux index 169d926c3..558bf2fcb 100644 --- a/stdlib/source/lux/data/format/css/value.lux +++ b/stdlib/source/lux/data/format/css/value.lux @@ -9,6 +9,7 @@ ["." maybe] [number ["." nat] + ["i" int] ["r" rev] ["f" frac]] ["." text @@ -863,14 +864,14 @@ (def: (%int value) (Format Int) - (if (i/< +0 value) + (if (i.< +0 value) (%.int value) (%.nat (.nat value)))) (template [ ] [(def: #export ( value) (-> Int (Value Time)) - (:abstraction (format (if (i/< +0 value) + (:abstraction (format (if (i.< +0 value) (%.int value) (%.nat (.nat value))) )))] @@ -1329,7 +1330,7 @@ (def: #export (z-index index) (-> Int (Value Z-Index)) - (:abstraction (if (i/< +0 index) + (:abstraction (if (i.< +0 index) (%.int index) (%.nat (.nat index))))) diff --git a/stdlib/source/lux/data/number/frac.lux b/stdlib/source/lux/data/number/frac.lux index 00e370d07..522f3c674 100644 --- a/stdlib/source/lux/data/number/frac.lux +++ b/stdlib/source/lux/data/number/frac.lux @@ -190,8 +190,8 @@ (case [(:: decode whole-part) (:: decode ("lux text concat" "+" decimal-part))] (^multi [(#try.Success whole) (#try.Success decimal)] - (i/>= +0 decimal)) - (let [sign (if (i/< +0 whole) + (//int.>= +0 decimal)) + (let [sign (if (//int.< +0 whole) -1.0 +1.0) div-power (loop [muls-left ("lux text size" decimal-part) diff --git a/stdlib/source/lux/data/number/int.lux b/stdlib/source/lux/data/number/int.lux index f0e030f5b..fa8dee78a 100644 --- a/stdlib/source/lux/data/number/int.lux +++ b/stdlib/source/lux/data/number/int.lux @@ -16,15 +16,59 @@ [// ["." nat]]) -(def: #export + (-> Int Int Int) i/+) - -(def: #export - (-> Int Int Int) i/-) - -(def: #export * (-> Int Int Int) i/*) - -(def: #export / (-> Int Int Int) i//) +(def: #export (= reference sample) + {#.doc "Int(eger) equivalence."} + (-> Int Int Bit) + ("lux i64 =" reference sample)) + +(def: #export (< reference sample) + {#.doc "Int(eger) less-than."} + (-> Int Int Bit) + ("lux i64 <" reference sample)) + +(def: #export (<= reference sample) + {#.doc "Int(eger) less-than-equal."} + (-> Int Int Bit) + (if ("lux i64 <" reference sample) + #1 + ("lux i64 =" reference sample))) + +(def: #export (> reference sample) + {#.doc "Int(eger) greater-than."} + (-> Int Int Bit) + ("lux i64 <" sample reference)) + +(def: #export (>= reference sample) + {#.doc "Int(eger) greater-than-equal."} + (-> Int Int Bit) + (if ("lux i64 <" sample reference) + #1 + ("lux i64 =" reference sample))) + +(template [ ] + [(def: #export ( left right) + {#.doc } + (-> Int Int Int) + (if ( right left) + left + right))] + + [min ..< "Int(eger) minimum."] + [max ..> "Int(eger) maximum."] + ) -(def: #export % (-> Int Int Int) i/%) +(template [ ] + [(def: #export ( param subject) + {#.doc } + (-> Int Int Int) + ( param subject))] + + [+ "lux i64 +" "Int(eger) addition."] + [- "lux i64 -" "Int(eger) substraction."] + [* "lux i64 *" "Int(eger) multiplication."] + [/ "lux i64 /" "Int(eger) division."] + [% "lux i64 %" "Int(eger) remainder."] + ) (def: #export (/% param subject) (-> Int Int [Int Int]) @@ -35,35 +79,61 @@ (def: #export (abs x) (-> Int Int) - (if (i/< +0 x) + (if (..< +0 x) (..* -1 x) x)) (def: #export (signum x) (-> Int Int) - (cond (i/= +0 x) +0 - (i/< +0 x) -1 + (cond (..= +0 x) +0 + (..< +0 x) -1 ## else +1)) (def: #export (mod param subject) (All [m] (-> Int Int Int)) (let [raw (..% param subject)] - (if (i/< +0 raw) - (let [shift (if (i/< +0 param) ..- ..+)] + (if (..< +0 raw) + (let [shift (if (..< +0 param) ..- ..+)] (|> raw (shift param))) raw))) +(def: #export even? + (-> Int Bit) + (|>> (..% +2) (..= +0))) + +(def: #export odd? + (-> Int Bit) + (|>> ..even? not)) + +(def: #export (gcd a b) + {#.doc "Greatest Common Divisor."} + (-> Int Int Int) + (case b + +0 a + _ (gcd b (..mod b a)))) + +(def: #export (lcm a b) + {#.doc "Least Common Multiple."} + (-> Int Int Int) + (case [a b] + (^or [_ +0] [+0 _]) + +0 + + _ + (|> a (/ (gcd a b)) (* b)) + )) + (def: #export frac (-> Int Frac) (|>> "lux i64 f64")) (structure: #export equivalence (Equivalence Int) - (def: = i/=)) + (def: = ..=)) (structure: #export order (Order Int) (def: &equivalence ..equivalence) - (def: < i/<)) + (def: < ..<)) (structure: #export enum (Enum Int) (def: &order ..order) @@ -82,13 +152,13 @@ [addition ..+ +0] [multiplication ..* +1] - [maximum i/max (:: ..interval bottom)] - [minimum i/min (:: ..interval top)] + [maximum ..max (:: ..interval bottom)] + [minimum ..min (:: ..interval top)] ) (def: (sign!! value) (-> Int Text) - (if (i/< +0 value) + (if (..< +0 value) "-" "+")) @@ -121,13 +191,13 @@ (template [ ] [(structure: #export (Codec Text Int) (def: (encode value) - (if (i/= +0 value) + (if (..= +0 value) "+0" (loop [input (|> value (../ ) ..abs) output (|> value (..% ) ..abs .nat maybe.assume)] - (if (i/= +0 input) + (if (..= +0 input) ("lux text concat" (sign!! value) output) (let [digit (maybe.assume ( (.nat (..% input))))] (recur (../ input) diff --git a/stdlib/source/lux/data/number/rev.lux b/stdlib/source/lux/data/number/rev.lux index b260fe085..0a9ed4b94 100644 --- a/stdlib/source/lux/data/number/rev.lux +++ b/stdlib/source/lux/data/number/rev.lux @@ -275,7 +275,7 @@ (loop [idx idx carry 0 output output] - (if (i/>= +0 (.int idx)) + (if (//int.>= +0 (.int idx)) (let [raw (|> (digits-get idx output) (n/* 5) (n/+ carry))] @@ -289,7 +289,7 @@ (loop [times power output (|> (make-digits []) (digits-put power 1))] - (if (i/>= +0 (.int times)) + (if (//int.>= +0 (.int times)) (recur (dec times) (digits-times-5! power output)) output))) @@ -299,7 +299,7 @@ (loop [idx (dec //i64.width) all-zeroes? #1 output ""] - (if (i/>= +0 (.int idx)) + (if (//int.>= +0 (.int idx)) (let [digit (digits-get idx digits)] (if (and (n/= 0 digit) all-zeroes?) @@ -318,7 +318,7 @@ (loop [idx (dec //i64.width) carry 0 output (make-digits [])] - (if (i/>= +0 (.int idx)) + (if (//int.>= +0 (.int idx)) (let [raw ($_ n/+ carry (digits-get idx param) @@ -371,7 +371,7 @@ (-> Digits Digits Digits) (loop [idx (dec //i64.width) output subject] - (if (i/>= +0 (.int idx)) + (if (//int.>= +0 (.int idx)) (recur (dec idx) (digits-sub-once! idx (digits-get idx param) output)) output))) @@ -386,7 +386,7 @@ (let [last-idx (dec //i64.width)] (loop [idx last-idx digits (make-digits [])] - (if (i/>= +0 (.int idx)) + (if (//int.>= +0 (.int idx)) (if (//i64.set? idx input) (let [digits' (digits-add (digits-power (n/- idx last-idx)) digits)] diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux index 041a3270b..c13a161ea 100644 --- a/stdlib/source/lux/macro.lux +++ b/stdlib/source/lux/macro.lux @@ -11,7 +11,8 @@ ["." name ("#@." codec equivalence)] ["." maybe] [number - ["." nat ("#@." decimal)]] + ["." nat ("#@." decimal)] + ["i" int]] ["." text ("#@." monoid equivalence)] [collection ["." list ("#@." monoid monad)]]]] @@ -730,7 +731,7 @@ ( #omit (def: (foo bar baz) (-> Int Int Int) - (i/+ bar baz))))} + (i.+ bar baz))))} (case (: (Maybe [Bit Code]) (case tokens (^ (list [_ (#.Tag ["" "omit"])] diff --git a/stdlib/source/lux/math.lux b/stdlib/source/lux/math.lux index cf3f01d9c..e27e09f86 100644 --- a/stdlib/source/lux/math.lux +++ b/stdlib/source/lux/math.lux @@ -4,7 +4,7 @@ [data [number ["." nat] - ["." int]]]]) + ["i" int]]]]) (template [ ] [(def: #export @@ -168,7 +168,6 @@ ))] [Nat nat.mod n/gcd n/lcm 0 n/* n// n/-] - [Int int.mod i/gcd i/lcm +0 i/* i// i/-] ) ## Hyperbolic functions diff --git a/stdlib/source/lux/math/infix.lux b/stdlib/source/lux/math/infix.lux index 97773f276..b31d77fd8 100644 --- a/stdlib/source/lux/math/infix.lux +++ b/stdlib/source/lux/math/infix.lux @@ -7,6 +7,8 @@ ["s" code (#+ Parser)]]] [data ["." product] + [number + ["i" int]] [collection ["." list ("#;." fold)]]] [macro @@ -77,9 +79,9 @@ (syntax: #export (infix {expr infix^}) {#.doc (doc "Infix math syntax." - (infix [x i/* +10]) - (infix [[x i/+ y] i/* [x i/- y]]) - (infix [sin [x i/+ y]]) + (infix [x i.* +10]) + (infix [[x i.+ y] i.* [x i.- y]]) + (infix [sin [x i.+ y]]) (infix [[x n/< y] and [y n/< z]]) (infix [#and x n/< y n/< z]) (infix [(n/* 3 9) gcd 450]) diff --git a/stdlib/source/lux/math/modular.lux b/stdlib/source/lux/math/modular.lux index 2ec37ed2a..882162d5d 100644 --- a/stdlib/source/lux/math/modular.lux +++ b/stdlib/source/lux/math/modular.lux @@ -11,7 +11,7 @@ ["s" code]]] [data [number - ["." int ("#@." decimal)]] + ["i" int ("#@." decimal)]] ["." text ("#@." monoid)]] [type abstract] @@ -29,7 +29,7 @@ (def: #export (from-int value) (Ex [m] (-> Int (Try (Modulus m)))) - (if (i/= +0 value) + (if (i.= +0 value) (ex.throw zero-cannot-be-a-modulus []) (#try.Success (:abstraction value)))) @@ -40,20 +40,20 @@ (exception: #export [m] (incorrect-modulus {modulus (Modulus m)} {parsed Int}) - (ex.report ["Expected" (int@encode (to-int modulus))] - ["Actual" (int@encode parsed)])) + (ex.report ["Expected" (i@encode (to-int modulus))] + ["Actual" (i@encode parsed)])) (exception: #export [rm sm] (cannot-equalize-moduli {reference (Modulus rm)} {sample (Modulus sm)}) - (ex.report ["Reference" (int@encode (to-int reference))] - ["Sample" (int@encode (to-int sample))])) + (ex.report ["Reference" (i@encode (to-int reference))] + ["Sample" (i@encode (to-int sample))])) (def: #export (congruent? modulus reference sample) (All [m] (-> (Modulus m) Int Int Bit)) (|> sample - (i/- reference) - (i/% (to-int modulus)) - (i/= +0))) + (i.- reference) + (i.% (to-int modulus)) + (i.= +0))) (syntax: #export (modulus {modulus s.int}) (case (from-int modulus) @@ -65,7 +65,7 @@ (def: intL (Parser Int) - (p.codec int.decimal + (p.codec i.decimal (l.and (l.one-of "-+") (l.many l.decimal)))) (abstract: #export (Mod m) @@ -77,7 +77,7 @@ (def: #export (mod modulus) (All [m] (-> (Modulus m) (-> Int (Mod m)))) (function (_ value) - (:abstraction {#remainder (int.mod (to-int modulus) value) + (:abstraction {#remainder (i.mod (to-int modulus) value) #modulus modulus}))) (def: #export (un-mod modular) @@ -92,22 +92,22 @@ (def: (encode modular) (let [[remainder modulus] (:representation modular)] ($_ text@compose - (int@encode remainder) + (i@encode remainder) separator - (int@encode (to-int modulus))))) + (i@encode (to-int modulus))))) (def: decode (l.run (do p.monad [[remainder _ _modulus] ($_ p.and intL (l.this separator) intL) _ (p.assert (ex.construct incorrect-modulus [modulus _modulus]) - (i/= (to-int modulus) _modulus))] + (i.= (to-int modulus) _modulus))] (wrap (mod modulus remainder)))))) (def: #export (equalize reference sample) (All [r s] (-> (Mod r) (Mod s) (Try (Mod r)))) (let [[reference reference-modulus] (:representation reference) [sample sample-modulus] (:representation sample)] - (if (i/= (to-int reference-modulus) + (if (i.= (to-int reference-modulus) (to-int sample-modulus)) (#try.Success (:abstraction {#remainder sample #modulus reference-modulus})) @@ -120,11 +120,11 @@ [sample _] (:representation sample)] ( reference sample)))] - [= i/=] - [< i/<] - [<= i/<=] - [> i/>] - [>= i/>=] + [= i.=] + [< i.<] + [<= i.<=] + [> i.>] + [>= i.>=] ) (template [ ] @@ -134,21 +134,21 @@ [subject _] (:representation subject)] (:abstraction {#remainder (|> subject ( param) - (int.mod (to-int modulus))) + (i.mod (to-int modulus))) #modulus modulus})))] - [+ i/+] - [- i/-] - [* i/*] + [+ i.+] + [- i.-] + [* i.*] ) - (def: (i/gcd+ a b) + (def: (gcd+ a b) (-> Int Int [Int Int Int]) - (if (i/= +0 a) + (if (i.= +0 a) [+0 +1 b] - (let [[ak bk gcd] (i/gcd+ (i/% a b) a)] - [(i/- (i/* ak - (i// a b)) + (let [[ak bk gcd] (gcd+ (i.% a b) a)] + [(i.- (i.* ak + (i./ a b)) bk) ak gcd]))) @@ -157,8 +157,8 @@ (All [m] (-> (Mod m) (Maybe (Mod m)))) (let [[value modulus] (:representation modular) _modulus (to-int modulus) - [vk mk gcd] (i/gcd+ value _modulus) - co-prime? (i/= +1 gcd)] + [vk mk gcd] (gcd+ value _modulus) + co-prime? (i.= +1 gcd)] (if co-prime? (#.Some (mod modulus vk)) #.None))) diff --git a/stdlib/source/lux/math/random.lux b/stdlib/source/lux/math/random.lux index cf82955ca..bda49fab0 100644 --- a/stdlib/source/lux/math/random.lux +++ b/stdlib/source/lux/math/random.lux @@ -10,7 +10,7 @@ ["." maybe] [number (#+ hex) ["." i64] - ["." int] + ["i" int] ["r" ratio] ["c" complex] ["f" frac]] @@ -117,10 +117,10 @@ (def: #export safe-frac (Random Frac) (let [mantissa-range (.int (i64.left-shift 53 1)) - mantissa-max (int.frac (dec mantissa-range))] + mantissa-max (i.frac (dec mantissa-range))] (:: ..monad map - (|>> (i/% mantissa-range) - int.frac + (|>> (i.% mantissa-range) + i.frac (f./ mantissa-max)) ..int))) diff --git a/stdlib/source/lux/target/js.lux b/stdlib/source/lux/target/js.lux index 47c8d9d8c..b66f40e05 100644 --- a/stdlib/source/lux/target/js.lux +++ b/stdlib/source/lux/target/js.lux @@ -4,6 +4,7 @@ [pipe (#+ case>)]] [data [number + ["i" int] ["f" frac]] ["." text ["%" format (#+ format)]] @@ -247,7 +248,7 @@ (def: #export (int value) (-> Int Literal) - (:abstraction (.if (i/< +0 value) + (:abstraction (.if (i.< +0 value) (%.int value) (%.nat (.nat value))))) diff --git a/stdlib/source/lux/target/jvm/encoding/signed.lux b/stdlib/source/lux/target/jvm/encoding/signed.lux index c5a7776b3..fb684847b 100644 --- a/stdlib/source/lux/target/jvm/encoding/signed.lux +++ b/stdlib/source/lux/target/jvm/encoding/signed.lux @@ -5,7 +5,8 @@ [order (#+ Order)]] [data [number - ["." i64]] + ["." i64] + ["i" int]] [format [".F" binary (#+ Writer)]]] [macro @@ -24,14 +25,14 @@ (structure: #export equivalence (All [brand] (Equivalence (Signed brand))) (def: (= reference sample) - (i/= (:representation reference) (:representation sample)))) + (i.= (:representation reference) (:representation sample)))) (structure: #export order (All [brand] (Order (Signed brand))) (def: &equivalence ..equivalence) (def: (< reference sample) - (i/< (:representation reference) (:representation sample)))) + (i.< (:representation reference) (:representation sample)))) (template [ <+>] [(with-expansions [ (template.identifier [ "'"])] @@ -54,7 +55,7 @@ (let [limit (|> (n/* i64.bits-per-byte) i64.mask .nat)] (:abstraction (i64.and limit - (i/+ (:representation parameter) + (i.+ (:representation parameter) (:representation subject))))))] [1 S1 s1-bytes s1 max-s1 s1/+] diff --git a/stdlib/source/lux/target/jvm/instruction.lux b/stdlib/source/lux/target/jvm/instruction.lux index 8ae42752f..ac4732e12 100644 --- a/stdlib/source/lux/target/jvm/instruction.lux +++ b/stdlib/source/lux/target/jvm/instruction.lux @@ -13,7 +13,8 @@ [text ["%" format (#+ format)]] [number - ["." nat]] + ["." nat] + ["i" int]] [collection ["." list ("#@." functor fold)] ["." dictionary (#+ Dictionary)]]]] @@ -366,7 +367,7 @@ (-> Address Address (Either Jump Big-Jump)) (let [jump (.int (n/- @to @from)) big? (n/> (//unsigned.nat //unsigned.max-u2) - (.nat (i/* (if (i/>= +0 jump) + (.nat (i.* (if (i.>= +0 jump) +1 -1) jump)))] diff --git a/stdlib/source/lux/target/lua.lux b/stdlib/source/lux/target/lua.lux index 7aa62345f..c969cc790 100644 --- a/stdlib/source/lux/target/lua.lux +++ b/stdlib/source/lux/target/lua.lux @@ -6,6 +6,7 @@ ["s" code]]] [data [number + ["i" int] ["f" frac]] ["." text ["%" format (#+ format)]] @@ -73,7 +74,7 @@ (def: #export (int value) (-> Int Literal) - (:abstraction (.if (i/< +0 value) + (:abstraction (.if (i.< +0 value) (%.int value) (%.nat (.nat value))))) diff --git a/stdlib/source/lux/time/date.lux b/stdlib/source/lux/time/date.lux index a495cc9fa..0b40932ef 100644 --- a/stdlib/source/lux/time/date.lux +++ b/stdlib/source/lux/time/date.lux @@ -13,7 +13,7 @@ ["." maybe] [number ["." nat ("#@." decimal)] - ["." int ("#@." decimal)]] + ["i" int ("#@." decimal)]] ["." text ("#@." monoid)] [collection ["." row (#+ Row row)]]]] @@ -29,7 +29,7 @@ (structure: #export equivalence (Equivalence Date) (def: (= reference sample) - (and (i/= (get@ #year reference) + (and (i.= (get@ #year reference) (get@ #year sample)) (:: //month.equivalence = (get@ #month reference) @@ -40,9 +40,9 @@ (structure: #export order (Order Date) (def: &equivalence ..equivalence) (def: (< reference sample) - (or (i/< (get@ #year reference) + (or (i.< (get@ #year reference) (get@ #year sample)) - (and (i/= (get@ #year reference) + (and (i.= (get@ #year reference) (get@ #year sample)) (or (:: //month.order < (get@ #month reference) @@ -57,15 +57,15 @@ (def: (pad value) (-> Int Text) (let [digits (nat@encode (.nat value))] - (if (i/< +10 value) + (if (i.< +10 value) (text@compose "0" digits) digits))) (def: (encode [year month day]) (-> Date Text) ($_ text@compose - (if (i/< +0 year) - (int@encode year) + (if (i.< +0 year) + (i@encode year) (nat@encode (.nat year))) "-" (pad (|> month //month.number inc .int)) "-" @@ -82,7 +82,7 @@ #.None +1)]] - (wrap (i/* signum (.int raw-year))))) + (wrap (i.* signum (.int raw-year))))) (def: lex-section (Parser Int) @@ -90,9 +90,9 @@ (def: (leap-years year) (-> Int Int) - (|> (i// +4 year) - (i/- (i// +100 year)) - (i/+ (i// +400 year)))) + (|> (i./ +4 year) + (i.- (i./ +100 year)) + (i.+ (i./ +400 year)))) (def: normal-months (Row Nat) @@ -107,7 +107,7 @@ (def: (divisible? factor input) (-> Int Int Bit) - (|> input (i/% factor) (i/= +0))) + (|> input (i.% factor) (i.= +0))) (def: (leap-year? year) (-> Int Bit) @@ -145,8 +145,8 @@ _ (l.this "-") utc-day lex-section _ (p.assert "Invalid day." - (and (i/>= +1 utc-day) - (i/<= (.int month-days) utc-day)))] + (and (i.>= +1 utc-day) + (i.<= (.int month-days) utc-day)))] (wrap {#year utc-year #month month #day (.nat (.dec utc-day))}))) diff --git a/stdlib/source/lux/time/duration.lux b/stdlib/source/lux/time/duration.lux index a82ae6bed..58d06ee2d 100644 --- a/stdlib/source/lux/time/duration.lux +++ b/stdlib/source/lux/time/duration.lux @@ -13,7 +13,7 @@ [data [number ["." nat ("#@." decimal)] - ["." int]] + ["i" int]] ["." text ("#@." monoid)]] [type abstract]]) @@ -35,8 +35,8 @@ (-> Duration Duration Duration) (:abstraction ( (:representation param) (:representation subject))))] - [merge i/+] - [frame i/%] + [merge i.+] + [frame i.%] ) (template [ ] @@ -44,13 +44,13 @@ (-> Nat Duration Duration) (|>> :representation ( (.int scalar)) :abstraction))] - [scale-up i/*] - [scale-down i//] + [scale-up i.*] + [scale-down i./] ) (def: #export inverse (-> Duration Duration) - (|>> :representation (i/* -1) :abstraction)) + (|>> :representation (i.* -1) :abstraction)) (def: #export (difference from to) (-> Duration Duration Duration) @@ -58,25 +58,25 @@ (def: #export (query param subject) (-> Duration Duration Int) - (i// (:representation param) (:representation subject))) + (i./ (:representation param) (:representation subject))) (structure: #export equivalence (Equivalence Duration) (def: (= param subject) - (i/= (:representation param) (:representation subject)))) + (i.= (:representation param) (:representation subject)))) (structure: #export order (Order Duration) (def: &equivalence ..equivalence) (def: (< param subject) - (i/< (:representation param) (:representation subject)))) + (i.< (:representation param) (:representation subject)))) (template [ ] [(def: #export (-> Duration Bit) (|>> :representation ( +0)))] - [positive? i/>] - [negative? i/<] - [neutral? i/=] + [positive? i.>] + [negative? i.<] + [neutral? i.=] ) ) @@ -106,7 +106,7 @@ (let [signed? (negative? duration) [days time-left] [(query day duration) (frame day duration)] days (if signed? - (int.abs days) + (i.abs days) days) time-left (if signed? (..inverse time-left) @@ -117,9 +117,9 @@ millis (to-millis time-left)] ($_ text@compose (if signed? "-" "+") - (if (i/= +0 days) "" (text@compose (nat@encode (.nat days)) "D")) - (if (i/= +0 hours) "" (text@compose (nat@encode (.nat hours)) "h")) - (if (i/= +0 minutes) "" (text@compose (nat@encode (.nat minutes)) "m")) - (if (i/= +0 seconds) "" (text@compose (nat@encode (.nat seconds)) "s")) - (if (i/= +0 millis) "" (text@compose (nat@encode (.nat millis)) "ms")) + (if (i.= +0 days) "" (text@compose (nat@encode (.nat days)) "D")) + (if (i.= +0 hours) "" (text@compose (nat@encode (.nat hours)) "h")) + (if (i.= +0 minutes) "" (text@compose (nat@encode (.nat minutes)) "m")) + (if (i.= +0 seconds) "" (text@compose (nat@encode (.nat seconds)) "s")) + (if (i.= +0 millis) "" (text@compose (nat@encode (.nat millis)) "ms")) )))) diff --git a/stdlib/source/lux/time/instant.lux b/stdlib/source/lux/time/instant.lux index b26707173..892b8df5b 100644 --- a/stdlib/source/lux/time/instant.lux +++ b/stdlib/source/lux/time/instant.lux @@ -14,7 +14,7 @@ [data ["." maybe] [number - ["." int ("#@." decimal)]] + ["i" int ("#@." decimal)]] ["." text ("#@." monoid)] [collection ["." list ("#@." fold)] @@ -41,11 +41,11 @@ (def: #export (span from to) (-> Instant Instant duration.Duration) - (duration.from-millis (i/- (:representation from) (:representation to)))) + (duration.from-millis (i.- (:representation from) (:representation to)))) (def: #export (shift duration instant) (-> duration.Duration Instant Instant) - (:abstraction (i/+ (duration.to-millis duration) (:representation instant)))) + (:abstraction (i.+ (duration.to-millis duration) (:representation instant)))) (def: #export (relative instant) (-> Instant duration.Duration) @@ -57,18 +57,18 @@ (structure: #export equivalence (Equivalence Instant) (def: (= param subject) - (:: int.equivalence = (:representation param) (:representation subject)))) + (:: i.equivalence = (:representation param) (:representation subject)))) (structure: #export order (Order Instant) (def: &equivalence ..equivalence) (def: (< param subject) - (:: int.order < (:representation param) (:representation subject)))) + (:: i.order < (:representation param) (:representation subject)))) (`` (structure: #export enum (Enum Instant) (def: &order ..order) (~~ (template [] [(def: - (|>> :representation (:: int.enum ) :abstraction))] + (|>> :representation (:: i.enum ) :abstraction))] [succ] [pred] )))) @@ -82,7 +82,7 @@ ## Codec::encode (def: (divisible? factor input) (-> Int Int Bit) - (|> input (i/% factor) (i/= +0))) + (|> input (i.% factor) (i.= +0))) (def: (leap-year? year) (-> Int Bit) @@ -99,7 +99,7 @@ (let [year (if (leap-year? reference) duration.leap-year duration.normal-year)] - (if (i/= +0 (duration.query year time-left)) + (if (i.= +0 (duration.query year time-left)) [reference time-left] (if (order.>= duration.order duration.empty time-left) (recur (inc reference) (duration.merge (duration.inverse year) time-left)) @@ -122,14 +122,14 @@ (if (order.>= duration.order duration.empty time) (row@fold (function (_ month-days [current-month time-left]) (let [month-duration (duration.scale-up month-days duration.day)] - (if (i/= +0 (duration.query month-duration time-left)) + (if (i.= +0 (duration.query month-duration time-left)) [current-month time-left] [(inc current-month) (duration.merge (duration.inverse month-duration) time-left)]))) [0 time] months) (row@fold (function (_ month-days [current-month time-left]) (let [month-duration (duration.scale-up month-days duration.day)] - (if (i/= +0 (duration.query month-duration time-left)) + (if (i.= +0 (duration.query month-duration time-left)) [current-month time-left] [(dec current-month) (duration.merge month-duration time-left)]))) [11 time] @@ -137,9 +137,9 @@ (def: (pad value) (-> Int Text) - (if (i/< +10 value) - (text@compose "0" (int@encode value)) - (int@encode value))) + (if (i.< +10 value) + (text@compose "0" (i@encode value)) + (i@encode value))) (def: (adjust-negative space duration) (-> duration.Duration duration.Duration duration.Duration) @@ -149,11 +149,11 @@ (def: (encode-millis millis) (-> Int Text) - (cond (i/= +0 millis) "" - (i/< +10 millis) ($_ text@compose ".00" (int@encode millis)) - (i/< +100 millis) ($_ text@compose ".0" (int@encode millis)) - ## (i/< +1,000 millis) - ($_ text@compose "." (int@encode millis)))) + (cond (i.= +0 millis) "" + (i.< +10 millis) ($_ text@compose ".00" (i@encode millis)) + (i.< +100 millis) ($_ text@compose ".0" (i@encode millis)) + ## (i.< +1,000 millis) + ($_ text@compose "." (i@encode millis)))) (def: seconds-per-day Int (duration.query duration.second duration.day)) (def: days-up-to-epoch Int +719468) @@ -162,35 +162,35 @@ (-> Instant [[Int Int Int] duration.Duration]) (let [offset (relative instant) seconds (duration.query duration.second offset) - z (|> seconds (i// seconds-per-day) (i/+ days-up-to-epoch)) - era (i// +146097 - (if (i/>= +0 z) + z (|> seconds (i./ seconds-per-day) (i.+ days-up-to-epoch)) + era (i./ +146097 + (if (i.>= +0 z) z - (i/- +146096 z))) - days-of-era (|> z (i/- (i/* +146097 era))) + (i.- +146096 z))) + days-of-era (|> z (i.- (i.* +146097 era))) years-of-era (|> days-of-era - (i/- (i// +1460 days-of-era)) - (i/+ (i// +36524 days-of-era)) - (i/- (i// +146096 days-of-era)) - (i// +365)) - year (|> years-of-era (i/+ (i/* +400 era))) + (i.- (i./ +1460 days-of-era)) + (i.+ (i./ +36524 days-of-era)) + (i.- (i./ +146096 days-of-era)) + (i./ +365)) + year (|> years-of-era (i.+ (i.* +400 era))) days-of-year (|> days-of-era - (i/- (|> (i/* +365 years-of-era) - (i/+ (i// +4 years-of-era)) - (i/- (i// +100 years-of-era))))) + (i.- (|> (i.* +365 years-of-era) + (i.+ (i./ +4 years-of-era)) + (i.- (i./ +100 years-of-era))))) day-time (duration.frame duration.day offset) days-of-year (if (order.>= duration.order duration.empty day-time) days-of-year (dec days-of-year)) - mp (|> days-of-year (i/* +5) (i/+ +2) (i// +153)) + mp (|> days-of-year (i.* +5) (i.+ +2) (i./ +153)) day (|> days-of-year - (i/- (|> mp (i/* +153) (i/+ +2) (i// +5))) - (i/+ +1)) + (i.- (|> mp (i.* +153) (i.+ +2) (i./ +5))) + (i.+ +1)) month (|> mp - (i/+ (if (i/< +10 mp) + (i.+ (if (i.< +10 mp) +3 -9))) - year (if (i/<= +2 month) + year (if (i.<= +2 month) (inc year) year)] [[year month day] @@ -206,7 +206,7 @@ [hours day-time] [(duration.query duration.hour day-time) (duration.frame duration.hour day-time)] [minutes day-time] [(duration.query duration.minute day-time) (duration.frame duration.minute day-time)] [seconds millis] [(duration.query duration.second day-time) (duration.frame duration.second day-time)]] - ($_ text@compose (int@encode year) "-" (pad month) "-" (pad day) "T" + ($_ text@compose (i@encode year) "-" (pad month) "-" (pad day) "T" (pad hours) ":" (pad minutes) ":" (pad seconds) (|> millis (adjust-negative duration.second) @@ -219,28 +219,28 @@ (Parser Int) (do p.monad [sign (p.or (l.this "-") (l.this "+")) - raw-year (p.codec int.decimal (l.many l.decimal)) + raw-year (p.codec i.decimal (l.many l.decimal)) #let [signum (case sign (#.Left _) -1 (#.Right _) +1)]] - (wrap (i/* signum raw-year)))) + (wrap (i.* signum raw-year)))) (def: lex-section (Parser Int) - (p.codec int.decimal (l.exactly 2 l.decimal))) + (p.codec i.decimal (l.exactly 2 l.decimal))) (def: lex-millis (Parser Int) (p.either (|> (l.at-most 3 l.decimal) - (p.codec int.decimal) + (p.codec i.decimal) (p.after (l.this "."))) (:: p.monad wrap +0))) (def: (leap-years year) (-> Int Int) - (|> (i// +4 year) - (i/- (i// +100 year)) - (i/+ (i// +400 year)))) + (|> (i./ +4 year) + (i.- (i./ +100 year)) + (i.+ (i./ +400 year)))) ## Based on: https://stackoverflow.com/a/3309340/6823464 ## (def: lex-instant @@ -250,8 +250,8 @@ ## _ (l.this "-") ## utc-month lex-section ## _ (p.assert "Invalid month." -## (and (i/>= +1 utc-month) -## (i/<= +12 utc-month))) +## (and (i.>= +1 utc-month) +## (i.<= +12 utc-month))) ## #let [months (if (leap-year? utc-year) ## leap-year-months ## normal-months) @@ -261,37 +261,37 @@ ## _ (l.this "-") ## utc-day lex-section ## _ (p.assert "Invalid day." -## (and (i/>= +1 utc-day) -## (i/<= (.int month-days) utc-day))) +## (and (i.>= +1 utc-day) +## (i.<= (.int month-days) utc-day))) ## _ (l.this "T") ## utc-hour lex-section ## _ (p.assert "Invalid hour." -## (and (i/>= +0 utc-hour) -## (i/<= +23 utc-hour))) +## (and (i.>= +0 utc-hour) +## (i.<= +23 utc-hour))) ## _ (l.this ":") ## utc-minute lex-section ## _ (p.assert "Invalid minute." -## (and (i/>= +0 utc-minute) -## (i/<= +59 utc-minute))) +## (and (i.>= +0 utc-minute) +## (i.<= +59 utc-minute))) ## _ (l.this ":") ## utc-second lex-section ## _ (p.assert "Invalid second." -## (and (i/>= +0 utc-second) -## (i/<= +59 utc-second))) +## (and (i.>= +0 utc-second) +## (i.<= +59 utc-second))) ## utc-millis lex-millis ## _ (l.this "Z") -## #let [years-since-epoch (i/- epoch-year utc-year) -## previous-leap-days (i/- (leap-years epoch-year) +## #let [years-since-epoch (i.- epoch-year utc-year) +## previous-leap-days (i.- (leap-years epoch-year) ## (leap-years (dec utc-year))) -## year-days-so-far (|> (i/* +365 years-since-epoch) -## (i/+ previous-leap-days)) +## year-days-so-far (|> (i.* +365 years-since-epoch) +## (i.+ previous-leap-days)) ## month-days-so-far (|> months ## row.to-list ## (list.take (.nat (dec utc-month))) ## (list@fold n/+ 0)) ## total-days (|> year-days-so-far -## (i/+ (.int month-days-so-far)) -## (i/+ (dec utc-day)))]] +## (i.+ (.int month-days-so-far)) +## (i.+ (dec utc-day)))]] ## (wrap (|> epoch ## (shift (duration.scale-up total-days duration.day)) ## (shift (duration.scale-up utc-hour duration.hour)) @@ -351,9 +351,9 @@ ## 1970/01/01 was a Thursday y1970m0d0 +4] (case (|> y1970m0d0 - (i/+ days) (i/% +7) + (i.+ days) (i.% +7) ## This is done to turn negative days into positive days. - (i/+ +7) (i/% +7)) + (i.+ +7) (i.% +7)) +0 #day.Sunday +1 #day.Monday +2 #day.Tuesday diff --git a/stdlib/source/lux/tool/compiler/phase/generation/php/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/php/case.lux index abd31b7f2..fedfff63f 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/php/case.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/php/case.lux @@ -8,6 +8,8 @@ ["." product] ["." text ["%" format (#+ format)]] + [number + ["i" int]] [collection ["." list ("#@." functor fold)] ["." set]]] @@ -104,7 +106,7 @@ (-> Nat Statement) (_.; (_.array-splice/3 [@cursor (_.int +0) - (_.int (i/* -1 (.int pops)))]))) + (_.int (i.* -1 (.int pops)))]))) (template [ ] [(def: ( simple? idx) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux index 80a142b37..9589e3336 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux @@ -7,6 +7,8 @@ [data ["." text ["%" format (#+ format)]] + [number + ["i" int]] [collection ["." list ("#@." functor fold)] ["." set]]] @@ -100,7 +102,7 @@ (def: (multi-pop! pops) (-> Nat (Statement Any)) - (_.delete (_.slice-from (_.int (i/* -1 (.int pops))) @cursor))) + (_.delete (_.slice-from (_.int (i.* -1 (.int pops))) @cursor))) (template [ ] [(def: ( simple? idx) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/ruby/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/ruby/case.lux index 41e55749e..695485a16 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/ruby/case.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/ruby/case.lux @@ -6,6 +6,8 @@ ["ex" exception (#+ exception:)]] [data ["." text] + [number + ["i" int]] [collection ["." list ("#@." functor fold)] ["." set]]] @@ -100,7 +102,7 @@ (def: (multi-pop! pops) (-> Nat (Statement Any)) - (_.statement (_.do "slice!" (list (_.int (i/* -1 (.int pops))) + (_.statement (_.do "slice!" (list (_.int (i.* -1 (.int pops))) (_.int (.int pops))) @cursor))) diff --git a/stdlib/source/lux/tool/compiler/synthesis.lux b/stdlib/source/lux/tool/compiler/synthesis.lux index de91d38a7..463affb73 100644 --- a/stdlib/source/lux/tool/compiler/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/synthesis.lux @@ -10,6 +10,7 @@ ["." text ("#;." equivalence) ["%" format (#+ Format format)]] [number + ["i" int] ["f" frac]] [collection ["." list ("#;." functor)] @@ -400,7 +401,7 @@ [#Text text;= %.text]) [(#I64 reference') (#I64 sample')] - (i/= (.int reference') (.int sample')) + (i.= (.int reference') (.int sample')) _ false))) diff --git a/stdlib/source/lux/type/unit.lux b/stdlib/source/lux/type/unit.lux index dbf356488..caf510403 100644 --- a/stdlib/source/lux/type/unit.lux +++ b/stdlib/source/lux/type/unit.lux @@ -11,6 +11,7 @@ ["s" code (#+ Parser)]]] [data [number + ["i" int] ["." ratio (#+ Ratio)]] [text ["%" format (#+ format)]]] @@ -86,10 +87,10 @@ (s.tuple (do p.monad [numerator s.int _ (p.assert (format "Numerator must be positive: " (%.int numerator)) - (i/> +0 numerator)) + (i.> +0 numerator)) denominator s.int _ (p.assert (format "Denominator must be positive: " (%.int denominator)) - (i/> +0 denominator))] + (i.> +0 denominator))] (wrap [(.nat numerator) (.nat denominator)])))) (syntax: #export (scale: @@ -105,13 +106,13 @@ (..Scale (~ g!scale)) (def: (~' scale) (|>> ..out - (i/* (~ (code.int (.int numerator)))) - (i// (~ (code.int (.int denominator)))) + (i.* (~ (code.int (.int numerator)))) + (i./ (~ (code.int (.int denominator)))) ..in)) (def: (~' de-scale) (|>> ..out - (i/* (~ (code.int (.int denominator)))) - (i// (~ (code.int (.int numerator)))) + (i.* (~ (code.int (.int denominator)))) + (i./ (~ (code.int (.int numerator)))) ..in)) (def: (~' ratio) [(~ (code.nat numerator)) (~ (code.nat denominator))]))) @@ -122,16 +123,16 @@ (All [unit] (-> (Qty unit) (Qty unit) (Qty unit))) (|> subject out ( (out param)) in))] - [u/+ i/+] - [u/- i/-] + [u/+ i.+] + [u/- i.-] ) (def: #export (u// param subject) (All [p s] (-> (Qty p) (Qty s) (|> (Qty s) (Per (Qty p))))) (function (_ input) (|> (out subject) - (i/* (out input)) - (i// (out param)) + (i.* (out input)) + (i./ (out param)) in))) (def: #export (u/* param subject) @@ -139,7 +140,7 @@ (function (_ input) (|> subject out - (i/* (out (input param))) + (i.* (out (input param))) in))) (def: #export (re-scale from to quantity) @@ -148,8 +149,8 @@ (:: to ratio))] (|> quantity out - (i/* (.int numerator)) - (i// (.int denominator)) + (i.* (.int numerator)) + (i./ (.int denominator)) in))) (scale: #export Kilo [+1 +1,000]) @@ -167,13 +168,13 @@ (structure: #export equivalence (All [unit] (Equivalence (Qty unit))) (def: (= reference sample) - (i/= (out reference) (out sample)))) + (i.= (out reference) (out sample)))) (structure: #export order (All [unit] (Order (Qty unit))) (def: &equivalence ..equivalence) (def: (< reference sample) - (i/< (out reference) (out sample)))) + (i.< (out reference) (out sample)))) (structure: #export enum (All [unit] (Enum (Qty unit))) (def: &order ..order) diff --git a/stdlib/source/lux/world/db/sql.lux b/stdlib/source/lux/world/db/sql.lux index 13d6c8b6f..f9b6c1e1d 100644 --- a/stdlib/source/lux/world/db/sql.lux +++ b/stdlib/source/lux/world/db/sql.lux @@ -3,6 +3,8 @@ [control [monad (#+ do)]] [data + [number + ["i" int]] ["." text ("#;." equivalence) ["%" format (#+ format)]] [collection @@ -121,7 +123,7 @@ (def: #export (int value) (-> Int Literal) - (..literal (if (i/< +0 value) + (..literal (if (i.< +0 value) (%.int value) (%.nat (.nat value))))) diff --git a/stdlib/source/lux/world/file.lux b/stdlib/source/lux/world/file.lux index 805a6ca05..0318dcb12 100644 --- a/stdlib/source/lux/world/file.lux +++ b/stdlib/source/lux/world/file.lux @@ -19,7 +19,7 @@ ["." text ["%" format (#+ format)]] [number - ["." int] + ["i" int] ["f" frac]] [collection ["." array (#+ Array)] @@ -261,7 +261,7 @@ stream (FileInputStream::new file) bytes-read (InputStream::read data stream) _ (java/lang/AutoCloseable::close stream)] - (if (i/= size bytes-read) + (if (i.= size bytes-read) (wrap data) (io.io (exception.throw cannot-read-all-data path))))))) @@ -474,7 +474,7 @@ (def: modify (..can-modify (function (modify time-stamp) - (io.io (let [when (|> time-stamp instant.relative duration.to-millis int.frac)] + (io.io (let [when (|> time-stamp instant.relative duration.to-millis i.frac)] (Fs::utimesSync [path when when] (!fs))))))) (def: delete diff --git a/stdlib/source/lux/world/net/http/cookie.lux b/stdlib/source/lux/world/net/http/cookie.lux index aac87c822..29e7fb6ce 100644 --- a/stdlib/source/lux/world/net/http/cookie.lux +++ b/stdlib/source/lux/world/net/http/cookie.lux @@ -6,6 +6,8 @@ ["p" parser ("#;." monad) ["l" text (#+ Parser)]]] [data + [number + ["i" int]] [text ["%" format (#+ format)]] [format @@ -31,7 +33,7 @@ (def: #export (max-age duration) (-> Duration Directive) (let [seconds (duration.query duration.second duration)] - (..directive (format "Max-Age=" (if (i/< +0 seconds) + (..directive (format "Max-Age=" (if (i.< +0 seconds) (%.int seconds) (%.nat (.nat seconds))))))) diff --git a/stdlib/source/program/licentia/input.lux b/stdlib/source/program/licentia/input.lux index 6d64515cf..0fb4b5f84 100644 --- a/stdlib/source/program/licentia/input.lux +++ b/stdlib/source/program/licentia/input.lux @@ -10,7 +10,7 @@ [format ["." json (#+ Reader)]] [number - ["." int] + ["i" int] ["f" frac]]]] [// [license (#+ Identification @@ -45,9 +45,9 @@ #let [amountI (f.int amountF)] _ (parser.assert (ex.construct cannot-use-fractional-amount amountF) (f.= amountF - (int.frac amountI))) + (i.frac amountI))) _ (parser.assert (ex.construct cannot-use-negative-amount amountI) - (i/> +0 amountI))] + (i.> +0 amountI))] (wrap (.nat amountI)))) (exception: #export (invalid-period {period (Period Nat)}) diff --git a/stdlib/source/spec/compositor/generation/common.lux b/stdlib/source/spec/compositor/generation/common.lux index e2e6199d9..b7a114893 100644 --- a/stdlib/source/spec/compositor/generation/common.lux +++ b/stdlib/source/spec/compositor/generation/common.lux @@ -10,7 +10,7 @@ ["." bit ("#@." equivalence)] [number ["." i64] - ["." int] + ["i" int] ["f" frac]] ["." text ("#@." equivalence) ["%" format (#+ format)]] @@ -88,7 +88,7 @@ false) (let [subject ])))] - ["lux i64 f64" Frac int.frac f.= subject] + ["lux i64 f64" Frac i.frac f.= subject] ["lux i64 char" Text (|>> (:coerce Nat) text.from-code) text@= (|> subject (:coerce Nat) (n/% (i64.left-shift 8 1)) @@ -105,19 +105,19 @@ (#try.Failure _) false)))] - ["lux i64 +" i/+ Int i/=] - ["lux i64 -" i/- Int i/=] - ["lux i64 *" i/* Int i/=] - ["lux i64 /" i// Int i/=] - ["lux i64 %" i/% Int i/=] - ["lux i64 =" i/= Bit bit@=] - ["lux i64 <" i/< Bit bit@=] + ["lux i64 +" i.+ Int i.=] + ["lux i64 -" i.- Int i.=] + ["lux i64 *" i.* Int i.=] + ["lux i64 /" i./ Int i.=] + ["lux i64 %" i.% Int i.=] + ["lux i64 =" i.= Bit bit@=] + ["lux i64 <" i.< Bit bit@=] )) )))) (def: simple-frac (Random Frac) - (|> r.nat (:: r.monad map (|>> (n/% 1000) .int int.frac)))) + (|> r.nat (:: r.monad map (|>> (n/% 1000) .int i.frac)))) (def: (f64 run) (-> Runner Test) diff --git a/stdlib/source/spec/compositor/generation/structure.lux b/stdlib/source/spec/compositor/generation/structure.lux index 619f3921f..a93b27086 100644 --- a/stdlib/source/spec/compositor/generation/structure.lux +++ b/stdlib/source/spec/compositor/generation/structure.lux @@ -8,6 +8,8 @@ ["." try]] [data ["." maybe] + [number + ["i" int]] ["." text ("#@." equivalence) ["%" format (#+ format)]] [collection @@ -52,7 +54,7 @@ #.None (not last?-in)) - same-value? (|> value-out (:coerce Int) (i/= value-in))] + same-value? (|> value-out (:coerce Int) (i.= value-in))] (and same-tag? same-flag? same-value?)))) @@ -72,7 +74,7 @@ (let [tuple-out (:coerce (Array Any) tuple-out)] (and (n/= size (array.size tuple-out)) (list.every? (function (_ [left right]) - (i/= left (:coerce Int right))) + (i.= left (:coerce Int right))) (list.zip2 tuple-in (array.to-list tuple-out))))) (#try.Failure _) diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 597f6d83e..580c02d2e 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -20,7 +20,7 @@ ["." name] [number ["." i64] - ["." int] + ["i" int] ["r" rev] ["f" frac]]] ["." math] @@ -314,14 +314,14 @@ (<| (_.context "Natural numbers.") (..even-or-odd random.nat n/even? n/odd?)) (<| (_.context "Integers.") - (..even-or-odd random.int i/even? i/odd?)))) + (..even-or-odd random.int i.even? i.odd?)))) (<| (_.context "Minimum and maximum.") (`` ($_ _.and (~~ (template [<=> ] [(<| (_.context ) (..minimum-and-maximum <=> [ ] [ ]))] - [i/= i/< i/min i/> i/max random.int "Integers."] + [i.= i.< i.min i.> i.max random.int "Integers."] [n/= n/< n/min n/> n/max random.nat "Natural numbers."] [r.= r.< r.min r.> r.max random.rev "Revolutions."] [f.= f.< f.min f.> f.max random.safe-frac "Fractions."] @@ -333,11 +333,11 @@ " " (%.name (name-of )))) (..conversion <=>))] - [i/= .nat .int (random@map (i/% +1,000,000) random.int)] - [n/= .int .nat (random@map (n/% 1,000,000) random.nat)] - [i/= int.frac f.int (random@map (i/% +1,000,000) random.int)] - [f.= f.int int.frac (random@map (|>> (i/% +1,000,000) int.frac) random.int)] - [r.= r.frac f.rev frac-rev] + [i.= .nat .int (random@map (i.% +1,000,000) random.int)] + [n/= .int .nat (random@map (n/% 1,000,000) random.nat)] + [i.= i.frac f.int (random@map (i.% +1,000,000) random.int)] + [f.= f.int i.frac (random@map (|>> (i.% +1,000,000) i.frac) random.int)] + [r.= r.frac f.rev frac-rev] ))))) (<| (_.context "Prelude macros.") ..prelude-macros) diff --git a/stdlib/source/test/lux/data/number/frac.lux b/stdlib/source/test/lux/data/number/frac.lux index 257d4c049..7afefb76d 100644 --- a/stdlib/source/test/lux/data/number/frac.lux +++ b/stdlib/source/test/lux/data/number/frac.lux @@ -15,11 +15,11 @@ {1 ["." / [// #* - ["." int]]]}) + ["i" int]]]}) (def: #export test Test - (let [gen-frac (:: r.monad map (|>> (i/% +100) int.frac) r.int)] + (let [gen-frac (:: r.monad map (|>> (i.% +100) i.frac) r.int)] (<| (_.context (%.name (name-of /._))) (`` ($_ _.and ($equivalence.spec /.equivalence gen-frac) diff --git a/stdlib/source/test/lux/data/number/i64.lux b/stdlib/source/test/lux/data/number/i64.lux index fd4b3adeb..fbfecf07a 100644 --- a/stdlib/source/test/lux/data/number/i64.lux +++ b/stdlib/source/test/lux/data/number/i64.lux @@ -3,7 +3,9 @@ ["_" test (#+ Test)] [data ["." name] - ["%" text/format (#+ format)]] + ["%" text/format (#+ format)] + [number + ["i" int]]] [abstract [monad (#+ do)] {[0 #test] @@ -82,7 +84,7 @@ (n/= pattern)))) (_.test "Shift right respect the sign of ints." (let [value (.int pattern)] - (if (i/< +0 value) - (i/< +0 (/.arithmetic-right-shift idx value)) - (i/>= +0 (/.arithmetic-right-shift idx value))))) + (if (i.< +0 value) + (i.< +0 (/.arithmetic-right-shift idx value)) + (i.>= +0 (/.arithmetic-right-shift idx value))))) )))) diff --git a/stdlib/source/test/lux/data/number/int.lux b/stdlib/source/test/lux/data/number/int.lux index 7d11f0a03..c9491c913 100644 --- a/stdlib/source/test/lux/data/number/int.lux +++ b/stdlib/source/test/lux/data/number/int.lux @@ -40,10 +40,10 @@ )) (_.test "Alternate notations." - (and (i/= (bin "+11001001") + (and (/.= (bin "+11001001") (bin "+11,00,10,01")) - (i/= (oct "-615243") + (/.= (oct "-615243") (oct "-615,243")) - (i/= (hex "+deadBEEF") + (/.= (hex "+deadBEEF") (hex "+dead,BEEF")))) )))) diff --git a/stdlib/source/test/lux/data/product.lux b/stdlib/source/test/lux/data/product.lux index b7522077c..7c962804b 100644 --- a/stdlib/source/test/lux/data/product.lux +++ b/stdlib/source/test/lux/data/product.lux @@ -1,7 +1,10 @@ (.module: [lux #* ["_" test (#+ Test)] - ["%" data/text/format (#+ format)]] + [data + ["%" text/format (#+ format)] + [number + ["i" int]]]] {1 ["." /]}) @@ -10,11 +13,11 @@ (<| (_.context (%.name (name-of .&))) ($_ _.and (_.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])] - (and (i/= +2 _left) - (i/= +1 _right)))) + (and (i.= +2 _left) + (i.= +1 _right)))) ))) diff --git a/stdlib/source/test/lux/host.jvm.lux b/stdlib/source/test/lux/host.jvm.lux index f142a1912..d1753e7a1 100644 --- a/stdlib/source/test/lux/host.jvm.lux +++ b/stdlib/source/test/lux/host.jvm.lux @@ -4,7 +4,9 @@ [control pipe] [data - ["." text ("#;." equivalence)]] + ["." text ("#;." equivalence)] + [number + ["i" int]]] [math ["r" random]] ["_" test (#+ Test)]] @@ -30,35 +32,38 @@ (#static currentTimeMillis [] #io long) (#static getenv [java/lang/String] #io #? java/lang/String)) -(class: #final (TestClass A) [java/lang/Runnable] - ## Fields - (#private foo boolean) - (#private bar A) - (#private baz java/lang/Object) - ## Methods - (#public [] (new self {value A}) [] - (exec (:= ::foo #1) - (:= ::bar value) - (:= ::baz "") - [])) - (#public (virtual self) java/lang/Object - "") - (#public #static (static) java/lang/Object - "") - (java/lang/Runnable [] (run self) void - [])) +## TODO: Handle "class:" ASAP. +## (class: #final (TestClass A) [java/lang/Runnable] +## ## Fields +## (#private foo boolean) +## (#private bar A) +## (#private baz java/lang/Object) +## ## Methods +## (#public [] (new self {value A}) [] +## (exec (:= ::foo #1) +## (:= ::bar value) +## (:= ::baz "") +## [])) +## (#public (virtual self) java/lang/Object +## "") +## (#public #static (static) java/lang/Object +## "") +## (java/lang/Runnable [] (run self) void +## [])) (def: test-runnable (object [] [java/lang/Runnable] [] - (java/lang/Runnable [] (run self) void - []))) + (java/lang/Runnable + [] (run self) void + []))) (def: test-callable (object [a] [(java/util/concurrent/Callable a)] [] - (java/util/concurrent/Callable [] (call self) a - (undefined)))) + ((java/util/concurrent/Callable a) + [] (call self) a #throws [java/lang/Exception] + (undefined)))) (interface: TestInterface ([] foo [boolean java/lang/String] void #throws [java/lang/Exception])) @@ -70,9 +75,9 @@ (`` ($_ _.and (~~ (template [ ] [(_.test - (or (|> sample (i/= sample)) + (or (|> sample (i.= sample)) (let [capped-sample (|> sample )] - (|> capped-sample (i/= capped-sample)))))] + (|> capped-sample (i.= capped-sample)))))] [/.long-to-byte /.byte-to-long "Can succesfully convert to/from byte."] [/.long-to-short /.short-to-long "Can succesfully convert to/from short."] @@ -126,7 +131,7 @@ (_.test "Can set and get array values." (let [arr (/.array Long size)] (exec (/.array-write idx value arr) - (i/= value (/.array-read idx arr)))))))) + (i.= value (/.array-read idx arr)))))))) (def: #export test ($_ _.and diff --git a/stdlib/source/test/lux/host.old.lux b/stdlib/source/test/lux/host.old.lux index c9446b857..19e8ae9ba 100644 --- a/stdlib/source/test/lux/host.old.lux +++ b/stdlib/source/test/lux/host.old.lux @@ -4,7 +4,9 @@ [control pipe] [data - ["." text ("#;." equivalence)]] + ["." text ("#;." equivalence)] + [number + ["i" int]]] [math ["r" random]] ["_" test (#+ Test)]] @@ -66,9 +68,9 @@ (`` ($_ _.and (~~ (template [ ] [(_.test - (or (|> sample (i/= sample)) + (or (|> sample (i.= sample)) (let [capped-sample (|> sample )] - (|> capped-sample (i/= capped-sample)))))] + (|> capped-sample (i.= capped-sample)))))] [/.long-to-byte /.byte-to-long "Can succesfully convert to/from byte."] [/.long-to-short /.short-to-long "Can succesfully convert to/from short."] @@ -122,7 +124,7 @@ (_.test "Can set and get array values." (let [arr (/.array Long size)] (exec (/.array-write idx value arr) - (i/= value (/.array-read idx arr)))))))) + (i.= value (/.array-read idx arr)))))))) (def: #export test ($_ _.and diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux index e0bcd9df4..00d734ee7 100644 --- a/stdlib/source/test/lux/macro/code.lux +++ b/stdlib/source/test/lux/macro/code.lux @@ -7,7 +7,7 @@ [data ["." text ("#@." equivalence)] [number - ["." int] + ["i" int] ["f" frac]]]] {1 ["." /]}) @@ -20,12 +20,12 @@ nat r.nat int r.int rev r.rev - above (:: @ map (i/% +100) r.int) - below (:: @ map (i/% +100) r.int) + above (:: @ map (i.% +100) r.int) + below (:: @ map (i.% +100) r.int) #let [frac (|> below - (i// +100) - int.frac - (f.+ (int.frac above)) + (i./ +100) + i.frac + (f.+ (i.frac above)) (f.* -1.0))] text (r.ascii 10) short (r.ascii/alpha 10) diff --git a/stdlib/source/test/lux/macro/poly/equivalence.lux b/stdlib/source/test/lux/macro/poly/equivalence.lux index c6dcd4687..adf150aee 100644 --- a/stdlib/source/test/lux/macro/poly/equivalence.lux +++ b/stdlib/source/test/lux/macro/poly/equivalence.lux @@ -11,7 +11,7 @@ ["." bit] ["." maybe] [number - ["." int]] + ["i" int]] ["." text] [collection ["." list]]] @@ -50,7 +50,7 @@ (Random Record) (do random.monad [size (:: @ map (n/% 2) random.nat) - #let [gen-int (|> random.int (:: @ map (|>> int.abs (i/% +1,000,000))))]] + #let [gen-int (|> random.int (:: @ map (|>> i.abs (i.% +1,000,000))))]] ($_ random.and random.bit gen-int diff --git a/stdlib/source/test/lux/math/modular.lux b/stdlib/source/test/lux/math/modular.lux index 8a2ba754d..96a80dc4c 100644 --- a/stdlib/source/test/lux/math/modular.lux +++ b/stdlib/source/test/lux/math/modular.lux @@ -8,7 +8,9 @@ ["." try]] [data ["." product] - ["." bit ("#@." equivalence)]] + ["." bit ("#@." equivalence)] + [number + ["i" int]]] ["." type ("#@." equivalence)]] {1 ["." /]}) @@ -19,12 +21,12 @@ (def: modulusR (r.Random Int) (|> r.int - (:: r.monad map (i/% +1000)) - (r.filter (|>> (i/= +0) not)))) + (:: r.monad map (i.% +1000)) + (r.filter (|>> (i.= +0) not)))) (def: valueR (r.Random Int) - (|> r.int (:: r.monad map (i/% +1000)))) + (|> r.int (:: r.monad map (i.% +1000)))) (def: (modR modulus) (All [m] (-> (/.Modulus m) (r.Random [Int (/.Mod m)]))) @@ -63,7 +65,7 @@ (<| (_.context (%.name (name-of /.Mod))) (do r.monad [_normalM modulusR - _alternativeM (|> modulusR (r.filter (|>> (i/= _normalM) not))) + _alternativeM (|> modulusR (r.filter (|>> (i.= _normalM) not))) #let [normalM (|> _normalM /.from-int try.assume) alternativeM (|> _alternativeM /.from-int try.assume)] [_param param] (modR normalM) @@ -78,15 +80,15 @@ (not (type@= (:of normalM) (:of copyM))))) (_.test "Can extract the original integer from the modulus." - (i/= _normalM + (i.= _normalM (/.to-int normalM))) (_.test "Can compare mod'ed values." (and (/.= subject subject) - ((comparison /.= i/=) param subject) - ((comparison /.< i/<) param subject) - ((comparison /.<= i/<=) param subject) - ((comparison /.> i/>) param subject) - ((comparison /.>= i/>=) param subject))) + ((comparison /.= i.=) param subject) + ((comparison /.< i.<) param subject) + ((comparison /.<= i.<=) param subject) + ((comparison /.> i.>) param subject) + ((comparison /.>= i.>=) param subject))) (_.test "Mod'ed values are ordered." (and (bit@= (/.< param subject) (not (/.>= param subject))) @@ -96,9 +98,9 @@ (not (or (/.< param subject) (/.> param subject)))))) (_.test "Can do arithmetic." - (and ((arithmetic normalM /.+ i/+) param subject) - ((arithmetic normalM /.- i/-) param subject) - ((arithmetic normalM /.* i/*) param subject))) + (and ((arithmetic normalM /.+ i.+) param subject) + ((arithmetic normalM /.- i.-) param subject) + ((arithmetic normalM /.* i.*) param subject))) (_.test "Can sometimes find multiplicative inverse." (case (/.inverse subject) (#.Some subject^-1) diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux index def28b2a0..47ed621d8 100644 --- a/stdlib/source/test/lux/target/jvm.lux +++ b/stdlib/source/test/lux/target/jvm.lux @@ -11,6 +11,8 @@ ["!" capability]]] [data [binary (#+ Binary)] + [number + ["i" int]] ["." text ["%" format (#+ format)]] [format @@ -147,7 +149,7 @@ output (java/lang/reflect/Method::invoke (host.null) (host.array java/lang/Object 0) method)] (wrap (:coerce Int output))) (#try.Success actual) - (i/= expected actual) + (i.= expected actual) (#try.Failure error) false))))) diff --git a/stdlib/source/test/lux/time/duration.lux b/stdlib/source/test/lux/time/duration.lux index 8ec82dc70..9eea2e03b 100644 --- a/stdlib/source/test/lux/time/duration.lux +++ b/stdlib/source/test/lux/time/duration.lux @@ -10,6 +10,9 @@ ["$." order] ["$." monoid] ["$." codec]]}] + [data + [number + ["i" int]]] [math ["r" random (#+ Random)]]] {1 @@ -32,7 +35,7 @@ (do r.monad [millis r.int] (_.test "Can convert from/to milliseconds." - (|> millis /.from-millis /.to-millis (i/= millis)))) + (|> millis /.from-millis /.to-millis (i.= millis)))) (do r.monad [sample (|> duration (:: @ map (/.frame /.day))) frame duration @@ -40,7 +43,7 @@ #let [(^open "/@.") /.order]] ($_ _.and (_.test "Can scale a duration." - (|> sample (/.scale-up factor) (/.query sample) (i/= (.int factor)))) + (|> sample (/.scale-up factor) (/.query sample) (i.= (.int factor)))) (_.test "Scaling a duration by one does not change it." (|> sample (/.scale-up 1) (/@= sample))) (_.test "Merging a duration with it's opposite yields an empty duration." diff --git a/stdlib/source/test/lux/time/instant.lux b/stdlib/source/test/lux/time/instant.lux index 3e3e2ca8c..484aecb5a 100644 --- a/stdlib/source/test/lux/time/instant.lux +++ b/stdlib/source/test/lux/time/instant.lux @@ -13,7 +13,9 @@ [control pipe] [data - ["." text]] + ["." text] + [number + ["i" int]]] [math ["r" random (#+ Random)]] [time @@ -28,7 +30,7 @@ (def: #export instant (Random Instant) - (:: r.monad map (|>> (i/% boundary) /.from-millis) r.int)) + (:: r.monad map (|>> (i.% boundary) /.from-millis) r.int)) (def: #export test Test @@ -43,7 +45,7 @@ (do r.monad [millis r.int] (_.test "Can convert from/to milliseconds." - (|> millis /.from-millis /.to-millis (i/= millis)))) + (|> millis /.from-millis /.to-millis (i.= millis)))) (do r.monad [sample instant span _duration.duration diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index 2659183af..91f7ba0be 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -15,7 +15,7 @@ ["." binary (#+ Binary)] ["." text] [number - ["." int]] + ["i" int]] [collection ["." list]]] [time @@ -29,7 +29,7 @@ (def: truncate-millis (let [millis +1,000] - (|>> (i// millis) (i/* millis)))) + (|>> (i./ millis) (i.* millis)))) (def: (creation-and-deletion number) (-> Nat Test) @@ -71,7 +71,7 @@ [file-size (|> r.nat (:: @ map (|>> (n/% 100) (n/max 10)))) dataL (_binary.binary file-size) dataR (_binary.binary file-size) - new-modified (|> r.int (:: @ map (|>> int.abs + new-modified (|> r.int (:: @ map (|>> i.abs truncate-millis duration.from-millis instant.absolute)))] -- cgit v1.2.3