aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source
diff options
context:
space:
mode:
authorEduardo Julian2017-02-22 18:01:05 -0400
committerEduardo Julian2017-02-22 18:01:05 -0400
commit38a81332a1cefb51ff89ee96a16bb4a65cee21bc (patch)
tree77db433c79db101a455e406415e1f801417de98a /stdlib/source
parent03a41265b2619257be45fddac691cb5bc18765a7 (diff)
- Implemented a variety of new procedures for text, chars, math and arrays.
Diffstat (limited to 'stdlib/source')
-rw-r--r--stdlib/source/lux.lux18
-rw-r--r--stdlib/source/lux/data/char.lux50
-rw-r--r--stdlib/source/lux/data/number.lux3
-rw-r--r--stdlib/source/lux/data/text.lux84
-rw-r--r--stdlib/source/lux/math.lux62
5 files changed, 102 insertions, 115 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index c6018398b..01064b829 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -2100,6 +2100,7 @@
(-> Char Text)
(let' [as-text (_lux_case x
#"\t" "\\t"
+ #"\v" "\\v"
#"\b" "\\b"
#"\n" "\\n"
#"\r" "\\r"
@@ -3222,13 +3223,14 @@
(#Some y)
(#Some y))))
-(def: (last-index-of part text)
- (-> Text Text (Maybe Nat))
- (_lux_proc ["text" "last-index"] [text part]))
+(do-template [<name> <proc> <start>]
+ [(def: (<name> part text)
+ (-> Text Text (Maybe Nat))
+ (_lux_proc ["text" <proc>] [text part <start>]))]
-(def: (index-of part text)
- (-> Text Text (Maybe Nat))
- (_lux_proc ["text" "index"] [text part]))
+ [index-of "index" +0]
+ [last-index-of "last-index" (_lux_proc ["text" "size"] [text])]
+ )
(def: (clip1 from text)
(-> Nat Text (Maybe Text))
@@ -3954,7 +3956,8 @@
[_ (#SymbolS "" m-name)]
(do Monad<Lux>
[m-name (clean-module m-name)]
- (wrap (list [m-name #None {#refer-defs #All #refer-open (list)}])))
+ (wrap (list [m-name #None {#refer-defs #All
+ #refer-open (list)}])))
(^ [_ (#FormS (list& [_ (#SymbolS "" m-name)] extra))])
(do Monad<Lux>
@@ -4863,6 +4866,7 @@
(-> Text Text)
(let [escaped (|> original
(replace "\t" "\\t")
+ (replace "\v" "\\v")
(replace "\b" "\\b")
(replace "\n" "\\n")
(replace "\r" "\\r")
diff --git a/stdlib/source/lux/data/char.lux b/stdlib/source/lux/data/char.lux
index 28877ae34..0db90898e 100644
--- a/stdlib/source/lux/data/char.lux
+++ b/stdlib/source/lux/data/char.lux
@@ -9,48 +9,43 @@
## [Structures]
(struct: #export _ (Eq Char)
(def: (= x y)
- (_lux_proc ["jvm" "ceq"] [x y])))
+ (_lux_proc ["char" "="] [x y])))
(struct: #export _ (Hash Char)
(def: eq Eq<Char>)
- (def: hash
- (|>. []
- (_lux_proc ["jvm" "c2i"])
- []
- (_lux_proc ["jvm" "i2l"])
- int-to-nat)))
+ (def: (hash input)
+ (_lux_proc ["char" "to-nat"] [input])))
(struct: #export _ (ord;Ord Char)
(def: eq Eq<Char>)
- (do-template [<name> <op>]
- [(def: (<name> test subject)
- (_lux_proc ["jvm" <op>] [subject test]))]
+ (def: (< test subject)
+ (_lux_proc ["char" "<"] [subject test]))
- [< "clt"]
- [> "cgt"]
- )
+ (def: (<= test subject)
+ (or (_lux_proc ["char" "="] [subject test])
+ (_lux_proc ["char" "<"] [subject test])))
- (do-template [<name> <op>]
- [(def: (<name> test subject)
- (or (_lux_proc ["jvm" "ceq"] [subject test])
- (_lux_proc ["jvm" <op>] [subject test])))]
+ (def: (> test subject)
+ (_lux_proc ["char" "<"] [test subject]))
- [<= "clt"]
- [>= "cgt"]
- ))
+ (def: (>= test subject)
+ (or (_lux_proc ["char" "="] [test subject])
+ (_lux_proc ["char" "<"] [test subject])))
+ )
(struct: #export _ (Codec Text Char)
(def: (encode x)
(let [as-text (case x
#"\t" "\\t"
+ #"\v" "\\v"
#"\b" "\\b"
#"\n" "\\n"
#"\r" "\\r"
#"\f" "\\f"
#"\"" "\\\""
#"\\" "\\\\"
- _ (_lux_proc ["jvm" "invokevirtual:java.lang.Object:toString:"] [x]))]
+ _ (_lux_proc ["char" "to-text"] [x]))]
($_ Text/append "#\"" as-text "\"")))
(def: (decode y)
@@ -70,13 +65,13 @@
[(#;Some #"\\") (#;Some char)]
(case char
#"t" (#;Right #"\t")
+ #"v" (#;Right #"\v")
#"b" (#;Right #"\b")
#"n" (#;Right #"\n")
#"r" (#;Right #"\r")
#"f" (#;Right #"\f")
#"\"" (#;Right #"\"")
#"\\" (#;Right #"\\")
- #"t" (#;Right #"\t")
_ (#;Left (Text/append "Wrong syntax for Char: " y)))
_
@@ -84,14 +79,19 @@
(#;Left (Text/append "Wrong syntax for Char: " y))))))
## [Values]
-(def: #export (space? x)
+(def: #export (space? char)
{#;doc "Checks whether the character is white-space."}
(-> Char Bool)
- (_lux_proc ["jvm" "invokestatic:java.lang.Character:isWhitespace:char"] [x]))
+ (case char
+ (^or #"\t" #"\v" #" " #"\n" #"\r" #"\f")
+ true
+
+ _
+ false))
(def: #export (as-text x)
(-> Char Text)
- (_lux_proc ["jvm" "invokevirtual:java.lang.Object:toString:"] [x]))
+ (_lux_proc ["char" "to-text"] [x]))
(def: #export (char x)
(-> Nat Char)
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index 0c52653af..1a29fc5b6 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -202,7 +202,8 @@
(let [digit (assume (_lux_proc ["text" "char"] [input idx]))]
(case (_lux_proc ["text" "index"]
[<char-set>
- (_lux_proc ["char" "to-text"] [digit])])
+ (_lux_proc ["char" "to-text"] [digit])
+ +0])
#;None
(#;Left <error>)
diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux
index bc350cc3a..4869d9e82 100644
--- a/stdlib/source/lux/data/text.lux
+++ b/stdlib/source/lux/data/text.lux
@@ -20,7 +20,7 @@
(def: #export (contains? sub text)
(-> Text Text Bool)
- (_lux_proc ["jvm" "invokevirtual:java.lang.String:contains:java.lang.CharSequence"] [text sub]))
+ (_lux_proc ["text" "contains?"] [text sub]))
(do-template [<name> <proc>]
[(def: #export (<name> input)
@@ -33,13 +33,7 @@
(def: #export (clip from to input)
(-> Nat Nat Text (Maybe Text))
- (if (and (n.< to from)
- (n.<= (size input) to))
- (#;Some (_lux_proc ["jvm" "invokevirtual:java.lang.String:substring:int,int"]
- [input
- (_lux_proc ["jvm" "l2i"] [(nat-to-int from)])
- (_lux_proc ["jvm" "l2i"] [(nat-to-int to)])]))
- #;None))
+ (_lux_proc ["text" "clip"] [input from to]))
(def: #export (clip' from input)
(-> Nat Text (Maybe Text))
@@ -47,30 +41,24 @@
(def: #export (replace pattern value template)
(-> Text Text Text Text)
- (_lux_proc ["jvm" "invokevirtual:java.lang.String:replace:java.lang.CharSequence,java.lang.CharSequence"] [template pattern value]))
+ (_lux_proc ["text" "replace-all"] [template pattern value]))
-(do-template [<common> <common-proc> <general> <general-proc>]
- [(def: #export (<common> pattern x)
+(do-template [<general> <common> <proc> <start>]
+ [(def: #export (<common> pattern input)
(-> Text Text (Maybe Nat))
- (case (_lux_proc ["jvm" "i2l"] [(_lux_proc ["jvm" <common-proc>] [x pattern])])
- -1 #;None
- idx (#;Some (int-to-nat idx))))
+ (_lux_proc ["text" <proc>] [input pattern <start>]))
- (def: #export (<general> pattern from x)
+ (def: #export (<general> pattern from input)
(-> Text Nat Text (Maybe Nat))
- (if (n.< (size x) from)
- (case (_lux_proc ["jvm" "i2l"] [(_lux_proc ["jvm" <general-proc>] [x pattern (_lux_proc ["jvm" "l2i"] [(nat-to-int from)])])])
- -1 #;None
- idx (#;Some (int-to-nat idx)))
- #;None))]
-
- [index-of "invokevirtual:java.lang.String:indexOf:java.lang.String" index-of' "invokevirtual:java.lang.String:indexOf:java.lang.String,int"]
- [last-index-of "invokevirtual:java.lang.String:lastIndexOf:java.lang.String" last-index-of' "invokevirtual:java.lang.String:lastIndexOf:java.lang.String,int"]
+ (_lux_proc ["text" <proc>] [input pattern from]))]
+
+ [index-of index-of' "index" +0]
+ [last-index-of last-index-of' "last-index" (size input)]
)
(def: #export (starts-with? prefix x)
(-> Text Text Bool)
- (case (index-of prefix x)
+ (case (index-of' prefix x)
(#;Some +0)
true
@@ -79,7 +67,7 @@
(def: #export (ends-with? postfix x)
(-> Text Text Bool)
- (case (last-index-of postfix x)
+ (case (last-index-of' postfix x)
(#;Some n)
(n.= (size x)
(n.+ (size postfix) n))
@@ -89,16 +77,17 @@
(def: #export (split at x)
(-> Nat Text (Maybe [Text Text]))
- (if (n.<= (size x) at)
- (let [pre (_lux_proc ["jvm" "invokevirtual:java.lang.String:substring:int,int"] [x (_lux_proc ["jvm" "l2i"] [0]) (_lux_proc ["jvm" "l2i"] [(nat-to-int at)])])
- post (_lux_proc ["jvm" "invokevirtual:java.lang.String:substring:int"] [x (_lux_proc ["jvm" "l2i"] [(nat-to-int at)])])]
- (#;Some [pre post]))
+ (case [(clip +0 at x) (clip' at x)]
+ [(#;Some pre) (#;Some post)]
+ (#;Some [pre post])
+
+ _
#;None))
(def: #export (split-with token sample)
(-> Text Text (Maybe [Text Text]))
(do Monad<Maybe>
- [index (index-of token sample)
+ [index (index-of' token sample)
[pre post'] (split index sample)
[_ post] (split (size token) post')]
(wrap [pre post])))
@@ -123,20 +112,25 @@
(struct: #export _ (ord;Ord Text)
(def: eq Eq<Text>)
- (do-template [<name> <op>]
- [(def: (<name> test subject)
- (<op> 0
- (_lux_proc ["jvm" "i2l"] [(_lux_proc ["jvm" "invokevirtual:java.lang.String:compareTo:java.lang.String"] [subject test])])))]
+ (def: (< test subject)
+ (_lux_proc ["text" "<"] [subject test]))
+
+ (def: (<= test subject)
+ (or (_lux_proc ["text" "<"] [subject test])
+ (_lux_proc ["text" "="] [subject test])))
- [< i.<]
- [<= i.<=]
- [> i.>]
- [>= i.>=]))
+ (def: (> test subject)
+ (_lux_proc ["text" "<"] [test subject]))
+
+ (def: (>= test subject)
+ (or (_lux_proc ["text" "<"] [test subject])
+ (_lux_proc ["text" "="] [test subject])))
+ )
(struct: #export _ (Monoid Text)
(def: unit "")
- (def: (append x y)
- (_lux_proc ["jvm" "invokevirtual:java.lang.String:concat:java.lang.String"] [x y])))
+ (def: (append left right)
+ (_lux_proc ["text" "append"] [left right])))
(open Monoid<Text>)
@@ -145,6 +139,7 @@
(let [escaped (|> original
(replace "\\" "\\\\")
(replace "\t" "\\t")
+ (replace "\v" "\\v")
(replace "\b" "\\b")
(replace "\n" "\\n")
(replace "\r" "\\r")
@@ -161,6 +156,7 @@
(|> input'
(replace "\\\\" "\\")
(replace "\\t" "\t")
+ (replace "\\v" "\v")
(replace "\\b" "\b")
(replace "\\n" "\n")
(replace "\\r" "\r")
@@ -175,12 +171,8 @@
(struct: #export _ (Hash Text)
(def: eq Eq<Text>)
- (def: hash
- (|>. []
- (_lux_proc ["jvm" "invokevirtual:java.lang.Object:hashCode:"])
- []
- (_lux_proc ["jvm" "i2l"])
- int-to-nat)))
+ (def: (hash input)
+ (_lux_proc ["text" "hash"] [input])))
(def: #export concat
(-> (List Text) Text)
diff --git a/stdlib/source/lux/math.lux b/stdlib/source/lux/math.lux
index e87bb1b1b..6f41b3e9b 100644
--- a/stdlib/source/lux/math.lux
+++ b/stdlib/source/lux/math.lux
@@ -5,7 +5,6 @@
[number "Int/" Number<Int>]
[product]
text/format)
- host
[compiler]
(macro ["s" syntax #+ syntax: Syntax "s/" Functor<Syntax>]
[ast])))
@@ -14,10 +13,10 @@
(do-template [<name> <value>]
[(def: #export <name>
Real
- (_lux_proc ["jvm" <value>] []))]
+ (_lux_proc ["math" <value>] []))]
- [e "getstatic:java.lang.Math:E"]
- [pi "getstatic:java.lang.Math:PI"]
+ [e "e"]
+ [pi "pi"]
)
(def: #export tau
@@ -26,52 +25,43 @@
6.28318530717958647692)
(do-template [<name> <method>]
- [(def: #export (<name> n)
+ [(def: #export (<name> input)
(-> Real Real)
- (_lux_proc ["jvm" <method>] [n]))]
+ (_lux_proc ["math" <method>] [input]))]
- [cos "invokestatic:java.lang.Math:cos:double"]
- [sin "invokestatic:java.lang.Math:sin:double"]
- [tan "invokestatic:java.lang.Math:tan:double"]
+ [cos "cos"]
+ [sin "sin"]
+ [tan "tan"]
- [acos "invokestatic:java.lang.Math:acos:double"]
- [asin "invokestatic:java.lang.Math:asin:double"]
- [atan "invokestatic:java.lang.Math:atan:double"]
+ [acos "acos"]
+ [asin "asin"]
+ [atan "atan"]
- [cosh "invokestatic:java.lang.Math:cosh:double"]
- [sinh "invokestatic:java.lang.Math:sinh:double"]
- [tanh "invokestatic:java.lang.Math:tanh:double"]
+ [cosh "cosh"]
+ [sinh "sinh"]
+ [tanh "tanh"]
- [exp "invokestatic:java.lang.Math:exp:double"]
- [log "invokestatic:java.lang.Math:log:double"]
+ [exp "exp"]
+ [log "log"]
- [root2 "invokestatic:java.lang.Math:sqrt:double"]
- [root3 "invokestatic:java.lang.Math:cbrt:double"]
+ [root2 "root2"]
+ [root3 "root3"]
- [degrees "invokestatic:java.lang.Math:toDegrees:double"]
- [radians "invokestatic:java.lang.Math:toRadians:double"]
- )
+ [degrees "degrees"]
+ [radians "radians"]
-(do-template [<name> <method>]
- [(def: #export (<name> n)
- (-> Real Real)
- (_lux_proc ["jvm" <method>] [n]))]
-
- [ceil "invokestatic:java.lang.Math:ceil:double"]
- [floor "invokestatic:java.lang.Math:floor:double"]
+ [ceil "ceil"]
+ [floor "floor"]
+ [round "round"]
)
-(def: #export (round n)
- (-> Real Real)
- (int-to-real (_lux_proc ["jvm" "invokestatic:java.lang.Math:round:double"] [n])))
-
(do-template [<name> <method>]
[(def: #export (<name> param subject)
(-> Real Real Real)
- (_lux_proc ["jvm" <method>] [subject param]))]
+ (_lux_proc ["math" <method>] [subject param]))]
- [atan2 "invokestatic:java.lang.Math:atan2:double,double"]
- [pow "invokestatic:java.lang.Math:pow:double,double"]
+ [atan2 "atan2"]
+ [pow "pow"]
)
(def: #export (log' base input)