aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data
diff options
context:
space:
mode:
authorEduardo Julian2018-07-28 14:55:30 -0400
committerEduardo Julian2018-07-28 14:55:30 -0400
commit15e71e57b688f5079fe606b2fee5e3efd2a5d5a7 (patch)
treeb59e411ebc82a4fb4fdfe66efcc2817fc83c6188 /stdlib/source/lux/data
parentdff8878c13610ae8d1207aaabefbecc88cd3911f (diff)
Added "+" sign to positive Int.
Diffstat (limited to 'stdlib/source/lux/data')
-rw-r--r--stdlib/source/lux/data/collection/row.lux2
-rw-r--r--stdlib/source/lux/data/collection/sequence.lux2
-rw-r--r--stdlib/source/lux/data/collection/tree/rose.lux6
-rw-r--r--stdlib/source/lux/data/color.lux120
-rw-r--r--stdlib/source/lux/data/error.lux8
-rw-r--r--stdlib/source/lux/data/format/json.lux2
-rw-r--r--stdlib/source/lux/data/maybe.lux4
-rw-r--r--stdlib/source/lux/data/number.lux256
-rw-r--r--stdlib/source/lux/data/number/complex.lux46
-rw-r--r--stdlib/source/lux/data/text/regex.lux5
10 files changed, 234 insertions, 217 deletions
diff --git a/stdlib/source/lux/data/collection/row.lux b/stdlib/source/lux/data/collection/row.lux
index ddedad6c5..c9e2c6786 100644
--- a/stdlib/source/lux/data/collection/row.lux
+++ b/stdlib/source/lux/data/collection/row.lux
@@ -343,7 +343,7 @@
## [Syntax]
(syntax: #export (row {elems (p.some s.any)})
{#.doc (doc "Row literals."
- (row 10 20 30 40))}
+ (row +10 +20 +30 +40))}
(wrap (list (` (from-list (list (~+ elems)))))))
## [Structures]
diff --git a/stdlib/source/lux/data/collection/sequence.lux b/stdlib/source/lux/data/collection/sequence.lux
index 95d60b555..ed06547c2 100644
--- a/stdlib/source/lux/data/collection/sequence.lux
+++ b/stdlib/source/lux/data/collection/sequence.lux
@@ -138,7 +138,7 @@
{branches (p.some s.any)})
{#.doc (doc "Allows destructuring of sequences in pattern-matching expressions."
"Caveat emptor: Only use it for destructuring, and not for testing values within the sequences."
- (let [(^sequence& x y z _tail) (some-sequence-func 1 2 3)]
+ (let [(^sequence& x y z _tail) (some-sequence-func +1 +2 +3)]
(func x y z)))}
(with-gensyms [g!sequence]
(let [body+ (` (let [(~+ (list/join (list/map (function (_ pattern)
diff --git a/stdlib/source/lux/data/collection/tree/rose.lux b/stdlib/source/lux/data/collection/tree/rose.lux
index 62b65422a..fc25f414f 100644
--- a/stdlib/source/lux/data/collection/tree/rose.lux
+++ b/stdlib/source/lux/data/collection/tree/rose.lux
@@ -49,9 +49,9 @@
(syntax: #export (tree {root tree^})
{#.doc (doc "Tree literals."
- (tree Int [10 {20 {}
- 30 {}
- 40 {}}]))}
+ (tree Int [+10 {+20 {}
+ +30 {}
+ +40 {}}]))}
(wrap (list (` (~ (loop [[value children] root]
(` {#value (~ value)
#children (list (~+ (list/map recur children)))})))))))
diff --git a/stdlib/source/lux/data/color.lux b/stdlib/source/lux/data/color.lux
index c708e8775..2eb8bd35f 100644
--- a/stdlib/source/lux/data/color.lux
+++ b/stdlib/source/lux/data/color.lux
@@ -53,62 +53,62 @@
blue (scale-down blue)
max ($_ f/max red green blue)
min ($_ f/min red green blue)
- luminance (|> (f/+ max min) (f// 2.0))]
+ luminance (|> (f/+ max min) (f// +2.0))]
(if (f/= max min)
## Achromatic
- [0.0 0.0 luminance]
+ [+0.0 +0.0 luminance]
## Chromatic
(let [diff (|> max (f/- min))
saturation (|> diff
- (f// (if (f/> 0.5 luminance)
- (|> 2.0 (f/- max) (f/- min))
+ (f// (if (f/> +0.5 luminance)
+ (|> +2.0 (f/- max) (f/- min))
(|> max (f/+ min)))))
hue' (cond (f/= red max)
(|> green (f/- blue) (f// diff)
- (f/+ (if (f/< blue green) 6.0 0.0)))
+ (f/+ (if (f/< blue green) +6.0 +0.0)))
(f/= green max)
(|> blue (f/- red) (f// diff)
- (f/+ 2.0))
+ (f/+ +2.0))
## (f/= blue max)
(|> red (f/- green) (f// diff)
- (f/+ 4.0)))]
- [(|> hue' (f// 6.0))
+ (f/+ +4.0)))]
+ [(|> hue' (f// +6.0))
saturation
luminance]))))
(def: (hue-to-rgb p q t)
(-> Frac Frac Frac Frac)
- (let [t (cond (f/< 0.0 t) (f/+ 1.0 t)
- (f/> 1.0 t) (f/- 1.0 t)
+ (let [t (cond (f/< +0.0 t) (f/+ +1.0 t)
+ (f/> +1.0 t) (f/- +1.0 t)
## else
t)
- f2/3 (f// 3.0 2.0)]
- (cond (f/< (f// 6.0 1.0) t)
- (|> q (f/- p) (f/* 6.0) (f/* t) (f/+ p))
+ f2/3 (f// +3.0 +2.0)]
+ (cond (f/< (f// +6.0 +1.0) t)
+ (|> q (f/- p) (f/* +6.0) (f/* t) (f/+ p))
- (f/< (f// 2.0 1.0) t)
+ (f/< (f// +2.0 +1.0) t)
q
(f/< f2/3 t)
- (|> q (f/- p) (f/* (|> f2/3 (f/- t))) (f/* 6.0) (f/+ p))
+ (|> q (f/- p) (f/* (|> f2/3 (f/- t))) (f/* +6.0) (f/+ p))
## else
p)))
(def: #export (from-hsl [hue saturation luminance])
(-> [Frac Frac Frac] Color)
- (if (f/= 0.0 saturation)
+ (if (f/= +0.0 saturation)
## Achromatic
(let [intensity (scale-up luminance)]
(color [intensity intensity intensity]))
## Chromatic
- (let [q (if (f/< 0.5 luminance)
- (|> saturation (f/+ 1.0) (f/* luminance))
+ (let [q (if (f/< +0.5 luminance)
+ (|> saturation (f/+ +1.0) (f/* luminance))
(|> luminance (f/+ saturation) (f/- (f/* saturation luminance))))
- p (|> luminance (f/* 2.0) (f/- q))
- third (|> 1.0 (f// 3.0))]
+ p (|> luminance (f/* +2.0) (f/- q))
+ third (|> +1.0 (f// +3.0))]
(color [(scale-up (|> hue (f/+ third) (hue-to-rgb p q)))
(scale-up (|> hue (hue-to-rgb p q)))
(scale-up (|> hue (f/- third) (hue-to-rgb p q)))]))))
@@ -123,38 +123,38 @@
min ($_ f/min red green blue)
brightness max
diff (|> max (f/- min))
- saturation (if (f/= 0.0 max)
- 0.0
+ saturation (if (f/= +0.0 max)
+ +0.0
(|> diff (f// max)))]
(if (f/= max min)
## Achromatic
- [0.0 saturation brightness]
+ [+0.0 saturation brightness]
## Chromatic
(let [hue (cond (f/= red max)
(|> green (f/- blue) (f// diff)
- (f/+ (if (f/< blue green) 6.0 0.0)))
+ (f/+ (if (f/< blue green) +6.0 +0.0)))
(f/= green max)
(|> blue (f/- red) (f// diff)
- (f/+ 2.0))
+ (f/+ +2.0))
## (f/= blue max)
(|> red (f/- green) (f// diff)
- (f/+ 4.0)))]
- [(|> hue (f// 6.0))
+ (f/+ +4.0)))]
+ [(|> hue (f// +6.0))
saturation
brightness]))))
(def: #export (from-hsb [hue saturation brightness])
(-> [Frac Frac Frac] Color)
- (let [hue (|> hue (f/* 6.0))
+ (let [hue (|> hue (f/* +6.0))
i (math.floor hue)
f (|> hue (f/- i))
- p (|> 1.0 (f/- saturation) (f/* brightness))
- q (|> 1.0 (f/- (f/* f saturation)) (f/* brightness))
- t (|> 1.0 (f/- (|> 1.0 (f/- f) (f/* saturation))) (f/* brightness))
+ p (|> +1.0 (f/- saturation) (f/* brightness))
+ q (|> +1.0 (f/- (f/* f saturation)) (f/* brightness))
+ t (|> +1.0 (f/- (|> +1.0 (f/- f) (f/* saturation))) (f/* brightness))
v brightness
- mod (|> i (f/% 6.0) frac-to-int .nat)
+ mod (|> i (f/% +6.0) frac-to-int .nat)
red (case mod |0 v |1 q |2 p |3 p |4 t |5 v _ (undefined))
green (case mod |0 t |1 v |2 v |3 q |4 p |5 p _ (undefined))
blue (case mod |0 p |1 p |2 t |3 v |4 v |5 q _ (undefined))]
@@ -168,34 +168,34 @@
red (scale-down red)
green (scale-down green)
blue (scale-down blue)
- key (|> 1.0 (f/- ($_ f/max red green blue)))
- f (if (f/< 1.0 key)
- (|> 1.0 (f// (|> 1.0 (f/- key))))
- 0.0)
- cyan (|> 1.0 (f/- red) (f/- key) (f/* f))
- magenta (|> 1.0 (f/- green) (f/- key) (f/* f))
- yellow (|> 1.0 (f/- blue) (f/- key) (f/* f))]
+ key (|> +1.0 (f/- ($_ f/max red green blue)))
+ f (if (f/< +1.0 key)
+ (|> +1.0 (f// (|> +1.0 (f/- key))))
+ +0.0)
+ cyan (|> +1.0 (f/- red) (f/- key) (f/* f))
+ magenta (|> +1.0 (f/- green) (f/- key) (f/* f))
+ yellow (|> +1.0 (f/- blue) (f/- key) (f/* f))]
[cyan magenta yellow key]))
(def: #export (from-cmyk [cyan magenta yellow key])
(-> [Frac Frac Frac Frac] Color)
- (if (f/= 1.0 key)
+ (if (f/= +1.0 key)
(color [|0 |0 |0])
- (let [red (|> (|> 1.0 (f/- cyan))
- (f/* (|> 1.0 (f/- key))))
- green (|> (|> 1.0 (f/- magenta))
- (f/* (|> 1.0 (f/- key))))
- blue (|> (|> 1.0 (f/- yellow))
- (f/* (|> 1.0 (f/- key))))]
+ (let [red (|> (|> +1.0 (f/- cyan))
+ (f/* (|> +1.0 (f/- key))))
+ green (|> (|> +1.0 (f/- magenta))
+ (f/* (|> +1.0 (f/- key))))
+ blue (|> (|> +1.0 (f/- yellow))
+ (f/* (|> +1.0 (f/- key))))]
(color [(scale-up red) (scale-up green) (scale-up blue)]))))
(def: (normalize ratio)
(-> Frac Frac)
- (cond (f/> 1.0 ratio)
- (f/% 1.0 ratio)
+ (cond (f/> +1.0 ratio)
+ (f/% +1.0 ratio)
- (f/< 0.0 ratio)
- (|> 1.0 (f/+ (f/% 1.0 ratio)))
+ (f/< +0.0 ratio)
+ (|> +1.0 (f/+ (f/% +1.0 ratio)))
## else
ratio))
@@ -203,7 +203,7 @@
(def: #export (interpolate ratio end start)
(-> Frac Color Color Color)
(let [dS (normalize ratio)
- dE (|> 1.0 (f/- dS))
+ dE (|> +1.0 (f/- dS))
interpolate' (: (-> Nat Nat Nat)
(function (_ end start)
(|> (|> start .int int-to-frac (f/* dS))
@@ -242,8 +242,8 @@
(let [[hue saturation luminance] (to-hsl color)]
(from-hsl [hue
(|> saturation
- (f/* (|> 1.0 (<op> (normalize ratio))))
- (f/min 1.0))
+ (f/* (|> +1.0 (<op> (normalize ratio))))
+ (f/min +1.0))
luminance])))]
[saturate f/+]
@@ -253,7 +253,7 @@
(def: #export (gray-scale color)
(-> Color Color)
(let [[_ _ luminance] (to-hsl color)]
- (from-hsl [0.0 0.0 luminance])))
+ (from-hsl [+0.0 +0.0 luminance])))
(do-template [<name> <1> <2>]
[(def: #export (<name> color)
@@ -263,9 +263,9 @@
(from-hsl [(|> hue (f/+ <1>) normalize) saturation luminance])
(from-hsl [(|> hue (f/+ <2>) normalize) saturation luminance])]))]
- [triad (|> 1.0 (f// 3.0)) (|> 2.0 (f// 3.0))]
- [clash (|> 1.0 (f// 4.0)) (|> 3.0 (f// 4.0))]
- [split-complement (|> 1.0 (f// 5.0)) (|> 3.0 (f// 5.0))]
+ [triad (|> +1.0 (f// +3.0)) (|> +2.0 (f// +3.0))]
+ [clash (|> +1.0 (f// +4.0)) (|> +3.0 (f// +4.0))]
+ [split-complement (|> +1.0 (f// +5.0)) (|> +3.0 (f// +5.0))]
)
(do-template [<name> <1> <2> <3>]
@@ -277,8 +277,8 @@
(from-hsl [(|> hue (f/+ <2>) normalize) saturation luminance])
(from-hsl [(|> hue (f/+ <3>) normalize) saturation luminance])]))]
- [square (|> 1.0 (f// 4.0)) (|> 2.0 (f// 4.0)) (|> 3.0 (f// 4.0))]
- [tetradic (|> 2.0 (f// 12.0)) (|> 6.0 (f// 12.0)) (|> 8.0 (f// 12.0))]
+ [square (|> +1.0 (f// +4.0)) (|> +2.0 (f// +4.0)) (|> +3.0 (f// +4.0))]
+ [tetradic (|> +2.0 (f// +12.0)) (|> +6.0 (f// +12.0)) (|> +8.0 (f// +12.0))]
)
(def: #export (analogous results slice color)
@@ -298,7 +298,7 @@
(if (n/= |0 results)
(list)
(let [[hue saturation brightness] (to-hsb color)
- slice (|> 1.0 (f// (|> results .int int-to-frac)))]
+ slice (|> +1.0 (f// (|> results .int int-to-frac)))]
(|> (list.n/range |0 (dec results))
(list/map (|>> .int int-to-frac
(f/* slice)
diff --git a/stdlib/source/lux/data/error.lux b/stdlib/source/lux/data/error.lux
index 8054736e9..17d88a5a0 100644
--- a/stdlib/source/lux/data/error.lux
+++ b/stdlib/source/lux/data/error.lux
@@ -86,10 +86,10 @@
(macro: #export (default tokens compiler)
{#.doc (doc "Allows you to provide a default value that will be used"
"if a (Error x) value turns out to be #Error."
- (is? 10
- (default 20 (#Success 10)))
- (is? 20
- (default 20 (#Error "KABOOM!"))))}
+ (is? +10
+ (default +20 (#Success +10)))
+ (is? +20
+ (default +20 (#Error "KABOOM!"))))}
(case tokens
(^ (list else error))
(#Success [compiler (list (` (case (~ error)
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux
index 02c05f5dd..549631f2a 100644
--- a/stdlib/source/lux/data/format/json.lux
+++ b/stdlib/source/lux/data/format/json.lux
@@ -55,7 +55,7 @@
(syntax: #export (json token)
{#.doc (doc "A simple way to produce JSON literals."
(json #1)
- (json 123.456)
+ (json +123.456)
(json "Some text")
(json #null)
(json ["this" "is" "an" "array"])
diff --git a/stdlib/source/lux/data/maybe.lux b/stdlib/source/lux/data/maybe.lux
index d6b44e02d..57ff95727 100644
--- a/stdlib/source/lux/data/maybe.lux
+++ b/stdlib/source/lux/data/maybe.lux
@@ -84,9 +84,9 @@
(macro: #export (default tokens state)
{#.doc "## Allows you to provide a default value that will be used
## if a (Maybe x) value turns out to be #.None.
- (default 20 (#.Some 10)) => 10
+ (default +20 (#.Some +10)) => +10
- (default 20 #.None) => 20"}
+ (default +20 #.None) => +20"}
(case tokens
(^ (list else maybe))
(let [g!temp (: Code [dummy-cursor (#.Identifier ["" ""])])
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index 9934af3de..573e422d6 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -10,7 +10,7 @@
interval
[codec (#+ Codec)]]
[data
- ["e" error]
+ ["." error (#+ Error)]
["." maybe]
["." text]]]
[/
@@ -74,8 +74,8 @@
<1>))
)]
- [ Int Order<Int> i/+ i/- i/* i// i/% i/= i/< 0 1 -1]
- [Frac Order<Frac> f/+ f/- f/* f// f/% f/= f/< 0.0 1.0 -1.0]
+ [ Int Order<Int> i/+ i/- i/* i// i/% i/= i/< +0 +1 -1]
+ [Frac Order<Frac> f/+ f/- f/* f// f/% f/= f/< +0.0 +1.0 -1.0]
)
(structure: #export _ (Number Rev)
@@ -108,7 +108,7 @@
(def: bottom <bottom>))]
[ Nat Enum<Nat> (:coerce Nat -1) |0]
- [ Int Enum<Int> 9_223_372_036_854_775_807 -9_223_372_036_854_775_808]
+ [ 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)]
)
@@ -122,12 +122,12 @@
[ 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/+]
- [ Mul@Monoid<Int> Int 1 i/*]
+ [ Add@Monoid<Int> Int +0 i/+]
+ [ Mul@Monoid<Int> Int +1 i/*]
[ Max@Monoid<Int> Int (:: Interval<Int> bottom) i/max]
[ Min@Monoid<Int> Int (:: Interval<Int> top) i/min]
- [Add@Monoid<Frac> Frac 0.0 f/+]
- [Mul@Monoid<Frac> Frac 1.0 f/*]
+ [Add@Monoid<Frac> Frac +0.0 f/+]
+ [Mul@Monoid<Frac> Frac +1.0 f/*]
[Max@Monoid<Frac> Frac (:: Interval<Frac> bottom) f/max]
[Min@Monoid<Frac> Frac (:: Interval<Frac> top) f/min]
[ Add@Monoid<Rev> Rev (:: Interval<Rev> bottom) r/+]
@@ -140,10 +140,10 @@
[(def: #export <name>
{#.doc <doc>}
Frac
- (f// 0.0 <numerator>))]
+ (f// +0.0 <numerator>))]
- [not-a-number 0.0 "Not a number."]
- [positive-infinity 1.0 "Positive infinity."]
+ [not-a-number +0.0 "Not a number."]
+ [positive-infinity +1.0 "Positive infinity."]
[negative-infinity -1.0 "Negative infinity."]
)
@@ -166,10 +166,10 @@
(def: (decode input)
(case (<decoder> [input])
(#.Some value)
- (#e.Success value)
+ (#error.Success value)
#.None
- (#e.Error <error>))))]
+ (#error.Error <error>))))]
[Frac "lux frac encode" "lux frac decode" "Could not decode Frac"]
)
@@ -314,16 +314,16 @@
(let [digit (maybe.assume (get-char repr idx))]
(case (<to-value> digit)
#.None
- (#e.Error ("lux text concat" <error> repr))
+ (#error.Error ("lux text concat" <error> repr))
(#.Some digit-value)
(recur (inc idx)
(|> output (n/* <base>) (n/+ digit-value)))))
- (#e.Success output)))
+ (#error.Success output)))
_
- (#e.Error ("lux text concat" <error> repr)))
- (#e.Error ("lux text concat" <error> repr))))))]
+ (#error.Error ("lux text concat" <error> repr)))
+ (#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: "]
@@ -331,51 +331,69 @@
[Hex@Codec<Text,Nat> |16 hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Nat: "]
)
+(def: (int/sign!! value)
+ (-> Int Text)
+ (if (i/< +0 value)
+ "-"
+ "+"))
+
+(def: (int/sign?? representation)
+ (-> Text (Maybe Int))
+ (case (get-char representation |0)
+ (^ (#.Some "-"))
+ (#.Some -1)
+
+ (^ (#.Some "+"))
+ (#.Some +1)
+
+ _
+ #.None))
+
+(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
+ output +0]
+ (if (n/< input-size idx)
+ (let [digit (maybe.assume (get-char repr idx))]
+ (case (<to-value> digit)
+ #.None
+ (#error.Error <error>)
+
+ (#.Some digit-value)
+ (recur (inc idx)
+ (|> output (i/* <base>) (i/+ (.int digit-value))))))
+ (#error.Success (i/* sign output)))))
+
(do-template [<struct> <base> <to-character> <to-value> <error>]
[(structure: #export <struct> (Codec Text Int)
(def: (encode value)
- (if (i/= 0 value)
- "0"
- (let [sign (if (i/< 0 value)
- "-"
- "")]
- (loop [input (|> value (i// <base>) (:: Number<Int> abs))
- output (|> value (i/% <base>) (:: Number<Int> abs) .nat
- <to-character>
- maybe.assume)]
- (if (i/= 0 input)
- ("lux text concat" sign output)
- (let [digit (maybe.assume (<to-character> (.nat (i/% <base> input))))]
- (recur (i// <base> input)
- ("lux text concat" digit output))))))))
+ (if (i/= +0 value)
+ "+0"
+ (loop [input (|> value (i// <base>) (:: Number<Int> abs))
+ output (|> value (i/% <base>) (:: Number<Int> abs) .nat
+ <to-character>
+ maybe.assume)]
+ (if (i/= +0 input)
+ ("lux text concat" (int/sign!! value) output)
+ (let [digit (maybe.assume (<to-character> (.nat (i/% <base> input))))]
+ (recur (i// <base> input)
+ ("lux text concat" digit output)))))))
(def: (decode repr)
(let [input-size ("lux text size" repr)]
- (if (n/>= |1 input-size)
- (let [sign (case (get-char repr |0)
- (^ (#.Some "-"))
- -1
-
- _
- 1)]
- (loop [idx (if (i/= -1 sign) |1 |0)
- output 0]
- (if (n/< input-size idx)
- (let [digit (maybe.assume (get-char repr idx))]
- (case (<to-value> digit)
- #.None
- (#e.Error <error>)
-
- (#.Some digit-value)
- (recur (inc idx)
- (|> output (i/* <base>) (i/+ (:coerce Int digit-value))))))
- (#e.Success (i/* sign output)))))
- (#e.Error <error>)))))]
-
- [Binary@Codec<Text,Int> 2 binary-character binary-value "Invalid binary syntax for Int: "]
- [Octal@Codec<Text,Int> 8 octal-character octal-value "Invalid octal syntax for Int: "]
- [_ 10 decimal-character decimal-value "Invalid syntax for Int: "]
- [Hex@Codec<Text,Int> 16 hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Int: "]
+ (if (n/> |1 input-size)
+ (case (int/sign?? repr)
+ (#.Some sign)
+ (int-decode-loop input-size repr sign <base> <to-value> <error>)
+
+ #.None
+ (#error.Error <error>))
+ (#error.Error <error>)))))]
+
+ [Binary@Codec<Text,Int> +2 binary-character binary-value "Invalid binary syntax for Int: "]
+ [Octal@Codec<Text,Int> +8 octal-character octal-value "Invalid octal syntax for Int: "]
+ [_ +10 decimal-character decimal-value "Invalid syntax for Int: "]
+ [Hex@Codec<Text,Int> +16 hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Int: "]
)
(def: (de-prefix input)
@@ -403,12 +421,12 @@
(case ("lux text char" repr |0)
(^multi (^ (#.Some (char ".")))
[(:: <nat> decode ("lux text concat" "|" (de-prefix repr)))
- (#e.Success output)])
- (#e.Success (:coerce Rev output))
+ (#error.Success output)])
+ (#error.Success (:coerce Rev output))
_
- (#e.Error ("lux text concat" <error> repr)))
- (#e.Error ("lux text concat" <error> repr))))))]
+ (#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: "]
@@ -420,17 +438,17 @@
(def: (encode value)
(let [whole (frac-to-int value)
whole-part (:: <int> encode whole)
- decimal (:: Number<Frac> abs (f/% 1.0 value))
- decimal-part (if (f/= 0.0 decimal)
+ decimal (:: Number<Frac> abs (f/% +1.0 value))
+ decimal-part (if (f/= +0.0 decimal)
".0"
(loop [dec-left decimal
output ""]
- (if (f/= 0.0 dec-left)
+ (if (f/= +0.0 dec-left)
("lux text concat" "." output)
(let [shifted (f/* <base> dec-left)
digit (|> shifted (f/% <base>) frac-to-int .nat
(get-char <char-set>) maybe.assume)]
- (recur (f/% 1.0 shifted)
+ (recur (f/% +1.0 shifted)
("lux text concat" output digit))))))]
("lux text concat" whole-part decimal-part)))
@@ -441,34 +459,34 @@
decimal-part (maybe.assume ("lux text clip" repr (inc split-index) ("lux text size" repr)))]
(case [(:: <int> decode whole-part)
(:: <int> decode decimal-part)]
- (^multi [(#e.Success whole) (#e.Success decimal)]
- (i/>= 0 decimal))
- (let [sign (if (i/< 0 whole)
+ (^multi [(#error.Success whole) (#error.Success decimal)]
+ (i/>= +0 decimal))
+ (let [sign (if (i/< +0 whole)
-1.0
- 1.0)
+ +1.0)
div-power (loop [muls-left ("lux text size" decimal-part)
- output 1.0]
+ output +1.0]
(if (n/= |0 muls-left)
output
(recur (dec muls-left)
(f/* <base> output))))
adjusted-decimal (|> decimal int-to-frac (f// div-power))
dec-rev (case (:: Hex@Codec<Text,Rev> decode ("lux text concat" "." decimal-part))
- (#e.Success dec-rev)
+ (#error.Success dec-rev)
dec-rev
- (#e.Error error)
+ (#error.Error error)
(error! error))]
- (#e.Success (f/+ (int-to-frac whole)
- (f/* sign adjusted-decimal))))
+ (#error.Success (f/+ (int-to-frac whole)
+ (f/* sign adjusted-decimal))))
_
- (#e.Error ("lux text concat" <error> repr))))
+ (#error.Error ("lux text concat" <error> repr))))
_
- (#e.Error ("lux text concat" <error> repr)))))]
+ (#error.Error ("lux text concat" <error> repr)))))]
- [Binary@Codec<Text,Frac> Binary@Codec<Text,Int> 2.0 "01" "Invalid binary syntax: "]
+ [Binary@Codec<Text,Frac> Binary@Codec<Text,Int> +2.0 "01" "Invalid binary syntax: "]
)
(def: (segment-digits chunk-size digits)
@@ -627,7 +645,7 @@
-1.0
_
- 1.0)]
+ +1.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))
@@ -637,14 +655,14 @@
("lux text concat" (<to> whole-part))
("lux text concat" (if (f/= -1.0 sign) "-" "")))]
(case (:: Binary@Codec<Text,Frac> decode as-binary)
- (#e.Error _)
- (#e.Error ("lux text concat" <error> repr))
+ (#error.Error _)
+ (#error.Error ("lux text concat" <error> repr))
output
output))
_
- (#e.Error ("lux text concat" <error> repr))))))]
+ (#error.Error ("lux text concat" <error> repr))))))]
[Octal@Codec<Text,Frac> "Invalid octaladecimal syntax: " binary-to-octal octal-to-binary]
[Hex@Codec<Text,Frac> "Invalid hexadecimal syntax: " binary-to-hex hex-to-binary]
@@ -661,12 +679,12 @@
description [cursor (#.Text ($_ "lux text concat"
encoding "\n"
underscore))]]
- (#e.Success [state (list (` (doc (~ description)
- (~ example-1)
- (~ example-2))))]))
+ (#error.Success [state (list (` (doc (~ description)
+ (~ example-1)
+ (~ example-2))))]))
_
- (#e.Error "Wrong syntax for \"encoding-doc\".")))
+ (#error.Error "Wrong syntax for \"encoding-doc\".")))
(def: (underscore-prefixed? number)
(-> Text Bit)
@@ -687,36 +705,36 @@
(case tokens
(#.Cons [meta (#.Text repr')] #.Nil)
(if (underscore-prefixed? repr')
- (#e.Error <error>)
+ (#error.Error <error>)
(let [repr (clean-underscores repr')]
(case (:: <nat> decode repr)
- (#e.Success value)
- (#e.Success [state (list [meta (#.Nat value)])])
+ (#error.Success value)
+ (#error.Success [state (list [meta (#.Nat value)])])
- (^multi (#e.Error _)
- [(:: <int> decode repr) (#e.Success value)])
- (#e.Success [state (list [meta (#.Int value)])])
+ (^multi (#error.Error _)
+ [(:: <int> decode repr) (#error.Success value)])
+ (#error.Success [state (list [meta (#.Int value)])])
- (^multi (#e.Error _)
- [(:: <rev> decode repr) (#e.Success value)])
- (#e.Success [state (list [meta (#.Rev value)])])
+ (^multi (#error.Error _)
+ [(:: <rev> decode repr) (#error.Success value)])
+ (#error.Success [state (list [meta (#.Rev value)])])
- (^multi (#e.Error _)
- [(:: <frac> decode repr) (#e.Success value)])
- (#e.Success [state (list [meta (#.Frac value)])])
+ (^multi (#error.Error _)
+ [(:: <frac> decode repr) (#error.Success value)])
+ (#error.Success [state (list [meta (#.Frac value)])])
_
- (#e.Error <error>))))
+ (#error.Error <error>))))
_
- (#e.Error <error>)))]
+ (#error.Error <error>)))]
[bin Binary@Codec<Text,Nat> Binary@Codec<Text,Int> Binary@Codec<Text,Rev> Binary@Codec<Text,Frac>
"Invalid binary syntax."
- (encoding-doc "binary" (bin "11001001") (bin "11_00_10_01"))]
+ (encoding-doc "binary" (bin "+11001001") (bin "+11_00_10_01"))]
[oct Octal@Codec<Text,Nat> Octal@Codec<Text,Int> Octal@Codec<Text,Rev> Octal@Codec<Text,Frac>
"Invalid octal syntax."
- (encoding-doc "octal" (oct "615243") (oct "615_243"))]
+ (encoding-doc "octal" (oct "+615243") (oct "+615_243"))]
[hex Hex@Codec<Text,Nat> Hex@Codec<Text,Int> Hex@Codec<Text,Rev> Hex@Codec<Text,Frac>
"Invalid hexadecimal syntax."
(encoding-doc "hexadecimal" (hex "deadBEEF") (hex "dead_BEEF"))]
@@ -755,7 +773,7 @@
(loop [idx idx
carry |0
output output]
- (if (i/>= 0 (:coerce Int idx))
+ (if (i/>= +0 (:coerce Int idx))
(let [raw (|> (digits-get idx output)
(n/* |5)
(n/+ carry))]
@@ -769,7 +787,7 @@
(loop [times power
output (|> (make-digits [])
(digits-put power |1))]
- (if (i/>= 0 (:coerce Int times))
+ (if (i/>= +0 (:coerce Int times))
(recur (dec times)
(digits-times-5! power output))
output)))
@@ -779,7 +797,7 @@
(loop [idx (dec i64.width)
all-zeroes? #1
output ""]
- (if (i/>= 0 (:coerce Int idx))
+ (if (i/>= +0 (:coerce Int idx))
(let [digit (digits-get idx digits)]
(if (and (n/= |0 digit)
all-zeroes?)
@@ -798,7 +816,7 @@
(loop [idx (dec i64.width)
carry |0
output (make-digits [])]
- (if (i/>= 0 (:coerce Int idx))
+ (if (i/>= +0 (:coerce Int idx))
(let [raw ($_ n/+
carry
(digits-get idx param)
@@ -816,7 +834,7 @@
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
@@ -852,7 +870,7 @@
(-> Digits Digits Digits)
(loop [idx (dec i64.width)
output subject]
- (if (i/>= 0 (.int idx))
+ (if (i/>= +0 (.int idx))
(recur (dec idx)
(digits-sub-once! idx (digits-get idx param) output))
output)))
@@ -865,7 +883,7 @@
".0"
(loop [idx last-idx
digits (make-digits [])]
- (if (i/>= 0 (:coerce Int idx))
+ (if (i/>= +0 (:coerce Int idx))
(if (i64.set? idx input)
(let [digits' (digits-add (digits-power (n/- idx last-idx))
digits)]
@@ -901,16 +919,16 @@
(recur (digits-sub! power digits)
(inc idx)
(i64.set (n/- idx (dec i64.width)) output))))
- (#e.Success (:coerce Rev output))))
+ (#error.Success (:coerce Rev output))))
#.None
- (#e.Error ("lux text concat" "Wrong syntax for Rev: " input)))
- (#e.Error ("lux text concat" "Wrong syntax for Rev: " input))))
+ (#error.Error ("lux text concat" "Wrong syntax for Rev: " input)))
+ (#error.Error ("lux text concat" "Wrong syntax for Rev: " input))))
))
(def: (log2 input)
(-> Frac Frac)
- (f// ("lux math log" 2.0)
+ (f// ("lux math log" +2.0)
("lux math log" input)))
(def: double-bias Nat |1023)
@@ -929,8 +947,8 @@
(f/= negative-infinity input)
(hex "|FFF0000000000000")
- (f/= 0.0 input)
- (let [reciprocal (f// input 1.0)]
+ (f/= +0.0 input)
+ (let [reciprocal (f// input +1.0)]
(if (f/= positive-infinity reciprocal)
## Positive zero
(hex "|0000000000000000")
@@ -944,9 +962,9 @@
exponent-mask (|> |1 (i64.left-shift exponent-size) dec)
mantissa (|> input
## Normalize
- (f// ("lux math pow" 2.0 exponent))
+ (f// ("lux math pow" +2.0 exponent))
## Make it int-equivalent
- (f/* ("lux math pow" 2.0 52.0)))
+ (f/* ("lux math pow" +2.0 +52.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)]
@@ -981,16 +999,16 @@
(and (n/= |0 E) (n/= |0 M))
(if (n/= |0 S)
- 0.0
- (f/* -1.0 0.0))
+ +0.0
+ (f/* -1.0 +0.0))
## else
(let [normalized (|> M (i64.set mantissa-size)
.int int-to-frac
- (f// ("lux math pow" 2.0 52.0)))
+ (f// ("lux math pow" +2.0 +52.0)))
power (|> E (n/- double-bias)
.int int-to-frac
- ("lux math pow" 2.0))
+ ("lux math pow" +2.0))
shifted (f/* power
normalized)]
(if (n/= |0 S)
diff --git a/stdlib/source/lux/data/number/complex.lux b/stdlib/source/lux/data/number/complex.lux
index 41e074be6..fb0401582 100644
--- a/stdlib/source/lux/data/number/complex.lux
+++ b/stdlib/source/lux/data/number/complex.lux
@@ -27,14 +27,14 @@
"The imaginary part can be omitted if it's 0."
(complex real))}
(wrap (list (` {#..real (~ real)
- #..imaginary (~ (maybe.default (' 0.0)
+ #..imaginary (~ (maybe.default (' +0.0)
?imaginary))}))))
-(def: #export i Complex (complex 0.0 1.0))
+(def: #export i Complex (complex +0.0 +1.0))
-(def: #export one Complex (complex 1.0 0.0))
+(def: #export one Complex (complex +1.0 +0.0))
-(def: #export zero Complex (complex 0.0 0.0))
+(def: #export zero Complex (complex +0.0 +0.0))
(def: #export (not-a-number? complex)
(or (number.not-a-number? (get@ #real complex))
@@ -158,8 +158,8 @@
(def: #export (tan subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject
- r2 (f/* 2.0 real)
- i2 (f/* 2.0 imaginary)
+ 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))}))
@@ -167,8 +167,8 @@
(def: #export (tanh subject)
(-> Complex Complex)
(let [(^slots [#real #imaginary]) subject
- r2 (f/* 2.0 real)
- i2 (f/* 2.0 imaginary)
+ 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))}))
@@ -178,15 +178,15 @@
(let [(^slots [#real #imaginary]) subject]
(complex (if (f/< (frac/abs imaginary)
(frac/abs real))
- (if (f/= 0.0 imaginary)
+ (if (f/= +0.0 imaginary)
(frac/abs real)
(let [q (f// imaginary real)]
- (f/* (math.pow 0.5 (f/+ 1.0 (f/* q q)))
+ (f/* (math.pow +0.5 (f/+ +1.0 (f/* q q)))
(frac/abs imaginary))))
- (if (f/= 0.0 real)
+ (if (f/= +0.0 real)
(frac/abs imaginary)
(let [q (f// real imaginary)]
- (f/* (math.pow 0.5 (f/+ 1.0 (f/* q q)))
+ (f/* (math.pow +0.5 (f/+ +1.0 (f/* q q)))
(frac/abs real))))
))))
@@ -234,18 +234,18 @@
(def: #export (root2 (^@ input (^slots [#real #imaginary])))
(-> Complex Complex)
- (let [t (|> input ..abs (get@ #real) (f/+ (frac/abs real)) (f// 2.0) (math.pow 0.5))]
- (if (f/>= 0.0 real)
+ (let [t (|> input ..abs (get@ #real) (f/+ (frac/abs real)) (f// +2.0) (math.pow +0.5))]
+ (if (f/>= +0.0 real)
{#real t
- #imaginary (f// (f/* 2.0 t)
+ #imaginary (f// (f/* +2.0 t)
imaginary)}
- {#real (f// (f/* 2.0 t)
+ {#real (f// (f/* +2.0 t)
(frac/abs imaginary))
- #imaginary (f/* t (copy-sign imaginary 1.0))})))
+ #imaginary (f/* t (copy-sign imaginary +1.0))})))
(def: #export (root2-1z input)
(-> Complex Complex)
- (|> (complex 1.0) (- (* input input)) root2))
+ (|> (complex +1.0) (- (* input input)) root2))
(def: #export (reciprocal (^slots [#real #imaginary]))
(-> Complex Complex)
@@ -253,12 +253,12 @@
(frac/abs real))
(let [q (f// imaginary real)
scale (f// (|> real (f/* q) (f/+ imaginary))
- 1.0)]
+ +1.0)]
{#real (f/* q scale)
#imaginary (frac/negate scale)})
(let [q (f// real imaginary)
scale (f// (|> imaginary (f/* q) (f/+ real))
- 1.0)]
+ +1.0)]
{#real scale
#imaginary (|> scale frac/negate (f/* q))})))
@@ -283,7 +283,7 @@
(+ i)
(/ (- input i))
log
- (* (/ (complex 2.0) i))))
+ (* (/ (complex +2.0) i))))
(def: #export (argument (^slots [#real #imaginary]))
(-> Complex Frac)
@@ -294,9 +294,9 @@
(if (n/= |0 nth)
(list)
(let [r-nth (|> nth .int int-to-frac)
- nth-root-of-abs (|> input abs (get@ #real) (math.pow (f// r-nth 1.0)))
+ nth-root-of-abs (|> input 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))]
+ slice (|> math.pi (f/* +2.0) (f// r-nth))]
(|> (list.n/range |0 (dec nth))
(list/map (function (_ nth')
(let [inner (|> nth' .int int-to-frac
diff --git a/stdlib/source/lux/data/text/regex.lux b/stdlib/source/lux/data/text/regex.lux
index 3cb65dd14..658d51ae2 100644
--- a/stdlib/source/lux/data/text/regex.lux
+++ b/stdlib/source/lux/data/text/regex.lux
@@ -183,8 +183,7 @@
(def: number^
(l.Lexer Nat)
(|> (l.many l.decimal)
- (p.codec number.Codec<Text,Int>)
- (parser/map .nat)))
+ (p.codec number.Codec<Text,Nat>)))
(def: re-back-reference^
(l.Lexer Code)
@@ -298,7 +297,7 @@
(' #let) (` [(~ g!total) (:: (~! text.Monoid<Text>) (~' compose) (~ g!total) (~ access))]))
steps)])
)))
- [0
+ [+0
(: (List Code) (list))
(: (List (List Code)) (list))]
parts)]]