aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/number
diff options
context:
space:
mode:
authorEduardo Julian2019-07-26 21:23:27 -0400
committerEduardo Julian2019-07-26 21:23:27 -0400
commita0889b2ee76c1ae7a9a5bbe2eec9f051b4f341e4 (patch)
tree08df3db7f8fffad6360a476d20db1d40b36c85cb /stdlib/source/lux/data/number
parent78fd01f7e6688448bbd710336d4d7b1c35ae058a (diff)
No more "n/"-prefixed functions.
Diffstat (limited to 'stdlib/source/lux/data/number')
-rw-r--r--stdlib/source/lux/data/number/complex.lux3
-rw-r--r--stdlib/source/lux/data/number/frac.lux36
-rw-r--r--stdlib/source/lux/data/number/i64.lux25
-rw-r--r--stdlib/source/lux/data/number/int.lux18
-rw-r--r--stdlib/source/lux/data/number/nat.lux162
-rw-r--r--stdlib/source/lux/data/number/ratio.lux40
-rw-r--r--stdlib/source/lux/data/number/rev.lux76
7 files changed, 241 insertions, 119 deletions
diff --git a/stdlib/source/lux/data/number/complex.lux b/stdlib/source/lux/data/number/complex.lux
index ec4b27326..ede5bb980 100644
--- a/stdlib/source/lux/data/number/complex.lux
+++ b/stdlib/source/lux/data/number/complex.lux
@@ -11,6 +11,7 @@
[data
["." maybe]
[number
+ ["n" nat]
["." int]
["f" frac]]
["." text ("#;." monoid)]
@@ -278,7 +279,7 @@
(def: #export (roots nth input)
(-> Nat Complex (List Complex))
- (if (n/= 0 nth)
+ (if (n.= 0 nth)
(list)
(let [r-nth (|> nth .int int.frac)
nth-root-of-abs (|> input abs (get@ #real) (math.pow (f./ r-nth +1.0)))
diff --git a/stdlib/source/lux/data/number/frac.lux b/stdlib/source/lux/data/number/frac.lux
index 522f3c674..0cd8fe897 100644
--- a/stdlib/source/lux/data/number/frac.lux
+++ b/stdlib/source/lux/data/number/frac.lux
@@ -196,7 +196,7 @@
+1.0)
div-power (loop [muls-left ("lux text size" decimal-part)
output +1.0]
- (if (n/= 0 muls-left)
+ (if (//nat.= 0 muls-left)
output
(recur (dec muls-left)
(..* <base> output))))
@@ -227,9 +227,9 @@
_
(let [num-digits ("lux text size" digits)]
- (if (n/<= chunk-size num-digits)
+ (if (//nat.<= chunk-size num-digits)
(list digits)
- (let [boundary (n/- chunk-size num-digits)
+ (let [boundary (//nat.- chunk-size num-digits)
chunk ("lux text clip" boundary num-digits digits)
remaining ("lux text clip" 0 boundary digits)]
(list& chunk (segment-digits chunk-size remaining)))))))
@@ -323,15 +323,15 @@
(template [<from> <from-translator> <to> <to-translator> <base-bits>]
[(def: (<from> on-left? input)
(-> Bit Text Text)
- (let [max-num-chars (n// <base-bits> 64)
+ (let [max-num-chars (//nat./ <base-bits> 64)
input-size ("lux text size" input)
- zero-padding (let [num-digits-that-need-padding (n/% <base-bits> input-size)]
- (if (n/= 0 num-digits-that-need-padding)
+ zero-padding (let [num-digits-that-need-padding (//nat.% <base-bits> input-size)]
+ (if (//nat.= 0 num-digits-that-need-padding)
""
- (loop [zeroes-left (n/- num-digits-that-need-padding
- <base-bits>)
+ (loop [zeroes-left (//nat.- num-digits-that-need-padding
+ <base-bits>)
output ""]
- (if (n/= 0 zeroes-left)
+ (if (//nat.= 0 zeroes-left)
output
(recur (dec zeroes-left)
("lux text concat" "0" output))))))
@@ -448,7 +448,7 @@
sign-bit (if (..= -1.0 (..signum input))
1
0)
- exponent-bits (|> exponent ..int .nat (n/+ double-bias) (//i64.and exponent-mask))
+ exponent-bits (|> exponent ..int .nat (//nat.+ double-bias) (//i64.and exponent-mask))
mantissa-bits (|> mantissa ..int .nat)]
($_ //i64.or
(//i64.left-shift 63 sign-bit)
@@ -464,7 +464,7 @@
[mantissa mantissa-mask mantissa-size 0]
[exponent exponent-mask exponent-size mantissa-size]
- [sign sign-mask 1 (n/+ exponent-size mantissa-size)]
+ [sign sign-mask 1 (//nat.+ exponent-size mantissa-size)]
)
(def: #export (from-bits input)
@@ -472,15 +472,15 @@
(let [S (sign input)
E (exponent input)
M (mantissa input)]
- (cond (n/= ..special-exponent-bits E)
- (if (n/= 0 M)
- (if (n/= 0 S)
+ (cond (//nat.= ..special-exponent-bits E)
+ (if (//nat.= 0 M)
+ (if (//nat.= 0 S)
..positive-infinity
..negative-infinity)
..not-a-number)
- (and (n/= 0 E) (n/= 0 M))
- (if (n/= 0 S)
+ (and (//nat.= 0 E) (//nat.= 0 M))
+ (if (//nat.= 0 S)
+0.0
(..* -1.0 +0.0))
@@ -488,12 +488,12 @@
(let [normalized (|> M (//i64.set mantissa-size)
.int //int.frac
(../ (math.pow +52.0 +2.0)))
- power (math.pow (|> E (n/- double-bias)
+ power (math.pow (|> E (//nat.- double-bias)
.int //int.frac)
+2.0)
shifted (..* power
normalized)]
- (if (n/= 0 S)
+ (if (//nat.= 0 S)
shifted
(..* -1.0 shifted))))))
diff --git a/stdlib/source/lux/data/number/i64.lux b/stdlib/source/lux/data/number/i64.lux
index 2b736b005..f8417cfb0 100644
--- a/stdlib/source/lux/data/number/i64.lux
+++ b/stdlib/source/lux/data/number/i64.lux
@@ -2,7 +2,10 @@
[lux (#- and or not)
[abstract
[equivalence (#+ Equivalence)]
- [monoid (#+ Monoid)]]])
+ [monoid (#+ Monoid)]]
+ [data
+ [number
+ ["n" nat]]]])
(def: #export bits-per-byte 8)
@@ -10,7 +13,7 @@
(def: #export width
Nat
- (n/* bits-per-byte
+ (n.* bits-per-byte
bytes-per-i64))
(template [<parameter-type> <name> <op> <doc>]
@@ -37,21 +40,21 @@
(def: #export (mask bits)
(-> Nat Mask)
- (|> 1 .i64 (..left-shift (n/% ..width bits)) .dec))
+ (|> 1 .i64 (..left-shift (n.% ..width bits)) .dec))
(def: #export sign Mask (|> 1 .i64 (..left-shift 63)))
(def: (add-shift shift value)
(-> Nat Nat Nat)
- (|> value (logic-right-shift shift) (n/+ value)))
+ (|> value (logic-right-shift shift) (n.+ value)))
(def: #export (count subject)
{#.doc "Count the number of 1s in a bit-map."}
(-> (I64 Any) Nat)
- (let [count' (n/- (|> subject (logic-right-shift 1) (..and 6148914691236517205) i64)
+ (let [count' (n.- (|> subject (logic-right-shift 1) (..and 6148914691236517205) i64)
(i64 subject))]
(|> count'
- (logic-right-shift 2) (..and 3689348814741910323) (n/+ (..and 3689348814741910323 count'))
+ (logic-right-shift 2) (..and 3689348814741910323) (n.+ (..and 3689348814741910323 count'))
(add-shift 4) (..and 1085102592571150095)
(add-shift 8)
(add-shift 16)
@@ -79,12 +82,12 @@
(def: #export (set? idx input)
(-> Nat (I64 Any) Bit)
- (|> input (:coerce I64) (..and (flag idx)) (n/= 0) .not))
+ (|> input (:coerce I64) (..and (flag idx)) (n.= 0) .not))
(template [<name> <main> <comp>]
[(def: #export (<name> distance input)
(All [s] (-> Nat (I64 s) (I64 s)))
- (let [backwards-distance (n/- (n/% width distance) width)]
+ (let [backwards-distance (n.- (n.% width distance) width)]
(|> input
(<comp> backwards-distance)
(..or (<main> distance input)))))]
@@ -124,10 +127,10 @@
(def: #export (sub width)
(Ex [size] (-> Nat (Maybe (Sub size))))
- (if (.and (n/> 0 width)
- (n/< ..width width))
+ (if (.and (n.> 0 width)
+ (n.< ..width width))
(let [top (dec width)
- shift (n/- width ..width)
+ shift (n.- width ..width)
sign (: Mask (|> 1 .i64 (..left-shift top)))
number (..mask (dec width))]
(#.Some {#narrow (function (narrow value)
diff --git a/stdlib/source/lux/data/number/int.lux b/stdlib/source/lux/data/number/int.lux
index fa8dee78a..67f2c8177 100644
--- a/stdlib/source/lux/data/number/int.lux
+++ b/stdlib/source/lux/data/number/int.lux
@@ -13,8 +13,8 @@
[data
[text (#+ Char)]
["." maybe]]]
- [//
- ["." nat]])
+ ["." // #_
+ ["#." nat]])
(def: #export (= reference sample)
{#.doc "Int(eger) equivalence."}
@@ -100,7 +100,7 @@
(def: #export even?
(-> Int Bit)
- (|>> (..% +2) (..= +0)))
+ (|>> (..% +2) ("lux i64 =" +0)))
(def: #export odd?
(-> Int Bit)
@@ -178,7 +178,7 @@
(-> Nat Text Int Int (-> Char (Maybe Nat)) Text (Try Int))
(loop [idx 1
output +0]
- (if (n/< input-size idx)
+ (if (//nat.< input-size idx)
(case (<to-value> ("lux text char" idx repr))
#.None
(#try.Failure <error>)
@@ -205,7 +205,7 @@
(def: (decode repr)
(let [input-size ("lux text size" repr)]
- (if (n/> 1 input-size)
+ (if (//nat.> 1 input-size)
(case (sign?? repr)
(#.Some sign)
(int-decode-loop input-size repr sign <base> <to-value> <error>)
@@ -214,10 +214,10 @@
(#try.Failure <error>))
(#try.Failure <error>)))))]
- [binary +2 nat.binary-character nat.binary-value "Invalid binary syntax for Int: "]
- [octal +8 nat.octal-character nat.octal-value "Invalid octal syntax for Int: "]
- [decimal +10 nat.decimal-character nat.decimal-value "Invalid syntax for Int: "]
- [hex +16 nat.hexadecimal-character nat.hexadecimal-value "Invalid hexadecimal syntax for Int: "]
+ [binary +2 //nat.binary-character //nat.binary-value "Invalid binary syntax for Int: "]
+ [octal +8 //nat.octal-character //nat.octal-value "Invalid octal syntax for Int: "]
+ [decimal +10 //nat.decimal-character //nat.decimal-value "Invalid syntax for Int: "]
+ [hex +16 //nat.hexadecimal-character //nat.hexadecimal-value "Invalid hexadecimal syntax for Int: "]
)
(structure: #export hash (Hash Int)
diff --git a/stdlib/source/lux/data/number/nat.lux b/stdlib/source/lux/data/number/nat.lux
index b86826fdd..4066d7b2f 100644
--- a/stdlib/source/lux/data/number/nat.lux
+++ b/stdlib/source/lux/data/number/nat.lux
@@ -12,29 +12,147 @@
["." function]
["." try (#+ Try)]]
[data
- ["." maybe]
- ["." text (#+ Char)]]])
+ ["." maybe]]])
-(def: #export + (-> Nat Nat Nat) n/+)
+(template [<extension> <output> <name> <documentation>]
+ [(def: #export (<name> parameter subject)
+ {#.doc <documentation>}
+ (-> Nat Nat <output>)
+ (<extension> parameter subject))]
-(def: #export - (-> Nat Nat Nat) n/-)
+ ["lux i64 =" Bit = "Nat(ural) equivalence."]
+ ["lux i64 +" Nat + "Nat(ural) addition."]
+ ["lux i64 -" Nat - "Nat(ural) substraction."]
+ )
+
+(def: high
+ (-> (I64 Any) I64)
+ (|>> ("lux i64 logical-right-shift" 32)))
+
+(def: low
+ (-> (I64 Any) I64)
+ (let [mask (|> 1 ("lux i64 left-shift" 32) ("lux i64 -" 1))]
+ (|>> ("lux i64 and" mask))))
+
+(def: #export (< reference sample)
+ {#.doc "Nat(ural) less-than."}
+ (-> Nat Nat Bit)
+ (let [referenceH (..high reference)
+ sampleH (..high sample)]
+ (if ("lux i64 <" referenceH sampleH)
+ #1
+ (if ("lux i64 =" referenceH sampleH)
+ ("lux i64 <"
+ (..low reference)
+ (..low sample))
+ #0))))
+
+(def: #export (<= reference sample)
+ {#.doc "Nat(ural) less-than-equal."}
+ (-> Nat Nat Bit)
+ (if (..< reference sample)
+ #1
+ ("lux i64 =" reference sample)))
-(def: #export * (-> Nat Nat Nat) n/*)
+(def: #export (> reference sample)
+ {#.doc "Nat(ural) greater-than."}
+ (-> Nat Nat Bit)
+ (..< sample reference))
-(def: #export / (-> Nat Nat Nat) n//)
+(def: #export (>= reference sample)
+ {#.doc "Nat(ural) greater-than-equal."}
+ (-> Nat Nat Bit)
+ (if (..< sample reference)
+ #1
+ ("lux i64 =" reference sample)))
+
+(template [<name> <test> <doc>]
+ [(def: #export (<name> left right)
+ {#.doc <doc>}
+ (-> Nat Nat Nat)
+ (if (<test> right left)
+ left
+ right))]
+
+ [min ..< "Nat(ural) minimum."]
+ [max ..> "Nat(ural) maximum."]
+ )
+
+(def: #export (* parameter subject)
+ {#.doc "Nat(ural) multiplication."}
+ (-> Nat Nat Nat)
+ ("lux coerce" Nat
+ ("lux i64 *"
+ ("lux coerce" Int parameter)
+ ("lux coerce" Int subject))))
-(def: #export % (-> Nat Nat Nat) n/%)
+(def: #export (/ parameter subject)
+ {#.doc "Nat(ural) division."}
+ (-> Nat Nat Nat)
+ (if ("lux i64 <" +0 ("lux coerce" Int parameter))
+ (if (..< parameter subject)
+ 0
+ 1)
+ (let [quotient (|> subject
+ ("lux i64 logical-right-shift" 1)
+ ("lux i64 /" ("lux coerce" Int parameter))
+ ("lux i64 left-shift" 1))
+ flat ("lux i64 *"
+ ("lux coerce" Int parameter)
+ ("lux coerce" Int quotient))
+ remainder ("lux i64 -" flat subject)]
+ (if (..< parameter remainder)
+ quotient
+ ("lux i64 +" 1 quotient)))))
-(def: #export (/% param subject)
+(def: #export (/% parameter subject)
+ {#.doc "Nat(ural) [division remainder]."}
(-> Nat Nat [Nat Nat])
- [(../ param subject)
- (..% param subject)])
+ (let [div (../ parameter subject)
+ flat ("lux i64 *"
+ ("lux coerce" Int parameter)
+ ("lux coerce" Int div))]
+ [div ("lux i64 -" flat subject)]))
+
+(def: #export (% parameter subject)
+ {#.doc "Nat(ural) remainder."}
+ (-> Nat Nat Nat)
+ (let [flat ("lux i64 *"
+ ("lux coerce" Int parameter)
+ ("lux coerce" Int (../ parameter subject)))]
+ ("lux i64 -" flat subject)))
-(def: #export (mod param subject)
+(def: #export (mod parameter subject)
(-> Nat Nat Nat)
- (let [exact (|> subject (../ param) (..* param))]
+ (let [exact (|> subject (../ parameter) (..* parameter))]
(|> subject (..- exact))))
+(def: #export (gcd a b)
+ {#.doc "Greatest Common Divisor."}
+ (-> Nat Nat Nat)
+ (case b
+ 0 a
+ _ (gcd b (..mod b a))))
+
+(def: #export (lcm a b)
+ {#.doc "Least Common Multiple."}
+ (-> Nat Nat Nat)
+ (case [a b]
+ (^or [_ 0] [0 _])
+ 0
+
+ _
+ (|> a (../ (..gcd a b)) (..* b))
+ ))
+
+(def: #export even?
+ (-> Nat Bit)
+ (|>> (..% 2) ("lux i64 =" 0)))
+
+(def: #export odd?
+ (-> Nat Bit)
+ (|>> ..even? not))
+
(def: #export frac
(-> Nat Frac)
(|>> .int "lux i64 f64"))
@@ -42,13 +160,13 @@
(structure: #export equivalence
(Equivalence Nat)
- (def: = n/=))
+ (def: = ..=))
(structure: #export order
(Order Nat)
(def: &equivalence ..equivalence)
- (def: < n/<))
+ (def: < ..<))
(structure: #export enum
(Enum Nat)
@@ -73,8 +191,8 @@
[addition ..+ 0]
[multiplication ..* 1]
- [minimum n/min (:: ..interval top)]
- [maximum n/max (:: ..interval bottom)]
+ [minimum ..min (:: ..interval top)]
+ [maximum ..max (:: ..interval bottom)]
)
(def: #export (binary-character value)
@@ -85,7 +203,7 @@
_ #.None))
(def: #export (binary-value digit)
- (-> Char (Maybe Nat))
+ (-> Nat (Maybe Nat))
(case digit
(^ (char "0")) (#.Some 0)
(^ (char "1")) (#.Some 1)
@@ -105,7 +223,7 @@
_ #.None))
(def: #export (octal-value digit)
- (-> Char (Maybe Nat))
+ (-> Nat (Maybe Nat))
(case digit
(^ (char "0")) (#.Some 0)
(^ (char "1")) (#.Some 1)
@@ -133,7 +251,7 @@
_ #.None))
(def: #export (decimal-value digit)
- (-> Char (Maybe Nat))
+ (-> Nat (Maybe Nat))
(case digit
(^ (char "0")) (#.Some 0)
(^ (char "1")) (#.Some 1)
@@ -169,7 +287,7 @@
_ #.None))
(def: #export (hexadecimal-value digit)
- (-> Char (Maybe Nat))
+ (-> Nat (Maybe Nat))
(case digit
(^ (char "0")) (#.Some 0)
(^ (char "1")) (#.Some 1)
@@ -205,10 +323,10 @@
(def: (decode repr)
(let [input-size ("lux text size" repr)]
- (if (n/> 0 input-size)
+ (if (..> 0 input-size)
(loop [idx 0
output 0]
- (if (n/< input-size idx)
+ (if (..< input-size idx)
(case (<to-value> ("lux text char" idx repr))
#.None
(#try.Failure ("lux text concat" <error> repr))
diff --git a/stdlib/source/lux/data/number/ratio.lux b/stdlib/source/lux/data/number/ratio.lux
index 09d81d20d..dcca35bf9 100644
--- a/stdlib/source/lux/data/number/ratio.lux
+++ b/stdlib/source/lux/data/number/ratio.lux
@@ -16,7 +16,7 @@
["." product]
["." maybe]
[number
- ["." nat ("#@." decimal)]]
+ ["n" nat ("#@." decimal)]]
["." text ("#@." monoid)]]
["." math]
["." macro
@@ -29,22 +29,22 @@
(def: (equalize parameter subject)
(-> Ratio Ratio [Nat Nat])
- [(n/* (get@ #denominator subject)
+ [(n.* (get@ #denominator subject)
(get@ #numerator parameter))
- (n/* (get@ #denominator parameter)
+ (n.* (get@ #denominator parameter)
(get@ #numerator subject))])
(def: (normalize (^slots [#numerator #denominator]))
(-> Ratio Ratio)
- (let [common (math.n/gcd numerator denominator)]
- {#numerator (n// common numerator)
- #denominator (n// common denominator)}))
+ (let [common (n.gcd numerator denominator)]
+ {#numerator (n./ common numerator)
+ #denominator (n./ common denominator)}))
(structure: #export equivalence (Equivalence Ratio)
(def: (= parameter subject)
- (and (n/= (get@ #numerator parameter)
+ (and (n.= (get@ #numerator parameter)
(get@ #numerator subject))
- (n/= (get@ #denominator parameter)
+ (n.= (get@ #denominator parameter)
(get@ #denominator subject)))))
(structure: #export order (Order Ratio)
@@ -52,28 +52,28 @@
(def: (< parameter subject)
(let [[parameter' subject'] (..equalize parameter subject)]
- (n/< parameter' subject')))
+ (n.< parameter' subject')))
)
(def: #export (+ parameter subject)
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalize parameter subject)]
- (normalize [(n/+ parameter' subject')
- (n/* (get@ #denominator parameter)
+ (normalize [(n.+ parameter' subject')
+ (n.* (get@ #denominator parameter)
(get@ #denominator subject))])))
(def: #export (- parameter subject)
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalize parameter subject)]
- (normalize [(n/- parameter' subject')
- (n/* (get@ #denominator parameter)
+ (normalize [(n.- parameter' subject')
+ (n.* (get@ #denominator parameter)
(get@ #denominator subject))])))
(def: #export (* parameter subject)
(-> Ratio Ratio Ratio)
- (normalize [(n/* (get@ #numerator parameter)
+ (normalize [(n.* (get@ #numerator parameter)
(get@ #numerator subject))
- (n/* (get@ #denominator parameter)
+ (n.* (get@ #denominator parameter)
(get@ #denominator subject))]))
(def: #export (/ parameter subject)
@@ -84,8 +84,8 @@
(def: #export (% parameter subject)
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalize parameter subject)
- quot (n// parameter' subject')]
- (..- (update@ #numerator (n/* quot) parameter)
+ quot (n./ parameter' subject')]
+ (..- (update@ #numerator (n.* quot) parameter)
subject)))
(def: #export (reciprocal (^slots [#numerator #denominator]))
@@ -97,14 +97,14 @@
(structure: #export codec (Codec Text Ratio)
(def: (encode (^slots [#numerator #denominator]))
- ($_ text@compose (nat@encode numerator) ..separator (nat@encode denominator)))
+ ($_ text@compose (n@encode numerator) ..separator (n@encode denominator)))
(def: (decode input)
(case (text.split-with ..separator input)
(#.Some [num denom])
(do try.monad
- [numerator (nat@decode num)
- denominator (nat@decode denom)]
+ [numerator (n@decode num)
+ denominator (n@decode denom)]
(wrap (normalize {#numerator numerator
#denominator denominator})))
diff --git a/stdlib/source/lux/data/number/rev.lux b/stdlib/source/lux/data/number/rev.lux
index 0a9ed4b94..b12a6f314 100644
--- a/stdlib/source/lux/data/number/rev.lux
+++ b/stdlib/source/lux/data/number/rev.lux
@@ -28,14 +28,14 @@
(def: #export (< reference sample)
{#.doc "Rev(olution) less-than."}
(-> Rev Rev Bit)
- (n/< ("lux coerce" Nat reference)
- ("lux coerce" Nat sample)))
+ (//nat.< ("lux coerce" Nat reference)
+ ("lux coerce" Nat sample)))
(def: #export (<= reference sample)
{#.doc "Rev(olution) less-than-equal."}
(-> Rev Rev Bit)
- (if (n/< ("lux coerce" Nat reference)
- ("lux coerce" Nat sample))
+ (if (//nat.< ("lux coerce" Nat reference)
+ ("lux coerce" Nat sample))
#1
("lux i64 =" reference sample)))
@@ -134,7 +134,7 @@
{#.doc "Rev(olution) remainder."}
(-> Rev Rev Rev)
(|> (:coerce Nat subject)
- (n/% (:coerce Nat param))
+ (//nat.% (:coerce Nat param))
(:coerce Rev)))
(def: #export (scale param subject)
@@ -149,10 +149,10 @@
(-> Nat Rev)
(:coerce Rev
(let [[trailing-zeroes remaining] (without-trailing-zeroes 0 numerator)]
- (n// remaining
- ({0 (:coerce Nat -1)
- _ ("lux i64 left-shift" (n/- trailing-zeroes 64) 1)}
- trailing-zeroes)))))
+ (//nat./ remaining
+ ({0 (:coerce Nat -1)
+ _ ("lux i64 left-shift" (//nat.- trailing-zeroes 64) 1)}
+ trailing-zeroes)))))
(def: #export (/% param subject)
(-> Rev Rev [Rev Rev])
@@ -206,14 +206,14 @@
(structure: #export <struct> (Codec Text Rev)
(def: (encode value)
(let [raw-output (:: <codec> encode (:coerce Nat value))
- max-num-chars (n/+ (n// <char-bit-size> 64)
- (case (n/% <char-bit-size> 64)
- 0 0
- _ 1))
+ max-num-chars (//nat.+ (//nat./ <char-bit-size> 64)
+ (case (//nat.% <char-bit-size> 64)
+ 0 0
+ _ 1))
raw-size ("lux text size" raw-output)
- zero-padding (loop [zeroes-left (n/- raw-size max-num-chars)
+ zero-padding (loop [zeroes-left (//nat.- raw-size max-num-chars)
output ""]
- (if (n/= 0 zeroes-left)
+ (if (//nat.= 0 zeroes-left)
output
(recur (dec zeroes-left)
("lux text concat" "0" output))))]
@@ -223,7 +223,7 @@
(def: (decode repr)
(let [repr-size ("lux text size" repr)]
- (if (n/> 1 repr-size)
+ (if (//nat.> 1 repr-size)
(case ("lux text char" 0 repr)
(^ (char "."))
(case (:: <codec> decode (de-prefix repr))
@@ -277,11 +277,11 @@
output output]
(if (//int.>= +0 (.int idx))
(let [raw (|> (digits-get idx output)
- (n/* 5)
- (n/+ carry))]
+ (//nat.* 5)
+ (//nat.+ carry))]
(recur (dec idx)
- (n// 10 raw)
- (digits-put idx (n/% 10 raw) output)))
+ (//nat./ 10 raw)
+ (digits-put idx (//nat.% 10 raw) output)))
output)))
(def: (digits-power power)
@@ -301,7 +301,7 @@
output ""]
(if (//int.>= +0 (.int idx))
(let [digit (digits-get idx digits)]
- (if (and (n/= 0 digit)
+ (if (and (//nat.= 0 digit)
all-zeroes?)
(recur (dec idx) #1 output)
(recur (dec idx)
@@ -319,22 +319,22 @@
carry 0
output (make-digits [])]
(if (//int.>= +0 (.int idx))
- (let [raw ($_ n/+
+ (let [raw ($_ //nat.+
carry
(digits-get idx param)
(digits-get idx subject))]
(recur (dec idx)
- (n// 10 raw)
- (digits-put idx (n/% 10 raw) output)))
+ (//nat./ 10 raw)
+ (digits-put idx (//nat.% 10 raw) output)))
output)))
(def: (text-to-digits input)
(-> Text (Maybe Digits))
(let [length ("lux text size" input)]
- (if (n/<= //i64.width length)
+ (if (//nat.<= //i64.width length)
(loop [idx 0
output (make-digits [])]
- (if (n/< length idx)
+ (if (//nat.< length idx)
(case ("lux text index" 0 ("lux text clip" idx (inc idx) input) "0123456789")
#.None
#.None
@@ -348,21 +348,21 @@
(def: (digits-lt param subject)
(-> Digits Digits Bit)
(loop [idx 0]
- (and (n/< //i64.width idx)
+ (and (//nat.< //i64.width idx)
(let [pd (digits-get idx param)
sd (digits-get idx subject)]
- (if (n/= pd sd)
+ (if (//nat.= pd sd)
(recur (inc idx))
- (n/< pd sd))))))
+ (//nat.< pd sd))))))
(def: (digits-sub-once! idx param subject)
(-> Nat Nat Digits Digits)
(let [sd (digits-get idx subject)]
- (if (n/>= param sd)
- (digits-put idx (n/- param sd) subject)
+ (if (//nat.>= param sd)
+ (digits-put idx (//nat.- param sd) subject)
(let [diff (|> sd
- (n/+ 10)
- (n/- param))]
+ (//nat.+ 10)
+ (//nat.- param))]
(|> subject
(digits-put idx diff)
(digits-sub-once! (dec idx) 1))))))
@@ -388,7 +388,7 @@
digits (make-digits [])]
(if (//int.>= +0 (.int idx))
(if (//i64.set? idx input)
- (let [digits' (digits-add (digits-power (n/- idx last-idx))
+ (let [digits' (digits-add (digits-power (//nat.- idx last-idx))
digits)]
(recur (dec idx)
digits'))
@@ -404,22 +404,22 @@
_
#0)
- within-limits? (n/<= (inc //i64.width)
- ("lux text size" input))]
+ within-limits? (//nat.<= (inc //i64.width)
+ ("lux text size" input))]
(if (and dotted? within-limits?)
(case (text-to-digits (de-prefix input))
(#.Some digits)
(loop [digits digits
idx 0
output 0]
- (if (n/< //i64.width idx)
+ (if (//nat.< //i64.width idx)
(let [power (digits-power idx)]
(if (digits-lt power digits)
## Skip power
(recur digits (inc idx) output)
(recur (digits-sub! power digits)
(inc idx)
- (//i64.set (n/- idx (dec //i64.width)) output))))
+ (//i64.set (//nat.- idx (dec //i64.width)) output))))
(#try.Success (:coerce Rev output))))
#.None