aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/number.lux
diff options
context:
space:
mode:
authorEduardo Julian2018-07-28 15:39:06 -0400
committerEduardo Julian2018-07-28 15:39:06 -0400
commite6db62dbd6529938dace0e1cf5743f4e985efb81 (patch)
tree1117a8e1d45a109e0d982a3927ebff38e0aca17b /stdlib/source/lux/data/number.lux
parent15e71e57b688f5079fe606b2fee5e3efd2a5d5a7 (diff)
Removed temporary "|" prefix on Nat.
Diffstat (limited to 'stdlib/source/lux/data/number.lux')
-rw-r--r--stdlib/source/lux/data/number.lux341
1 files changed, 168 insertions, 173 deletions
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index 573e422d6..13ffe71da 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -51,8 +51,8 @@
(def: abs id)
(def: (signum x)
(case x
- |0 |0
- _ |1))
+ 0 0
+ _ 1))
)
(do-template [<type> <order> <+> <-> <*> </> <%> <=> <<> <0> <1> <-1>]
@@ -107,10 +107,10 @@
(def: top <top>)
(def: bottom <bottom>))]
- [ Nat Enum<Nat> (:coerce Nat -1) |0]
+ [ Nat Enum<Nat> (:coerce Nat -1) 0]
[ Int Enum<Int> +9_223_372_036_854_775_807 -9_223_372_036_854_775_808]
[Frac Enum<Frac> ("lux frac max") ("lux frac min")]
- [ Rev Enum<Rev> (:coerce Rev -1) (:coerce Rev |0)]
+ [ Rev Enum<Rev> (:coerce Rev -1) (:coerce Rev 0)]
)
(do-template [<name> <type> <identity> <compose>]
@@ -118,8 +118,8 @@
(def: identity <identity>)
(def: compose <compose>))]
- [ Add@Monoid<Nat> Nat |0 n/+]
- [ Mul@Monoid<Nat> Nat |1 n/*]
+ [ Add@Monoid<Nat> Nat 0 n/+]
+ [ Mul@Monoid<Nat> Nat 1 n/*]
[ Max@Monoid<Nat> Nat (:: Interval<Nat> bottom) n/max]
[ Min@Monoid<Nat> Nat (:: Interval<Nat> top) n/min]
[ Add@Monoid<Int> Int +0 i/+]
@@ -182,113 +182,113 @@
(def: (binary-character value)
(-> Nat (Maybe Text))
(case value
- |0 (#.Some "0")
- |1 (#.Some "1")
+ 0 (#.Some "0")
+ 1 (#.Some "1")
_ #.None))
(def: (binary-value digit)
(-> Text (Maybe Nat))
(case digit
- "0" (#.Some |0)
- "1" (#.Some |1)
+ "0" (#.Some 0)
+ "1" (#.Some 1)
_ #.None))
(def: (octal-character value)
(-> Nat (Maybe Text))
(case value
- |0 (#.Some "0")
- |1 (#.Some "1")
- |2 (#.Some "2")
- |3 (#.Some "3")
- |4 (#.Some "4")
- |5 (#.Some "5")
- |6 (#.Some "6")
- |7 (#.Some "7")
+ 0 (#.Some "0")
+ 1 (#.Some "1")
+ 2 (#.Some "2")
+ 3 (#.Some "3")
+ 4 (#.Some "4")
+ 5 (#.Some "5")
+ 6 (#.Some "6")
+ 7 (#.Some "7")
_ #.None))
(def: (octal-value digit)
(-> Text (Maybe Nat))
(case digit
- "0" (#.Some |0)
- "1" (#.Some |1)
- "2" (#.Some |2)
- "3" (#.Some |3)
- "4" (#.Some |4)
- "5" (#.Some |5)
- "6" (#.Some |6)
- "7" (#.Some |7)
+ "0" (#.Some 0)
+ "1" (#.Some 1)
+ "2" (#.Some 2)
+ "3" (#.Some 3)
+ "4" (#.Some 4)
+ "5" (#.Some 5)
+ "6" (#.Some 6)
+ "7" (#.Some 7)
_ #.None))
(def: (decimal-character value)
(-> Nat (Maybe Text))
(case value
- |0 (#.Some "0")
- |1 (#.Some "1")
- |2 (#.Some "2")
- |3 (#.Some "3")
- |4 (#.Some "4")
- |5 (#.Some "5")
- |6 (#.Some "6")
- |7 (#.Some "7")
- |8 (#.Some "8")
- |9 (#.Some "9")
+ 0 (#.Some "0")
+ 1 (#.Some "1")
+ 2 (#.Some "2")
+ 3 (#.Some "3")
+ 4 (#.Some "4")
+ 5 (#.Some "5")
+ 6 (#.Some "6")
+ 7 (#.Some "7")
+ 8 (#.Some "8")
+ 9 (#.Some "9")
_ #.None))
(def: (decimal-value digit)
(-> Text (Maybe Nat))
(case digit
- "0" (#.Some |0)
- "1" (#.Some |1)
- "2" (#.Some |2)
- "3" (#.Some |3)
- "4" (#.Some |4)
- "5" (#.Some |5)
- "6" (#.Some |6)
- "7" (#.Some |7)
- "8" (#.Some |8)
- "9" (#.Some |9)
+ "0" (#.Some 0)
+ "1" (#.Some 1)
+ "2" (#.Some 2)
+ "3" (#.Some 3)
+ "4" (#.Some 4)
+ "5" (#.Some 5)
+ "6" (#.Some 6)
+ "7" (#.Some 7)
+ "8" (#.Some 8)
+ "9" (#.Some 9)
_ #.None))
(def: (hexadecimal-character value)
(-> Nat (Maybe Text))
(case value
- |0 (#.Some "0")
- |1 (#.Some "1")
- |2 (#.Some "2")
- |3 (#.Some "3")
- |4 (#.Some "4")
- |5 (#.Some "5")
- |6 (#.Some "6")
- |7 (#.Some "7")
- |8 (#.Some "8")
- |9 (#.Some "9")
- |10 (#.Some "A")
- |11 (#.Some "B")
- |12 (#.Some "C")
- |13 (#.Some "D")
- |14 (#.Some "E")
- |15 (#.Some "F")
+ 0 (#.Some "0")
+ 1 (#.Some "1")
+ 2 (#.Some "2")
+ 3 (#.Some "3")
+ 4 (#.Some "4")
+ 5 (#.Some "5")
+ 6 (#.Some "6")
+ 7 (#.Some "7")
+ 8 (#.Some "8")
+ 9 (#.Some "9")
+ 10 (#.Some "A")
+ 11 (#.Some "B")
+ 12 (#.Some "C")
+ 13 (#.Some "D")
+ 14 (#.Some "E")
+ 15 (#.Some "F")
_ #.None))
(def: (hexadecimal-value digit)
(-> Text (Maybe Nat))
(case digit
- "0" (#.Some |0)
- "1" (#.Some |1)
- "2" (#.Some |2)
- "3" (#.Some |3)
- "4" (#.Some |4)
- "5" (#.Some |5)
- "6" (#.Some |6)
- "7" (#.Some |7)
- "8" (#.Some |8)
- "9" (#.Some |9)
- (^or "a" "A") (#.Some |10)
- (^or "b" "B") (#.Some |11)
- (^or "c" "C") (#.Some |12)
- (^or "d" "D") (#.Some |13)
- (^or "e" "E") (#.Some |14)
- (^or "f" "F") (#.Some |15)
+ "0" (#.Some 0)
+ "1" (#.Some 1)
+ "2" (#.Some 2)
+ "3" (#.Some 3)
+ "4" (#.Some 4)
+ "5" (#.Some 5)
+ "6" (#.Some 6)
+ "7" (#.Some 7)
+ "8" (#.Some 8)
+ "9" (#.Some 9)
+ (^or "a" "A") (#.Some 10)
+ (^or "b" "B") (#.Some 11)
+ (^or "c" "C") (#.Some 12)
+ (^or "d" "D") (#.Some 13)
+ (^or "e" "E") (#.Some 14)
+ (^or "f" "F") (#.Some 15)
_ #.None))
(do-template [<struct> <base> <to-character> <to-value> <error>]
@@ -299,36 +299,31 @@
(let [digit (maybe.assume (<to-character> (n/% <base> input)))
output' ("lux text concat" digit output)
input' (n// <base> input)]
- (if (n/= |0 input')
- ("lux text concat" "|" output')
+ (if (n/= 0 input')
+ output'
(recur input' output')))))
(def: (decode repr)
(let [input-size ("lux text size" repr)]
- (if (n/>= |2 input-size)
- (case ("lux text char" repr |0)
- (^ (#.Some (char "|")))
- (loop [idx |1
- output |0]
- (if (n/< input-size idx)
- (let [digit (maybe.assume (get-char repr idx))]
- (case (<to-value> digit)
- #.None
- (#error.Error ("lux text concat" <error> repr))
-
- (#.Some digit-value)
- (recur (inc idx)
- (|> output (n/* <base>) (n/+ digit-value)))))
- (#error.Success output)))
-
- _
- (#error.Error ("lux text concat" <error> repr)))
+ (if (n/> 0 input-size)
+ (loop [idx 0
+ output 0]
+ (if (n/< input-size idx)
+ (let [digit (maybe.assume (get-char repr idx))]
+ (case (<to-value> digit)
+ #.None
+ (#error.Error ("lux text concat" <error> repr))
+
+ (#.Some digit-value)
+ (recur (inc idx)
+ (|> output (n/* <base>) (n/+ digit-value)))))
+ (#error.Success output)))
(#error.Error ("lux text concat" <error> repr))))))]
- [Binary@Codec<Text,Nat> |2 binary-character binary-value "Invalid binary syntax for Nat: "]
- [Octal@Codec<Text,Nat> |8 octal-character octal-value "Invalid octal syntax for Nat: "]
- [_ |10 decimal-character decimal-value "Invalid syntax for Nat: "]
- [Hex@Codec<Text,Nat> |16 hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Nat: "]
+ [Binary@Codec<Text,Nat> 2 binary-character binary-value "Invalid binary syntax for Nat: "]
+ [Octal@Codec<Text,Nat> 8 octal-character octal-value "Invalid octal syntax for Nat: "]
+ [_ 10 decimal-character decimal-value "Invalid syntax for Nat: "]
+ [Hex@Codec<Text,Nat> 16 hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Nat: "]
)
(def: (int/sign!! value)
@@ -339,7 +334,7 @@
(def: (int/sign?? representation)
(-> Text (Maybe Int))
- (case (get-char representation |0)
+ (case (get-char representation 0)
(^ (#.Some "-"))
(#.Some -1)
@@ -351,7 +346,7 @@
(def: (int-decode-loop input-size repr sign <base> <to-value> <error>)
(-> Nat Text Int Int (-> Text (Maybe Nat)) Text (Error Int))
- (loop [idx |1
+ (loop [idx 1
output +0]
(if (n/< input-size idx)
(let [digit (maybe.assume (get-char repr idx))]
@@ -381,7 +376,7 @@
(def: (decode repr)
(let [input-size ("lux text size" repr)]
- (if (n/> |1 input-size)
+ (if (n/> 1 input-size)
(case (int/sign?? repr)
(#.Some sign)
(int-decode-loop input-size repr sign <base> <to-value> <error>)
@@ -398,17 +393,17 @@
(def: (de-prefix input)
(-> Text Text)
- (maybe.assume ("lux text clip" input |1 ("lux text size" input))))
+ (maybe.assume ("lux text clip" input 1 ("lux text size" input))))
(do-template [<struct> <nat> <char-bit-size> <error>]
[(structure: #export <struct> (Codec Text Rev)
(def: (encode value)
(let [raw-output (de-prefix (:: <nat> encode (:coerce Nat value)))
- max-num-chars (n// <char-bit-size> |64)
+ max-num-chars (n// <char-bit-size> 64)
raw-size ("lux text size" raw-output)
zero-padding (loop [zeroes-left (n/- raw-size max-num-chars)
output ""]
- (if (n/= |0 zeroes-left)
+ (if (n/= 0 zeroes-left)
output
(recur (dec zeroes-left)
("lux text concat" "0" output))))
@@ -417,10 +412,10 @@
(def: (decode repr)
(let [repr-size ("lux text size" repr)]
- (if (n/>= |2 repr-size)
- (case ("lux text char" repr |0)
+ (if (n/>= 2 repr-size)
+ (case ("lux text char" repr 0)
(^multi (^ (#.Some (char ".")))
- [(:: <nat> decode ("lux text concat" "|" (de-prefix repr)))
+ [(:: <nat> decode (de-prefix repr))
(#error.Success output)])
(#error.Success (:coerce Rev output))
@@ -428,9 +423,9 @@
(#error.Error ("lux text concat" <error> repr)))
(#error.Error ("lux text concat" <error> repr))))))]
- [Binary@Codec<Text,Rev> Binary@Codec<Text,Nat> |1 "Invalid binary syntax: "]
- [Octal@Codec<Text,Rev> Octal@Codec<Text,Nat> |3 "Invalid octal syntax: "]
- [Hex@Codec<Text,Rev> Hex@Codec<Text,Nat> |4 "Invalid hexadecimal syntax: "]
+ [Binary@Codec<Text,Rev> Binary@Codec<Text,Nat> 1 "Invalid binary syntax: "]
+ [Octal@Codec<Text,Rev> Octal@Codec<Text,Nat> 3 "Invalid octal syntax: "]
+ [Hex@Codec<Text,Rev> Hex@Codec<Text,Nat> 4 "Invalid hexadecimal syntax: "]
)
(do-template [<struct> <int> <base> <char-set> <error>]
@@ -453,9 +448,9 @@
("lux text concat" whole-part decimal-part)))
(def: (decode repr)
- (case ("lux text index" repr "." |0)
+ (case ("lux text index" repr "." 0)
(#.Some split-index)
- (let [whole-part (maybe.assume ("lux text clip" repr |0 split-index))
+ (let [whole-part (maybe.assume ("lux text clip" repr 0 split-index))
decimal-part (maybe.assume ("lux text clip" repr (inc split-index) ("lux text size" repr)))]
(case [(:: <int> decode whole-part)
(:: <int> decode decimal-part)]
@@ -466,7 +461,7 @@
+1.0)
div-power (loop [muls-left ("lux text size" decimal-part)
output +1.0]
- (if (n/= |0 muls-left)
+ (if (n/= 0 muls-left)
output
(recur (dec muls-left)
(f/* <base> output))))
@@ -501,7 +496,7 @@
(list digits)
(let [boundary (n/- chunk-size num-digits)
chunk (maybe.assume ("lux text clip" digits boundary num-digits))
- remaining (maybe.assume ("lux text clip" digits |0 boundary))]
+ remaining (maybe.assume ("lux text clip" digits 0 boundary))]
(list& chunk (segment-digits chunk-size remaining)))))))
(def: (bin-segment-to-hex input)
@@ -593,15 +588,15 @@
(do-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 (n// <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)
+ (if (n/= 0 num-digits-that-need-padding)
""
(loop [zeroes-left (n/- num-digits-that-need-padding
<base-bits>)
output ""]
- (if (n/= |0 zeroes-left)
+ (if (n/= 0 zeroes-left)
output
(recur (dec zeroes-left)
("lux text concat" "0" output))))))
@@ -615,12 +610,12 @@
(def: <to>
(-> Text Text)
- (|>> (segment-digits |1)
+ (|>> (segment-digits 1)
(map <to-translator>)
re-join-chunks))]
- [binary-to-hex bin-segment-to-hex hex-to-binary hex-segment-to-bin |4]
- [binary-to-octal bin-segment-to-octal octal-to-binary octal-segment-to-bin |3]
+ [binary-to-hex bin-segment-to-hex hex-to-binary hex-segment-to-bin 4]
+ [binary-to-octal bin-segment-to-octal octal-to-binary octal-segment-to-bin 3]
)
(do-template [<struct> <error> <from> <to>]
@@ -628,9 +623,9 @@
(def: (encode value)
(let [sign (:: Number<Frac> signum value)
raw-bin (:: Binary@Codec<Text,Frac> encode value)
- dot-idx (maybe.assume ("lux text index" raw-bin "." |0))
+ dot-idx (maybe.assume ("lux text index" raw-bin "." 0))
whole-part (maybe.assume ("lux text clip" raw-bin
- (if (f/= -1.0 sign) |1 |0)
+ (if (f/= -1.0 sign) 1 0)
dot-idx))
decimal-part (maybe.assume ("lux text clip" raw-bin (inc dot-idx) ("lux text size" raw-bin)))
hex-output (|> (<from> #0 decimal-part)
@@ -640,15 +635,15 @@
hex-output))
(def: (decode repr)
- (let [sign (case ("lux text index" repr "-" |0)
- (#.Some |0)
+ (let [sign (case ("lux text index" repr "-" 0)
+ (#.Some 0)
-1.0
_
+1.0)]
- (case ("lux text index" repr "." |0)
+ (case ("lux text index" repr "." 0)
(#.Some split-index)
- (let [whole-part (maybe.assume ("lux text clip" repr (if (f/= -1.0 sign) |1 |0) split-index))
+ (let [whole-part (maybe.assume ("lux text clip" repr (if (f/= -1.0 sign) 1 0) split-index))
decimal-part (maybe.assume ("lux text clip" repr (inc split-index) ("lux text size" repr)))
as-binary (|> (<to> decimal-part)
("lux text concat" ".")
@@ -688,8 +683,8 @@
(def: (underscore-prefixed? number)
(-> Text Bit)
- (case ("lux text index" number "_" |0)
- (#.Some |0)
+ (case ("lux text index" number "_" 0)
+ (#.Some 0)
#1
_
@@ -758,7 +753,7 @@
(def: (digits-get idx digits)
(-> Nat Digits Nat)
- (maybe.default |0 ("lux array get" digits idx)))
+ (maybe.default 0 ("lux array get" digits idx)))
(def: (digits-put idx digit digits)
(-> Nat Nat Digits Digits)
@@ -771,22 +766,22 @@
(def: (digits-times-5! idx output)
(-> Nat Digits Digits)
(loop [idx idx
- carry |0
+ carry 0
output output]
(if (i/>= +0 (:coerce Int idx))
(let [raw (|> (digits-get idx output)
- (n/* |5)
+ (n/* 5)
(n/+ carry))]
(recur (dec idx)
- (n// |10 raw)
- (digits-put idx (n/% |10 raw) output)))
+ (n// 10 raw)
+ (digits-put idx (n/% 10 raw) output)))
output)))
(def: (digits-power power)
(-> Nat Digits)
(loop [times power
output (|> (make-digits [])
- (digits-put power |1))]
+ (digits-put power 1))]
(if (i/>= +0 (:coerce Int times))
(recur (dec times)
(digits-times-5! power output))
@@ -799,7 +794,7 @@
output ""]
(if (i/>= +0 (:coerce Int idx))
(let [digit (digits-get idx digits)]
- (if (and (n/= |0 digit)
+ (if (and (n/= 0 digit)
all-zeroes?)
(recur (dec idx) #1 output)
(recur (dec idx)
@@ -814,7 +809,7 @@
(def: (digits-add param subject)
(-> Digits Digits Digits)
(loop [idx (dec i64.width)
- carry |0
+ carry 0
output (make-digits [])]
(if (i/>= +0 (:coerce Int idx))
(let [raw ($_ n/+
@@ -822,19 +817,19 @@
(digits-get idx param)
(digits-get idx subject))]
(recur (dec idx)
- (n// |10 raw)
- (digits-put idx (n/% |10 raw) output)))
+ (n// 10 raw)
+ (digits-put idx (n/% 10 raw) output)))
output)))
(def: (text-to-digits input)
(-> Text (Maybe Digits))
(let [length ("lux text size" input)]
(if (n/<= i64.width length)
- (loop [idx |0
+ (loop [idx 0
output (make-digits [])]
(if (n/< length idx)
(let [char (maybe.assume (get-char input idx))]
- (case ("lux text index" "+0123456789" char |0)
+ (case ("lux text index" "+0123456789" char 0)
#.None
#.None
@@ -846,7 +841,7 @@
(def: (digits-lt param subject)
(-> Digits Digits Bit)
- (loop [idx |0]
+ (loop [idx 0]
(and (n/< i64.width idx)
(let [pd (digits-get idx param)
sd (digits-get idx subject)]
@@ -860,11 +855,11 @@
(if (n/>= param sd)
(digits-put idx (n/- param sd) subject)
(let [diff (|> sd
- (n/+ |10)
+ (n/+ 10)
(n/- param))]
(|> subject
(digits-put idx diff)
- (digits-sub-once! (dec idx) |1))))))
+ (digits-sub-once! (dec idx) 1))))))
(def: (digits-sub! param subject)
(-> Digits Digits Digits)
@@ -879,7 +874,7 @@
(def: (encode input)
(let [input (:coerce Nat input)
last-idx (dec i64.width)]
- (if (n/= |0 input)
+ (if (n/= 0 input)
".0"
(loop [idx last-idx
digits (make-digits [])]
@@ -896,21 +891,21 @@
(def: (decode input)
(let [length ("lux text size" input)
- dotted? (case ("lux text index" input "." |0)
- (#.Some |0)
+ dotted? (case ("lux text index" input "." 0)
+ (#.Some 0)
#1
_
#0)]
(if (and dotted?
(n/<= (inc i64.width) length))
- (case (|> ("lux text clip" input |1 length)
+ (case (|> ("lux text clip" input 1 length)
maybe.assume
text-to-digits)
(#.Some digits)
(loop [digits digits
- idx |0
- output |0]
+ idx 0
+ output 0]
(if (n/< i64.width idx)
(let [power (digits-power idx)]
(if (digits-lt power digits)
@@ -931,58 +926,58 @@
(f// ("lux math log" +2.0)
("lux math log" input)))
-(def: double-bias Nat |1023)
+(def: double-bias Nat 1023)
-(def: mantissa-size Nat |52)
-(def: exponent-size Nat |11)
+(def: mantissa-size Nat 52)
+(def: exponent-size Nat 11)
(def: #export (frac-to-bits input)
(-> Frac I64)
(i64 (cond (not-a-number? input)
- (hex "|7FF7FFFFFFFFFFFF")
+ (hex "7FF7FFFFFFFFFFFF")
(f/= positive-infinity input)
- (hex "|7FF0000000000000")
+ (hex "7FF0000000000000")
(f/= negative-infinity input)
- (hex "|FFF0000000000000")
+ (hex "FFF0000000000000")
(f/= +0.0 input)
(let [reciprocal (f// input +1.0)]
(if (f/= positive-infinity reciprocal)
## Positive zero
- (hex "|0000000000000000")
+ (hex "0000000000000000")
## Negative zero
- (hex "|8000000000000000")))
+ (hex "8000000000000000")))
## else
(let [sign (:: Number<Frac> signum input)
input (:: Number<Frac> abs input)
exponent ("lux math floor" (log2 input))
- exponent-mask (|> |1 (i64.left-shift exponent-size) dec)
+ exponent-mask (|> 1 (i64.left-shift exponent-size) dec)
mantissa (|> input
## Normalize
(f// ("lux math pow" +2.0 exponent))
## Make it int-equivalent
(f/* ("lux math pow" +2.0 +52.0)))
- sign-bit (if (f/= -1.0 sign) |1 |0)
+ sign-bit (if (f/= -1.0 sign) 1 0)
exponent-bits (|> exponent frac-to-int .nat (n/+ double-bias) (i64.and exponent-mask))
mantissa-bits (|> mantissa frac-to-int .nat)]
($_ i64.or
- (i64.left-shift |63 sign-bit)
+ (i64.left-shift 63 sign-bit)
(i64.left-shift mantissa-size exponent-bits)
(i64.clear mantissa-size mantissa-bits)))
)))
(do-template [<getter> <mask> <size> <offset>]
- [(def: <mask> (|> |1 (i64.left-shift <size>) dec (i64.left-shift <offset>)))
+ [(def: <mask> (|> 1 (i64.left-shift <size>) dec (i64.left-shift <offset>)))
(def: (<getter> input)
(-> (I64 Any) I64)
(|> input (i64.and <mask>) (i64.logical-right-shift <offset>) i64))]
- [mantissa mantissa-mask mantissa-size |0]
+ [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 (n/+ exponent-size mantissa-size)]
)
(def: #export (bits-to-frac input)
@@ -990,15 +985,15 @@
(let [S (sign input)
E (exponent input)
M (mantissa input)]
- (cond (n/= (hex "|7FF") E)
- (if (n/= |0 M)
- (if (n/= |0 S)
+ (cond (n/= (hex "7FF") E)
+ (if (n/= 0 M)
+ (if (n/= 0 S)
positive-infinity
negative-infinity)
not-a-number)
- (and (n/= |0 E) (n/= |0 M))
- (if (n/= |0 S)
+ (and (n/= 0 E) (n/= 0 M))
+ (if (n/= 0 S)
+0.0
(f/* -1.0 +0.0))
@@ -1011,7 +1006,7 @@
("lux math pow" +2.0))
shifted (f/* power
normalized)]
- (if (n/= |0 S)
+ (if (n/= 0 S)
shifted
(f/* -1.0 shifted))))))