aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/number
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/data/number')
-rw-r--r--stdlib/source/lux/data/number/complex.lux90
-rw-r--r--stdlib/source/lux/data/number/ratio.lux28
2 files changed, 59 insertions, 59 deletions
diff --git a/stdlib/source/lux/data/number/complex.lux b/stdlib/source/lux/data/number/complex.lux
index 783c8eb81..d17180530 100644
--- a/stdlib/source/lux/data/number/complex.lux
+++ b/stdlib/source/lux/data/number/complex.lux
@@ -1,4 +1,4 @@
-(;module: {#;doc "Complex arithmetic."}
+(.module: {#.doc "Complex arithmetic."}
lux
(lux [math]
(control [eq #+ Eq]
@@ -20,13 +20,13 @@
{#real Frac
#imaginary Frac})
-(syntax: #export (complex real [?imaginary (p;maybe s;any)])
- {#;doc (doc "Complex literals."
+(syntax: #export (complex real [?imaginary (p.maybe s.any)])
+ {#.doc (doc "Complex literals."
(complex real imaginary)
"The imaginary part can be omitted if it's 0."
(complex real))}
- (wrap (list (` {#;;real (~ real)
- #;;imaginary (~ (maybe;default (' 0.0)
+ (wrap (list (` {#..real (~ real)
+ #..imaginary (~ (maybe.default (' 0.0)
?imaginary))}))))
(def: #export i Complex (complex 0.0 1.0))
@@ -36,8 +36,8 @@
(def: #export zero Complex (complex 0.0 0.0))
(def: #export (not-a-number? complex)
- (or (number;not-a-number? (get@ #real complex))
- (number;not-a-number? (get@ #imaginary complex))))
+ (or (number.not-a-number? (get@ #real complex))
+ (number.not-a-number? (get@ #imaginary complex))))
(def: #export (c/= param input)
(-> Complex Complex Bool)
@@ -117,60 +117,60 @@
(-> Complex Complex Complex)
(let [scaled (c// param input)
quotient (|> scaled
- (update@ #real math;floor)
- (update@ #imaginary math;floor))]
+ (update@ #real math.floor)
+ (update@ #imaginary math.floor))]
(c/- (c/* quotient param)
input)))
(def: #export (cos subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject]
- {#real (f/* (math;cosh imaginary)
- (math;cos real))
- #imaginary (f/* (math;sinh imaginary)
- (frac/negate (math;sin real)))}))
+ {#real (f/* (math.cosh imaginary)
+ (math.cos real))
+ #imaginary (f/* (math.sinh imaginary)
+ (frac/negate (math.sin real)))}))
(def: #export (cosh subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject]
- {#real (f/* (math;cos imaginary)
- (math;cosh real))
- #imaginary (f/* (math;sin imaginary)
- (math;sinh real))}))
+ {#real (f/* (math.cos imaginary)
+ (math.cosh real))
+ #imaginary (f/* (math.sin imaginary)
+ (math.sinh real))}))
(def: #export (sin subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject]
- {#real (f/* (math;cosh imaginary)
- (math;sin real))
- #imaginary (f/* (math;sinh imaginary)
- (math;cos real))}))
+ {#real (f/* (math.cosh imaginary)
+ (math.sin real))
+ #imaginary (f/* (math.sinh imaginary)
+ (math.cos real))}))
(def: #export (sinh subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject]
- {#real (f/* (math;cos imaginary)
- (math;sinh real))
- #imaginary (f/* (math;sin imaginary)
- (math;cosh real))}))
+ {#real (f/* (math.cos imaginary)
+ (math.sinh real))
+ #imaginary (f/* (math.sin imaginary)
+ (math.cosh real))}))
(def: #export (tan subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject
r2 (f/* 2.0 real)
i2 (f/* 2.0 imaginary)
- d (f/+ (math;cos r2) (math;cosh i2))]
- {#real (f// d (math;sin r2))
- #imaginary (f// d (math;sinh i2))}))
+ d (f/+ (math.cos r2) (math.cosh i2))]
+ {#real (f// d (math.sin r2))
+ #imaginary (f// d (math.sinh i2))}))
(def: #export (tanh subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject
r2 (f/* 2.0 real)
i2 (f/* 2.0 imaginary)
- d (f/+ (math;cosh r2) (math;cos i2))]
- {#real (f// d (math;sinh r2))
- #imaginary (f// d (math;sin i2))}))
+ d (f/+ (math.cosh r2) (math.cos i2))]
+ {#real (f// d (math.sinh r2))
+ #imaginary (f// d (math.sin i2))}))
(def: #export (c/abs subject)
(-> Complex Complex)
@@ -180,12 +180,12 @@
(if (f/= 0.0 imaginary)
(frac/abs real)
(let [q (f// imaginary real)]
- (f/* (math;root2 (f/+ 1.0 (f/* q q)))
+ (f/* (math.root2 (f/+ 1.0 (f/* q q)))
(frac/abs imaginary))))
(if (f/= 0.0 real)
(frac/abs imaginary)
(let [q (f// real imaginary)]
- (f/* (math;root2 (f/+ 1.0 (f/* q q)))
+ (f/* (math.root2 (f/+ 1.0 (f/* q q)))
(frac/abs real))))
))))
@@ -208,15 +208,15 @@
(def: #export (exp subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject
- r-exp (math;exp real)]
- {#real (f/* r-exp (math;cos imaginary))
- #imaginary (f/* r-exp (math;sin imaginary))}))
+ r-exp (math.exp real)]
+ {#real (f/* r-exp (math.cos imaginary))
+ #imaginary (f/* r-exp (math.sin imaginary))}))
(def: #export (log subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject]
- {#real (|> subject c/abs (get@ #real) math;log)
- #imaginary (math;atan2 real imaginary)}))
+ {#real (|> subject c/abs (get@ #real) math.log)
+ #imaginary (math.atan2 real imaginary)}))
(do-template [<name> <type> <op>]
[(def: #export (<name> param input)
@@ -233,7 +233,7 @@
(def: #export (root2 (^@ input (^slots [#real #imaginary])))
(-> Complex Complex)
- (let [t (|> input c/abs (get@ #real) (f/+ (frac/abs real)) (f// 2.0) math;root2)]
+ (let [t (|> input c/abs (get@ #real) (f/+ (frac/abs real)) (f// 2.0) math.root2)]
(if (f/>= 0.0 real)
{#real t
#imaginary (f// (f/* 2.0 t)
@@ -286,24 +286,24 @@
(def: #export (argument (^slots [#real #imaginary]))
(-> Complex Frac)
- (math;atan2 real imaginary))
+ (math.atan2 real imaginary))
(def: #export (nth-roots nth input)
(-> Nat Complex (List Complex))
(if (n/= +0 nth)
(list)
(let [r-nth (|> nth nat-to-int int-to-frac)
- nth-root-of-abs (|> input c/abs (get@ #real) (math;pow (f// r-nth 1.0)))
+ nth-root-of-abs (|> input c/abs (get@ #real) (math.pow (f// r-nth 1.0)))
nth-phi (|> input argument (f// r-nth))
- slice (|> math;pi (f/* 2.0) (f// r-nth))]
- (|> (list;n/range +0 (n/dec nth))
+ slice (|> math.pi (f/* 2.0) (f// r-nth))]
+ (|> (list.n/range +0 (n/dec nth))
(L/map (function [nth']
(let [inner (|> nth' nat-to-int int-to-frac
(f/* slice)
(f/+ nth-phi))
real (f/* nth-root-of-abs
- (math;cos inner))
+ (math.cos inner))
imaginary (f/* nth-root-of-abs
- (math;sin inner))]
+ (math.sin inner))]
{#real real
#imaginary imaginary})))))))
diff --git a/stdlib/source/lux/data/number/ratio.lux b/stdlib/source/lux/data/number/ratio.lux
index 23e128464..6f5b64f5e 100644
--- a/stdlib/source/lux/data/number/ratio.lux
+++ b/stdlib/source/lux/data/number/ratio.lux
@@ -1,4 +1,4 @@
-(;module: {#;doc "Rational arithmetic."}
+(.module: {#.doc "Rational arithmetic."}
lux
(lux [math]
(control [eq #+ Eq]
@@ -23,7 +23,7 @@
(def: #hidden (normalize (^slots [#numerator #denominator]))
(-> Ratio Ratio)
- (let [common (math;gcd numerator denominator)]
+ (let [common (math.gcd numerator denominator)]
{#numerator (n// common numerator)
#denominator (n// common denominator)}))
@@ -103,7 +103,7 @@
(struct: #export _ (Eq Ratio)
(def: = r/=))
-(struct: #export _ (order;Order Ratio)
+(struct: #export _ (order.Order Ratio)
(def: eq Eq<Ratio>)
(def: < r/<)
(def: <= r/<=)
@@ -128,10 +128,10 @@
(def: part-encode
(-> Nat Text)
- (|>> n/encode (text;split +1) maybe;assume product;right))
+ (|>> n/encode (text.split +1) maybe.assume product.right))
(def: part-decode
- (-> Text (E;Error Nat))
+ (-> Text (E.Error Nat))
(|>> (format "+") n/decode))
(struct: #export _ (Codec Text Ratio)
@@ -139,22 +139,22 @@
($_ Text/compose (part-encode numerator) separator (part-encode denominator)))
(def: (decode input)
- (case (text;split-with separator input)
- (#;Some [num denom])
- (do E;Monad<Error>
+ (case (text.split-with separator input)
+ (#.Some [num denom])
+ (do E.Monad<Error>
[numerator (part-decode num)
denominator (part-decode denom)]
(wrap (normalize {#numerator numerator
#denominator denominator})))
- #;None
- (#;Left (Text/compose "Invalid syntax for ratio: " input)))))
+ #.None
+ (#.Left (Text/compose "Invalid syntax for ratio: " input)))))
-(syntax: #export (ratio numerator [?denominator (p;maybe s;any)])
- {#;doc (doc "Rational literals."
+(syntax: #export (ratio numerator [?denominator (p.maybe s.any)])
+ {#.doc (doc "Rational literals."
(ratio numerator denominator)
"The denominator can be omitted if it's 1."
(ratio numerator))}
- (wrap (list (` (normalize {#;;numerator (~ numerator)
- #;;denominator (~ (maybe;default (' +1)
+ (wrap (list (` (normalize {#..numerator (~ numerator)
+ #..denominator (~ (maybe.default (' +1)
?denominator))})))))