aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/text/lexer.lux
diff options
context:
space:
mode:
authorEduardo Julian2018-08-20 23:21:01 -0400
committerEduardo Julian2018-08-20 23:21:01 -0400
commita1944a9d561e76b02717673647b87704118c03a6 (patch)
tree36a76c0a82a9dd120152366aee3f4e1e307f8377 /stdlib/source/lux/data/text/lexer.lux
parent726dbf02da1ae0da3965ec0a72e99fec1730f882 (diff)
- More minor optimizations.
- Removed ratio syntax for Frac.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/data/text/lexer.lux64
1 files changed, 32 insertions, 32 deletions
diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/data/text/lexer.lux
index 80e2cea0f..677810eb8 100644
--- a/stdlib/source/lux/data/text/lexer.lux
+++ b/stdlib/source/lux/data/text/lexer.lux
@@ -4,14 +4,14 @@
[monad (#+ do Monad)]
["p" parser]]
[data
- ["." text ("text/." Monoid<Text>)]
["." product]
["." maybe]
["e" error]
[collection
["." list ("list/." Fold<List>)]]]
[macro
- ["." code]]])
+ ["." code]]]
+ ["." // ("text/." Monoid<Text>)])
(type: Offset Nat)
@@ -26,7 +26,7 @@
(def: (remaining offset tape)
(-> Offset Text Text)
- (|> tape (text.split offset) maybe.assume product.right))
+ (|> tape (//.split offset) maybe.assume product.right))
(def: cannot-lex-error Text "Cannot lex from empty text.")
@@ -41,7 +41,7 @@
(#e.Error msg)
(#e.Success [[end-offset _] output])
- (if (n/= end-offset (text.size input))
+ (if (n/= end-offset (//.size input))
(#e.Success output)
(#e.Error (unconsumed-input-error end-offset input)))
))
@@ -67,9 +67,9 @@
{#.doc "Just returns the next character without applying any logic."}
(Lexer Text)
(function (_ [offset tape])
- (case (text.nth offset tape)
+ (case (//.nth offset tape)
(#.Some output)
- (#e.Success [[(inc offset) tape] (text.from-code output)])
+ (#e.Success [[(inc offset) tape] (//.from-code output)])
_
(#e.Error cannot-lex-error))))
@@ -102,22 +102,22 @@
{#.doc "Lex a text if it matches the given sample."}
(-> Text (Lexer Any))
(function (_ [offset tape])
- (case (text.index-of' reference offset tape)
+ (case (//.index-of' reference offset tape)
(#.Some where)
(if (n/= offset where)
- (#e.Success [[(n/+ (text.size reference) offset) tape] []])
- (#e.Error ($_ text/compose "Could not match: " (text.encode reference) " @ " (maybe.assume (text.clip' offset tape)))))
+ (#e.Success [[(n/+ (//.size reference) offset) tape] []])
+ (#e.Error ($_ text/compose "Could not match: " (//.encode reference) " @ " (maybe.assume (//.clip' offset tape)))))
_
- (#e.Error ($_ text/compose "Could not match: " (text.encode reference))))))
+ (#e.Error ($_ text/compose "Could not match: " (//.encode reference))))))
(def: #export (this? reference)
{#.doc "Lex a text if it matches the given sample."}
(-> Text (Lexer Bit))
(function (_ (^@ input [offset tape]))
- (case (text.index-of' reference offset tape)
+ (case (//.index-of' reference offset tape)
(^multi (#.Some where) (n/= offset where))
- (#e.Success [[(n/+ (text.size reference) offset) tape] #1])
+ (#e.Success [[(n/+ (//.size reference) offset) tape] #1])
_
(#e.Success [input #0]))))
@@ -126,7 +126,7 @@
{#.doc "Ensure the lexer's input is empty."}
(Lexer Any)
(function (_ (^@ input [offset tape]))
- (if (n/= offset (text.size tape))
+ (if (n/= offset (//.size tape))
(#e.Success [input []])
(#e.Error (unconsumed-input-error offset tape)))))
@@ -134,15 +134,15 @@
{#.doc "Ask if the lexer's input is empty."}
(Lexer Bit)
(function (_ (^@ input [offset tape]))
- (#e.Success [input (n/= offset (text.size tape))])))
+ (#e.Success [input (n/= offset (//.size tape))])))
(def: #export peek
{#.doc "Lex the next character (without consuming it from the input)."}
(Lexer Text)
(function (_ (^@ input [offset tape]))
- (case (text.nth offset tape)
+ (case (//.nth offset tape)
(#.Some output)
- (#e.Success [input (text.from-code output)])
+ (#e.Success [input (//.from-code output)])
_
(#e.Error cannot-lex-error))))
@@ -158,8 +158,8 @@
(-> Nat Nat (Lexer Text))
(do p.Monad<Parser>
[char any
- #let [char' (maybe.assume (text.nth 0 char))]
- _ (p.assert ($_ text/compose "Character is not within range: " (text.from-code bottom) "-" (text.from-code top))
+ #let [char' (maybe.assume (//.nth 0 char))]
+ _ (p.assert ($_ text/compose "Character is not within range: " (//.from-code bottom) "-" (//.from-code top))
(.and (n/>= bottom char')
(n/<= top char')))]
(wrap char)))
@@ -199,10 +199,10 @@
{#.doc (code.text ($_ text/compose "Only lex characters that are" <description-modifier> " part of a piece of text."))}
(-> Text (Lexer Text))
(function (_ [offset tape])
- (case (text.nth offset tape)
+ (case (//.nth offset tape)
(#.Some output)
- (let [output (text.from-code output)]
- (if (<modifier> (text.contains? output options))
+ (let [output (//.from-code output)]
+ (if (<modifier> (//.contains? output options))
(#e.Success [[(inc offset) tape] output])
(#e.Error ($_ text/compose "Character (" output
") is should " <description-modifier>
@@ -220,10 +220,10 @@
{#.doc (code.text ($_ text/compose "Only lex characters that are" <description-modifier> " part of a piece of text."))}
(-> Text (Lexer Slice))
(function (_ [offset tape])
- (case (text.nth offset tape)
+ (case (//.nth offset tape)
(#.Some output)
- (let [output (text.from-code output)]
- (if (<modifier> (text.contains? output options))
+ (let [output (//.from-code output)]
+ (if (<modifier> (//.contains? output options))
(#e.Success [[(inc offset) tape]
{#basis offset
#distance 1}])
@@ -242,11 +242,11 @@
{#.doc "Only lex characters that satisfy a predicate."}
(-> (-> Nat Bit) (Lexer Text))
(function (_ [offset tape])
- (case (text.nth offset tape)
+ (case (//.nth offset tape)
(#.Some output)
(if (p output)
- (#e.Success [[(inc offset) tape] (text.from-code output)])
- (#e.Error ($_ text/compose "Character does not satisfy predicate: " (text.from-code output))))
+ (#e.Success [[(inc offset) tape] (//.from-code output)])
+ (#e.Error ($_ text/compose "Character does not satisfy predicate: " (//.from-code output))))
_
(#e.Error cannot-lex-error))))
@@ -254,7 +254,7 @@
(def: #export space
{#.doc "Only lex white-space."}
(Lexer Text)
- (satisfies text.space?))
+ (satisfies //.space?))
(def: #export (and left right)
(-> (Lexer Text) (Lexer Text) (Lexer Text))
@@ -274,7 +274,7 @@
[(def: #export (<name> lexer)
{#.doc (code.text ($_ text/compose "Lex " <doc-modifier> " characters as a single continuous text."))}
(-> (Lexer Text) (Lexer Text))
- (|> lexer <base> (:: p.Monad<Parser> map text.concat)))]
+ (|> lexer <base> (:: p.Monad<Parser> map //.concat)))]
[some p.some "some"]
[many p.many "many"]
@@ -294,7 +294,7 @@
[(def: #export (<name> amount lexer)
{#.doc (code.text ($_ text/compose "Lex " <doc-modifier> " N characters."))}
(-> Nat (Lexer Text) (Lexer Text))
- (|> lexer (<base> amount) (:: p.Monad<Parser> map text.concat)))]
+ (|> lexer (<base> amount) (:: p.Monad<Parser> map //.concat)))]
[exactly p.exactly "exactly"]
[at-most p.at-most "at most"]
@@ -315,7 +315,7 @@
(def: #export (between from to lexer)
{#.doc "Lex between N and M characters."}
(-> Nat Nat (Lexer Text) (Lexer Text))
- (|> lexer (p.between from to) (:: p.Monad<Parser> map text.concat)))
+ (|> lexer (p.between from to) (:: p.Monad<Parser> map //.concat)))
(def: #export (between! from to lexer)
{#.doc "Lex between N and M characters."}
@@ -344,7 +344,7 @@
(do p.Monad<Parser>
[[basis distance] lexer]
(function (_ (^@ input [offset tape]))
- (case (text.clip basis (n/+ basis distance) tape)
+ (case (//.clip basis (n/+ basis distance) tape)
(#.Some output)
(#e.Success [input output])