aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/data')
-rw-r--r--stdlib/source/lux/data/number.lux2
-rw-r--r--stdlib/source/lux/data/number/frac.lux28
-rw-r--r--stdlib/source/lux/data/number/i64.lux31
-rw-r--r--stdlib/source/lux/data/number/int.lux4
-rw-r--r--stdlib/source/lux/data/number/nat.lux2
-rw-r--r--stdlib/source/lux/data/number/rev.lux8
-rw-r--r--stdlib/source/lux/data/text.lux48
7 files changed, 57 insertions, 66 deletions
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index b4408518e..e6b169fc4 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -29,7 +29,7 @@
(def: (comma-prefixed? number)
(-> Text Bit)
- (case ("lux text index" number "," 0)
+ (case ("lux text index" 0 "," number)
(#.Some 0)
#1
diff --git a/stdlib/source/lux/data/number/frac.lux b/stdlib/source/lux/data/number/frac.lux
index 924831dcf..f49f73039 100644
--- a/stdlib/source/lux/data/number/frac.lux
+++ b/stdlib/source/lux/data/number/frac.lux
@@ -107,14 +107,14 @@
(let [shifted (f/* <base> dec-left)
digit-idx (|> shifted (f/% <base>) frac-to-int .nat)]
(recur (f/% +1.0 shifted)
- ("lux text concat" output ("lux text clip" <char-set> digit-idx (inc digit-idx))))))))]
+ ("lux text concat" output ("lux text clip" digit-idx (inc digit-idx) <char-set>)))))))]
("lux text concat" whole-part decimal-part)))
(def: (decode repr)
- (case ("lux text index" repr "." 0)
+ (case ("lux text index" 0 "." repr)
(#.Some split-index)
- (let [whole-part ("lux text clip" repr 0 split-index)
- decimal-part ("lux text clip" repr (inc split-index) ("lux text size" repr))]
+ (let [whole-part ("lux text clip" 0 split-index repr)
+ decimal-part ("lux text clip" (inc split-index) ("lux text size" repr) repr)]
(case [(:: <int> decode whole-part)
(:: <int> decode ("lux text concat" "+" decimal-part))]
(^multi [(#error.Success whole) (#error.Success decimal)]
@@ -158,8 +158,8 @@
(if (n/<= chunk-size num-digits)
(list digits)
(let [boundary (n/- chunk-size num-digits)
- chunk ("lux text clip" digits boundary num-digits)
- remaining ("lux text clip" digits 0 boundary)]
+ chunk ("lux text clip" boundary num-digits digits)
+ remaining ("lux text clip" 0 boundary digits)]
(list& chunk (segment-digits chunk-size remaining)))))))
(def: (bin-segment-to-hex input)
@@ -286,11 +286,9 @@
(def: (encode value)
(let [sign (:: ..number signum value)
raw-bin (:: ..binary encode value)
- dot-idx (maybe.assume ("lux text index" raw-bin "." 0))
- whole-part ("lux text clip" raw-bin
- (if (f/= -1.0 sign) 1 0)
- dot-idx)
- decimal-part ("lux text clip" raw-bin (inc dot-idx) ("lux text size" raw-bin))
+ dot-idx (maybe.assume ("lux text index" 0 "." raw-bin))
+ whole-part ("lux text clip" (if (f/= -1.0 sign) 1 0) dot-idx raw-bin)
+ decimal-part ("lux text clip" (inc dot-idx) ("lux text size" raw-bin) raw-bin)
hex-output (|> (<from> #0 decimal-part)
("lux text concat" ".")
("lux text concat" (<from> #1 whole-part))
@@ -298,16 +296,16 @@
hex-output))
(def: (decode repr)
- (let [sign (case ("lux text index" repr "-" 0)
+ (let [sign (case ("lux text index" 0 "-" repr)
(#.Some 0)
-1.0
_
+1.0)]
- (case ("lux text index" repr "." 0)
+ (case ("lux text index" 0 "." repr)
(#.Some split-index)
- (let [whole-part ("lux text clip" repr 1 split-index)
- decimal-part ("lux text clip" repr (inc split-index) ("lux text size" repr))
+ (let [whole-part ("lux text clip" 1 split-index repr)
+ decimal-part ("lux text clip" (inc split-index) ("lux text size" repr) repr)
as-binary (|> (<to> decimal-part)
("lux text concat" ".")
("lux text concat" (<to> whole-part))
diff --git a/stdlib/source/lux/data/number/i64.lux b/stdlib/source/lux/data/number/i64.lux
index 321c628e9..ffce20b4c 100644
--- a/stdlib/source/lux/data/number/i64.lux
+++ b/stdlib/source/lux/data/number/i64.lux
@@ -12,15 +12,19 @@
(n/* bits-per-byte
bytes-per-i64))
-(template [<name> <op> <doc>]
- [(def: #export (<name> param subject)
+(template [<parameter-type> <name> <op> <doc>]
+ [(def: #export (<name> parameter subject)
{#.doc <doc>}
- (All [s] (-> (I64 Any) (I64 s) (I64 s)))
- (<op> param subject))]
-
- [and "lux i64 and" "Bitwise and."]
- [or "lux i64 or" "Bitwise or."]
- [xor "lux i64 xor" "Bitwise xor."]
+ (All [s] (-> <parameter-type> (I64 s) (I64 s)))
+ (<op> parameter subject))]
+
+ [(I64 Any) and "lux i64 and" "Bitwise and."]
+ [(I64 Any) or "lux i64 or" "Bitwise or."]
+ [(I64 Any) xor "lux i64 xor" "Bitwise xor."]
+
+ [Nat left-shift "lux i64 left-shift" "Bitwise left-shift."]
+ [Nat logic-right-shift "lux i64 logical-right-shift" "Unsigned bitwise logic-right-shift."]
+ [Nat arithmetic-right-shift "lux i64 arithmetic-right-shift" "Signed bitwise arithmetic-right-shift."]
)
(def: #export not
@@ -42,17 +46,6 @@
(def: compose ..and)
)
-(template [<name> <op> <doc>]
- [(def: #export (<name> param subject)
- {#.doc <doc>}
- (All [s] (-> Nat (I64 s) (I64 s)))
- (<op> param subject))]
-
- [left-shift "lux i64 left-shift" "Bitwise left-shift."]
- [logic-right-shift "lux i64 logical-right-shift" "Unsigned bitwise logic-right-shift."]
- [arithmetic-right-shift "lux i64 arithmetic-right-shift" "Signed bitwise arithmetic-right-shift."]
- )
-
(def: #export (mask bits)
(-> Nat (I64 Any))
(|> 1 (..left-shift (n/% ..width bits)) .dec))
diff --git a/stdlib/source/lux/data/number/int.lux b/stdlib/source/lux/data/number/int.lux
index 9a2ce2b9b..f94049296 100644
--- a/stdlib/source/lux/data/number/int.lux
+++ b/stdlib/source/lux/data/number/int.lux
@@ -73,7 +73,7 @@
(def: (int;sign?? representation)
(-> Text (Maybe Int))
- (case ("lux text char" representation 0)
+ (case ("lux text char" 0 representation)
(^ (char "-"))
(#.Some -1)
@@ -88,7 +88,7 @@
(loop [idx 1
output +0]
(if (n/< input-size idx)
- (case (<to-value> ("lux text char" repr idx))
+ (case (<to-value> ("lux text char" idx repr))
#.None
(#error.Failure <error>)
diff --git a/stdlib/source/lux/data/number/nat.lux b/stdlib/source/lux/data/number/nat.lux
index fb47d2460..c1f0ca420 100644
--- a/stdlib/source/lux/data/number/nat.lux
+++ b/stdlib/source/lux/data/number/nat.lux
@@ -191,7 +191,7 @@
(loop [idx 0
output 0]
(if (n/< input-size idx)
- (case (<to-value> ("lux text char" repr idx))
+ (case (<to-value> ("lux text char" idx repr))
#.None
(#error.Failure ("lux text concat" <error> repr))
diff --git a/stdlib/source/lux/data/number/rev.lux b/stdlib/source/lux/data/number/rev.lux
index fa79f597d..bbb34c570 100644
--- a/stdlib/source/lux/data/number/rev.lux
+++ b/stdlib/source/lux/data/number/rev.lux
@@ -52,7 +52,7 @@
(def: (de-prefix input)
(-> Text Text)
- ("lux text clip" input 1 ("lux text size" input)))
+ ("lux text clip" 1 ("lux text size" input) input))
(template [<struct> <codec> <char-bit-size> <error>]
[(with-expansions [<error-output> (as-is (#error.Failure ("lux text concat" <error> repr)))]
@@ -77,7 +77,7 @@
(def: (decode repr)
(let [repr-size ("lux text size" repr)]
(if (n/> 1 repr-size)
- (case ("lux text char" repr 0)
+ (case ("lux text char" 0 repr)
(^ (char "."))
(case (:: <codec> decode (de-prefix repr))
(#error.Success output)
@@ -188,7 +188,7 @@
(loop [idx 0
output (make-digits [])]
(if (n/< length idx)
- (case ("lux text index" "0123456789" ("lux text clip" input idx (inc idx)) 0)
+ (case ("lux text index" 0 ("lux text clip" idx (inc idx) input) "0123456789")
#.None
#.None
@@ -251,7 +251,7 @@
)))))
(def: (decode input)
- (let [dotted? (case ("lux text index" input "." 0)
+ (let [dotted? (case ("lux text index" 0 "." input)
(#.Some 0)
#1
diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux
index 110afd81d..384d4e860 100644
--- a/stdlib/source/lux/data/text.lux
+++ b/stdlib/source/lux/data/text.lux
@@ -12,7 +12,7 @@
[number
["." i64]]
[collection
- ["." list ("#;." fold)]]]
+ ["." list ("#@." fold)]]]
[tool
[compiler
["." host]]]])
@@ -46,20 +46,20 @@
(def: #export (nth idx input)
(-> Nat Text (Maybe Char))
(if (n/< ("lux text size" input) idx)
- (#.Some ("lux text char" input idx))
+ (#.Some ("lux text char" idx input))
#.None))
(def: #export (index-of' pattern from input)
(-> Text Nat Text (Maybe Nat))
- ("lux text index" input pattern from))
+ ("lux text index" from pattern input))
(def: #export (index-of pattern input)
(-> Text Text (Maybe Nat))
- ("lux text index" input pattern 0))
+ ("lux text index" 0 pattern input))
(def: (last-index-of'' part since text)
(-> Text Nat Text (Maybe Nat))
- (case ("lux text index" text part (inc since))
+ (case ("lux text index" (inc since) part text)
#.None
(#.Some since)
@@ -68,7 +68,7 @@
(def: #export (last-index-of' part from text)
(-> Text Nat Text (Maybe Nat))
- (case ("lux text index" text part from)
+ (case ("lux text index" from part text)
(#.Some since)
(last-index-of'' part since text)
@@ -77,7 +77,7 @@
(def: #export (last-index-of part text)
(-> Text Text (Maybe Nat))
- (case ("lux text index" text part 0)
+ (case ("lux text index" 0 part text)
(#.Some since)
(last-index-of'' part since text)
@@ -105,7 +105,7 @@
(def: #export (contains? sub text)
(-> Text Text Bit)
- (case ("lux text index" text sub 0)
+ (case ("lux text index" 0 sub text)
(#.Some _)
#1
@@ -116,14 +116,14 @@
(-> Nat Nat Text (Maybe Text))
(if (and (n/<= to from)
(n/<= ("lux text size" input) to))
- (#.Some ("lux text clip" input from to))
+ (#.Some ("lux text clip" from to input))
#.None))
(def: #export (clip' from input)
(-> Nat Text (Maybe Text))
(let [size ("lux text size" input)]
(if (n/<= size from)
- (#.Some ("lux text clip" input from size))
+ (#.Some ("lux text clip" from size input))
#.None)))
(def: #export (split at x)
@@ -169,25 +169,25 @@
template))
(structure: #export equivalence (Equivalence Text)
- (def: (= test subject)
- ("lux text =" subject test)))
+ (def: (= reference sample)
+ ("lux text =" reference sample)))
(structure: #export order (Order Text)
(def: &equivalence ..equivalence)
- (def: (< test subject)
- ("lux text <" subject test))
+ (def: (< reference sample)
+ ("lux text <" reference sample))
- (def: (<= test subject)
- (or ("lux text <" subject test)
- ("lux text =" subject test)))
+ (def: (<= reference sample)
+ (or ("lux text <" reference sample)
+ ("lux text =" reference sample)))
- (def: (> test subject)
- ("lux text <" test subject))
+ (def: (> reference sample)
+ ("lux text <" sample reference))
- (def: (>= test subject)
- (or ("lux text <" test subject)
- ("lux text =" test subject)))
+ (def: (>= reference sample)
+ (or ("lux text <" sample reference)
+ ("lux text =" reference sample)))
)
(structure: #export monoid (Monoid Text)
@@ -215,13 +215,13 @@
(|> hash
(i64.left-shift 5)
(n/- hash)
- (n/+ ("lux text char" input idx))))
+ (n/+ ("lux text char" idx input))))
hash)))))))
(def: #export concat
(-> (List Text) Text)
(let [(^open ".") ..monoid]
- (|>> list.reverse (list;fold compose identity))))
+ (|>> list.reverse (list@fold compose identity))))
(def: #export (join-with sep texts)
(-> Text (List Text) Text)