aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/compiler/default/syntax.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/compiler/default/syntax.lux')
-rw-r--r--stdlib/source/lux/compiler/default/syntax.lux58
1 files changed, 29 insertions, 29 deletions
diff --git a/stdlib/source/lux/compiler/default/syntax.lux b/stdlib/source/lux/compiler/default/syntax.lux
index e06590f2e..5b20dcff5 100644
--- a/stdlib/source/lux/compiler/default/syntax.lux
+++ b/stdlib/source/lux/compiler/default/syntax.lux
@@ -64,7 +64,7 @@
[content (l.many (l.one-of new-line))]
(wrap [(|> where
(update@ #.line (n/+ (text.size content)))
- (set@ #.column +0))
+ (set@ #.column 0))
content]))
))
@@ -78,7 +78,7 @@
_ (l.this new-line)]
(wrap [(|> where
(update@ #.line inc)
- (set@ #.column +0))
+ (set@ #.column 0))
comment])))
## This is just a helper parser to find text which doesn't run into
@@ -100,7 +100,7 @@
(do p.Monad<Parser>
[_ (l.this "#(")]
(loop [comment ""
- where (update@ #.column (n/+ +2) where)]
+ where (update@ #.column (n/+ 2) where)]
($_ p.either
## These are normal chunks of commented text.
(do @
@@ -115,7 +115,7 @@
(recur (format comment new-line)
(|> where
(update@ #.line inc)
- (set@ #.column +0))))
+ (set@ #.column 0))))
## This is the rule for handling nested sub-comments.
## Ultimately, the whole comment is just treated as text
## (the comment must respect the syntax structure, but the
@@ -129,7 +129,7 @@
## Finally, this is the rule for closing the comment.
(do @
[_ (l.this ")#")]
- (wrap [(update@ #.column (n/+ +2) where)
+ (wrap [(update@ #.column (n/+ 2) where)
comment]))
))))
@@ -171,22 +171,22 @@
[code l.any]
(case code
## Handle special cases.
- "t" (wrap [+2 "\t"])
- "v" (wrap [+2 "\v"])
- "b" (wrap [+2 "\b"])
- "n" (wrap [+2 "\n"])
- "r" (wrap [+2 "\r"])
- "f" (wrap [+2 "\f"])
- "\"" (wrap [+2 "\""])
- "\\" (wrap [+2 "\\"])
+ "t" (wrap [2 "\t"])
+ "v" (wrap [2 "\v"])
+ "b" (wrap [2 "\b"])
+ "n" (wrap [2 "\n"])
+ "r" (wrap [2 "\r"])
+ "f" (wrap [2 "\f"])
+ "\"" (wrap [2 "\""])
+ "\\" (wrap [2 "\\"])
## Handle unicode escapes.
"u"
(do p.Monad<Parser>
- [code (l.between +1 +4 l.hexadecimal)]
- (wrap (case (|> code (format "+") (:: number.Hex@Codec<Text,Nat> decode))
+ [code (l.between 1 4 l.hexadecimal)]
+ (wrap (case (:: number.Hex@Codec<Text,Nat> decode code)
(#.Right value)
- [(n/+ +2 (text.size code)) (text.from-code value)]
+ [(n/+ 2 (text.size code)) (text.from-code value)]
_
(undefined))))
@@ -207,6 +207,8 @@
(l.and l.decimal
(l.some rich-digit)))
+(def: sign^ (l.one-of "+-"))
+
(do-template [<name> <tag> <lexer> <codec>]
[(def: #export (<name> where)
(-> Cursor (l.Lexer [Cursor Code]))
@@ -221,8 +223,7 @@
[where (<tag> value)]]))))]
[int #.Int
- (l.and (p.default "" (l.one-of "-"))
- rich-digits^)
+ (l.and sign^ rich-digits^)
number.Codec<Text,Int>]
[rev #.Rev
@@ -251,7 +252,7 @@
(update@ #.column (n/+ chars-consumed)))
char]))))
_ (l.this "\"")
- #let [char (maybe.assume (text.nth +0 char))]]
+ #let [char (maybe.assume (text.nth 0 char))]]
(wrap [(|> where'
(update@ #.column inc))
[where (#.Nat char)]])))
@@ -259,8 +260,7 @@
(def: (normal-nat where)
(-> Cursor (l.Lexer [Cursor Code]))
(do p.Monad<Parser>
- [chunk (l.and (l.one-of "+")
- rich-digits^)]
+ [chunk rich-digits^]
(case (:: number.Codec<Text,Nat> decode chunk)
(#.Left error)
(p.fail error)
@@ -278,14 +278,14 @@
(-> Cursor (l.Lexer [Cursor Code]))
(do p.Monad<Parser>
[chunk ($_ l.and
- (p.default "" (l.one-of "-"))
+ sign^
rich-digits^
(l.one-of ".")
rich-digits^
(p.default ""
($_ l.and
(l.one-of "eE")
- (p.default "" (l.one-of "+-"))
+ sign^
rich-digits^)))]
(case (:: number.Codec<Text,Frac> decode chunk)
(#.Left error)
@@ -317,9 +317,9 @@
_ (l.this? "/")
denominator frac-ratio-fragment
_ (p.assert "Denominator cannot be 0."
- (not (f/= 0.0 denominator)))]
+ (not (f/= +0.0 denominator)))]
(wrap (|> numerator
- (f/* (if signed? -1.0 1.0))
+ (f/* (if signed? -1.0 +1.0))
(f// denominator)))))]
(wrap [(update@ #.column (n/+ (text.size chunk)) where)
[where (#.Frac value)]])))
@@ -412,7 +412,7 @@
(recur (format text-read new-line)
(|> where
(update@ #.line inc)
- (set@ #.column +0))
+ (set@ #.column 0))
#1)))))]
(wrap [where'
[where (#.Text text-read)]])))
@@ -529,7 +529,7 @@
[_ (l.this current-module-mark)
def-name name-part^]
(wrap [[current-module def-name]
- (n/+ +2 (text.size def-name))]))
+ (n/+ 2 (text.size def-name))]))
## If the name is prefixed by the mark, but no module
## part, the module is assumed to be "lux" (otherwise known as
## the 'prelude').
@@ -559,7 +559,7 @@
second-part]
($_ n/+
(text.size first-part)
- +1
+ 1
(text.size second-part))]))
(wrap [["" first-part]
(text.size first-part)])))))
@@ -569,7 +569,7 @@
(do p.Monad<Parser>
[[value length] (p.after (l.this "#")
(name^ current-module aliases))]
- (wrap [(update@ #.column (|>> ($_ n/+ +1 length)) where)
+ (wrap [(update@ #.column (|>> ($_ n/+ 1 length)) where)
[where (#.Tag value)]])))
(def: #export (identifier current-module aliases where)