aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/lang/syntax.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/lang/syntax.lux426
1 files changed, 213 insertions, 213 deletions
diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux
index 49e27aecd..46558014e 100644
--- a/stdlib/source/lux/lang/syntax.lux
+++ b/stdlib/source/lux/lang/syntax.lux
@@ -24,7 +24,7 @@
## Lux Code nodes/tokens are annotated with cursor meta-data
## (file-name, line, column) to keep track of their provenance and
## location, which is helpful for documentation and debugging.
-(;module:
+(.module:
lux
(lux (control monad
["p" parser "p/" Monad<Parser>]
@@ -51,42 +51,42 @@
## It operates recursively in order to produce the longest continuous
## chunk of white-space.
(def: (space^ where)
- (-> Cursor (l;Lexer [Cursor Text]))
- (p;either (do p;Monad<Parser>
- [content (l;many (l;one-of white-space))]
- (wrap [(update@ #;column (n/+ (text;size content)) where)
+ (-> Cursor (l.Lexer [Cursor Text]))
+ (p.either (do p.Monad<Parser>
+ [content (l.many (l.one-of white-space))]
+ (wrap [(update@ #.column (n/+ (text.size content)) where)
content]))
## New-lines must be handled as a separate case to ensure line
## information is handled properly.
- (do p;Monad<Parser>
- [content (l;many (l;one-of new-line))]
+ (do p.Monad<Parser>
+ [content (l.many (l.one-of new-line))]
(wrap [(|> where
- (update@ #;line (n/+ (text;size content)))
- (set@ #;column +0))
+ (update@ #.line (n/+ (text.size content)))
+ (set@ #.column +0))
content]))
))
## Single-line comments can start anywhere, but only go up to the
## next new-line.
(def: (single-line-comment^ where)
- (-> Cursor (l;Lexer [Cursor Text]))
- (do p;Monad<Parser>
- [_ (l;this "##")
- comment (l;some (l;none-of new-line))
- _ (l;this new-line)]
+ (-> Cursor (l.Lexer [Cursor Text]))
+ (do p.Monad<Parser>
+ [_ (l.this "##")
+ comment (l.some (l.none-of new-line))
+ _ (l.this new-line)]
(wrap [(|> where
- (update@ #;line n/inc)
- (set@ #;column +0))
+ (update@ #.line n/inc)
+ (set@ #.column +0))
comment])))
## This is just a helper parser to find text which doesn't run into
## any special character sequences for multi-line comments.
(def: comment-bound^
- (l;Lexer Unit)
- ($_ p;either
- (l;this new-line)
- (l;this ")#")
- (l;this "#(")))
+ (l.Lexer Unit)
+ ($_ p.either
+ (l.this new-line)
+ (l.this ")#")
+ (l.this "#(")))
## Multi-line comments are bounded by #( these delimiters, #(and, they may
## also be nested)# )#.
@@ -94,26 +94,26 @@
## That is, any nested comment must have matched delimiters.
## Unbalanced comments ought to be rejected as invalid code.
(def: (multi-line-comment^ where)
- (-> Cursor (l;Lexer [Cursor Text]))
- (do p;Monad<Parser>
- [_ (l;this "#(")]
+ (-> Cursor (l.Lexer [Cursor Text]))
+ (do p.Monad<Parser>
+ [_ (l.this "#(")]
(loop [comment ""
- where (update@ #;column (n/+ +2) where)]
- ($_ p;either
+ where (update@ #.column (n/+ +2) where)]
+ ($_ p.either
## These are normal chunks of commented text.
(do @
- [chunk (l;many (l;not comment-bound^))]
+ [chunk (l.many (l.not comment-bound^))]
(recur (format comment chunk)
(|> where
- (update@ #;column (n/+ (text;size chunk))))))
+ (update@ #.column (n/+ (text.size chunk))))))
## This is a special rule to handle new-lines within
## comments properly.
(do @
- [_ (l;this new-line)]
+ [_ (l.this new-line)]
(recur (format comment new-line)
(|> where
- (update@ #;line n/inc)
- (set@ #;column +0))))
+ (update@ #.line n/inc)
+ (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
@@ -126,8 +126,8 @@
sub-where))
## Finally, this is the rule for closing the comment.
(do @
- [_ (l;this ")#")]
- (wrap [(update@ #;column (n/+ +2) where)
+ [_ (l.this ")#")]
+ (wrap [(update@ #.column (n/+ +2) where)
comment]))
))))
@@ -138,8 +138,8 @@
## from being used in any situation (alternatively, forcing one type
## of comment to be the only usable one).
(def: (comment^ where)
- (-> Cursor (l;Lexer [Cursor Text]))
- (p;either (single-line-comment^ where)
+ (-> Cursor (l.Lexer [Cursor Text]))
+ (p.either (single-line-comment^ where)
(multi-line-comment^ where)))
## To simplify parsing, I remove any left-padding that an Code token
@@ -147,15 +147,15 @@
## Left-padding is assumed to be either white-space or a comment.
## The cursor gets updated, but the padding gets ignored.
(def: (left-padding^ where)
- (-> Cursor (l;Lexer Cursor))
- ($_ p;either
- (do p;Monad<Parser>
+ (-> Cursor (l.Lexer Cursor))
+ ($_ p.either
+ (do p.Monad<Parser>
[[where comment] (comment^ where)]
(left-padding^ where))
- (do p;Monad<Parser>
+ (do p.Monad<Parser>
[[where white-space] (space^ where)]
(left-padding^ where))
- (:: p;Monad<Parser> wrap where)))
+ (:: p.Monad<Parser> wrap where)))
## Escaped character sequences follow the usual syntax of
## back-slash followed by a letter (e.g. \n).
@@ -163,10 +163,10 @@
## and 4 characters long (e.g. \u12aB).
## Escaped characters may show up in Char and Text literals.
(def: escaped-char^
- (l;Lexer [Nat Text])
- (p;after (l;this "\\")
- (do p;Monad<Parser>
- [code l;any]
+ (l.Lexer [Nat Text])
+ (p.after (l.this "\\")
+ (do p.Monad<Parser>
+ [code l.any]
(case code
## Handle special cases.
"t" (wrap [+2 "\t"])
@@ -180,169 +180,169 @@
## 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))
- (#;Right value)
- [(n/+ +2 (text;size code)) (text;from-code value)]
+ (do p.Monad<Parser>
+ [code (l.between +1 +4 l.hexadecimal)]
+ (wrap (case (|> code (format "+") (:: number.Hex@Codec<Text,Nat> decode))
+ (#.Right value)
+ [(n/+ +2 (text.size code)) (text.from-code value)]
_
(undefined))))
_
- (p;fail (format "Invalid escaping syntax: " (%t code)))))))
+ (p.fail (format "Invalid escaping syntax: " (%t code)))))))
## These are very simple parsers that just cut chunks of text in
## specific shapes and then use decoders already present in the
## standard library to actually produce the values from the literals.
(def: rich-digit
- (l;Lexer Text)
- (p;either l;decimal
- (p;after (l;this "_") (p/wrap ""))))
+ (l.Lexer Text)
+ (p.either l.decimal
+ (p.after (l.this "_") (p/wrap ""))))
(def: rich-digits^
- (l;Lexer Text)
- (l;seq l;decimal
- (l;some rich-digit)))
+ (l.Lexer Text)
+ (l.seq l.decimal
+ (l.some rich-digit)))
(def: (marker^ token)
- (-> Text (l;Lexer Text))
- (p;after (l;this token) (p/wrap token)))
+ (-> Text (l.Lexer Text))
+ (p.after (l.this token) (p/wrap token)))
(do-template [<name> <tag> <lexer> <codec>]
[(def: #export (<name> where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
[chunk <lexer>]
(case (:: <codec> decode chunk)
- (#;Left error)
- (p;fail error)
+ (#.Left error)
+ (p.fail error)
- (#;Right value)
- (wrap [(update@ #;column (n/+ (text;size chunk)) where)
+ (#.Right value)
+ (wrap [(update@ #.column (n/+ (text.size chunk)) where)
[where (<tag> value)]]))))]
- [bool #;Bool
- (p;either (marker^ "true") (marker^ "false"))
- bool;Codec<Text,Bool>]
+ [bool #.Bool
+ (p.either (marker^ "true") (marker^ "false"))
+ bool.Codec<Text,Bool>]
- [int #;Int
- (l;seq (p;default "" (l;one-of "-"))
+ [int #.Int
+ (l.seq (p.default "" (l.one-of "-"))
rich-digits^)
- number;Codec<Text,Int>]
+ number.Codec<Text,Int>]
- [deg #;Deg
- (l;seq (l;one-of ".")
+ [deg #.Deg
+ (l.seq (l.one-of ".")
rich-digits^)
- number;Codec<Text,Deg>]
+ number.Codec<Text,Deg>]
)
(def: (nat-char where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [_ (l;this "#\"")
- [where' char] (: (l;Lexer [Cursor Text])
- ($_ p;either
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [_ (l.this "#\"")
+ [where' char] (: (l.Lexer [Cursor Text])
+ ($_ p.either
## Normal text characters.
(do @
- [normal (l;none-of "\\\"\n")]
+ [normal (l.none-of "\\\"\n")]
(wrap [(|> where
- (update@ #;column n/inc))
+ (update@ #.column n/inc))
normal]))
## Must handle escaped
## chars separately.
(do @
[[chars-consumed char] escaped-char^]
(wrap [(|> where
- (update@ #;column (n/+ chars-consumed)))
+ (update@ #.column (n/+ chars-consumed)))
char]))))
- _ (l;this "\"")
- #let [char (maybe;assume (text;nth +0 char))]]
+ _ (l.this "\"")
+ #let [char (maybe.assume (text.nth +0 char))]]
(wrap [(|> where'
- (update@ #;column n/inc))
- [where (#;Nat char)]])))
+ (update@ #.column n/inc))
+ [where (#.Nat char)]])))
(def: (normal-nat where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [chunk (l;seq (l;one-of "+")
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [chunk (l.seq (l.one-of "+")
rich-digits^)]
- (case (:: number;Codec<Text,Nat> decode chunk)
- (#;Left error)
- (p;fail error)
+ (case (:: number.Codec<Text,Nat> decode chunk)
+ (#.Left error)
+ (p.fail error)
- (#;Right value)
- (wrap [(update@ #;column (n/+ (text;size chunk)) where)
- [where (#;Nat value)]]))))
+ (#.Right value)
+ (wrap [(update@ #.column (n/+ (text.size chunk)) where)
+ [where (#.Nat value)]]))))
(def: #export (nat where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (p;either (normal-nat where)
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (p.either (normal-nat where)
(nat-char where)))
(def: (normal-frac where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [chunk ($_ l;seq
- (p;default "" (l;one-of "-"))
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [chunk ($_ l.seq
+ (p.default "" (l.one-of "-"))
rich-digits^
- (l;one-of ".")
+ (l.one-of ".")
rich-digits^
- (p;default ""
- ($_ l;seq
- (l;one-of "eE")
- (p;default "" (l;one-of "+-"))
+ (p.default ""
+ ($_ l.seq
+ (l.one-of "eE")
+ (p.default "" (l.one-of "+-"))
rich-digits^)))]
- (case (:: number;Codec<Text,Frac> decode chunk)
- (#;Left error)
- (p;fail error)
+ (case (:: number.Codec<Text,Frac> decode chunk)
+ (#.Left error)
+ (p.fail error)
- (#;Right value)
- (wrap [(update@ #;column (n/+ (text;size chunk)) where)
- [where (#;Frac value)]]))))
+ (#.Right value)
+ (wrap [(update@ #.column (n/+ (text.size chunk)) where)
+ [where (#.Frac value)]]))))
(def: frac-ratio-fragment
- (l;Lexer Frac)
- (<| (p;codec number;Codec<Text,Frac>)
- (:: p;Monad<Parser> map (function [digits]
+ (l.Lexer Frac)
+ (<| (p.codec number.Codec<Text,Frac>)
+ (:: p.Monad<Parser> map (function [digits]
(format digits ".0")))
rich-digits^))
(def: (ratio-frac where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [chunk ($_ l;seq
- (p;default "" (l;one-of "-"))
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [chunk ($_ l.seq
+ (p.default "" (l.one-of "-"))
rich-digits^
- (l;one-of "/")
+ (l.one-of "/")
rich-digits^)
- value (l;local chunk
+ value (l.local chunk
(do @
- [signed? (l;this? "-")
+ [signed? (l.this? "-")
numerator frac-ratio-fragment
- _ (l;this? "/")
+ _ (l.this? "/")
denominator frac-ratio-fragment
- _ (p;assert "Denominator cannot be 0."
+ _ (p.assert "Denominator cannot be 0."
(not (f/= 0.0 denominator)))]
(wrap (|> numerator
(f/* (if signed? -1.0 1.0))
(f// denominator)))))]
- (wrap [(update@ #;column (n/+ (text;size chunk)) where)
- [where (#;Frac value)]])))
+ (wrap [(update@ #.column (n/+ (text.size chunk)) where)
+ [where (#.Frac value)]])))
(def: #export (frac where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (p;either (normal-frac where)
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (p.either (normal-frac where)
(ratio-frac where)))
## This parser looks so complex because text in Lux can be multi-line
## and there are rules regarding how this is handled.
(def: #export (text where)
- (-> Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
[## Lux text "is delimited by double-quotes", as usual in most
## programming languages.
- _ (l;this "\"")
+ _ (l.this "\"")
## I must know what column the text body starts at (which is
## always 1 column after the left-delimiting quote).
## This is important because, when procesing subsequent lines,
@@ -350,8 +350,8 @@
## as many spaces as necessary to be column-aligned.
## This helps ensure that the formatting on the text in the
## source-code matches the formatting of the Text value.
- #let [offset-column (n/inc (get@ #;column where))]
- [where' text-read] (: (l;Lexer [Cursor Text])
+ #let [offset-column (n/inc (get@ #.column where))]
+ [where' text-read] (: (l.Lexer [Cursor Text])
## I must keep track of how much of the
## text body has been read, how far the
## cursor has progressed, and whether I'm
@@ -359,9 +359,9 @@
## processing normal text body.
(loop [text-read ""
where (|> where
- (update@ #;column n/inc))
+ (update@ #.column n/inc))
must-have-offset? false]
- (p;either (if must-have-offset?
+ (p.either (if must-have-offset?
## If I'm at the start of a
## new line, I must ensure the
## space-offset is at least
@@ -369,30 +369,30 @@
## the text's body's column,
## to ensure they are aligned.
(do @
- [offset (l;many (l;one-of " "))
- #let [offset-size (text;size offset)]]
+ [offset (l.many (l.one-of " "))
+ #let [offset-size (text.size offset)]]
(if (n/>= offset-column offset-size)
## Any extra offset
## becomes part of the
## text's body.
(recur (|> offset
- (text;split offset-column)
- (maybe;default (undefined))
- product;right
+ (text.split offset-column)
+ (maybe.default (undefined))
+ product.right
(format text-read))
(|> where
- (update@ #;column (n/+ offset-size)))
+ (update@ #.column (n/+ offset-size)))
false)
- (p;fail (format "Each line of a multi-line text must have an appropriate offset!\n"
+ (p.fail (format "Each line of a multi-line text must have an appropriate offset!\n"
"Expected: " (%i (nat-to-int offset-column)) " columns.\n"
" Actual: " (%i (nat-to-int offset-size)) " columns.\n"))))
- ($_ p;either
+ ($_ p.either
## Normal text characters.
(do @
- [normal (l;many (l;none-of "\\\"\n"))]
+ [normal (l.many (l.none-of "\\\"\n"))]
(recur (format text-read normal)
(|> where
- (update@ #;column (n/+ (text;size normal))))
+ (update@ #.column (n/+ (text.size normal))))
false))
## Must handle escaped
## chars separately.
@@ -400,13 +400,13 @@
[[chars-consumed char] escaped-char^]
(recur (format text-read char)
(|> where
- (update@ #;column (n/+ chars-consumed)))
+ (update@ #.column (n/+ chars-consumed)))
false))
## The text ends when it
## reaches the right-delimiter.
(do @
- [_ (l;this "\"")]
- (wrap [(update@ #;column n/inc where)
+ [_ (l.this "\"")]
+ (wrap [(update@ #.column n/inc where)
text-read]))))
## If a new-line is
## encountered, it gets
@@ -414,14 +414,14 @@
## the loop is alerted that the
## next line must have an offset.
(do @
- [_ (l;this new-line)]
+ [_ (l.this new-line)]
(recur (format text-read new-line)
(|> where
- (update@ #;line n/inc)
- (set@ #;column +0))
+ (update@ #.line n/inc)
+ (set@ #.column +0))
true)))))]
(wrap [where'
- [where (#;Text text-read)]])))
+ [where (#.Text text-read)]])))
## Form and tuple syntax is mostly the same, differing only in the
## delimiters involved.
@@ -429,32 +429,32 @@
(do-template [<name> <tag> <open> <close>]
[(def: (<name> where ast)
(-> Cursor
- (-> Cursor (l;Lexer [Cursor Code]))
- (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [_ (l;this <open>)
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [_ (l.this <open>)
[where' elems] (loop [elems (: (Sequence Code)
- sequence;empty)
+ sequence.empty)
where where]
- (p;either (do @
+ (p.either (do @
[## Must update the cursor as I
## go along, to keep things accurate.
[where' elem] (ast where)]
- (recur (sequence;add elem elems)
+ (recur (sequence.add elem elems)
where'))
(do @
[## Must take into account any
## padding present before the
## end-delimiter.
where' (left-padding^ where)
- _ (l;this <close>)]
- (wrap [(update@ #;column n/inc where')
- (sequence;to-list elems)]))))]
+ _ (l.this <close>)]
+ (wrap [(update@ #.column n/inc where')
+ (sequence.to-list elems)]))))]
(wrap [where'
[where (<tag> elems)]])))]
- [form #;Form "(" ")"]
- [tuple #;Tuple "[" "]"]
+ [form #.Form "(" ")"]
+ [tuple #.Tuple "[" "]"]
)
## Records are almost (syntactically) the same as forms and tuples,
@@ -468,34 +468,34 @@
## macros.
(def: (record where ast)
(-> Cursor
- (-> Cursor (l;Lexer [Cursor Code]))
- (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
- [_ (l;this "{")
+ (-> Cursor (l.Lexer [Cursor Code]))
+ (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
+ [_ (l.this "{")
[where' elems] (loop [elems (: (Sequence [Code Code])
- sequence;empty)
+ sequence.empty)
where where]
- (p;either (do @
+ (p.either (do @
[[where' key] (ast where)
[where' val] (ast where')]
- (recur (sequence;add [key val] elems)
+ (recur (sequence.add [key val] elems)
where'))
(do @
[where' (left-padding^ where)
- _ (l;this "}")]
- (wrap [(update@ #;column n/inc where')
- (sequence;to-list elems)]))))]
+ _ (l.this "}")]
+ (wrap [(update@ #.column n/inc where')
+ (sequence.to-list elems)]))))]
(wrap [where'
- [where (#;Record elems)]])))
+ [where (#.Record elems)]])))
## The parts of an identifier are separated by a single mark.
-## E.g. module;name.
+## E.g. module.name.
## Only one such mark may be used in an identifier, since there
## can only be 2 parts to an identifier (the module [before the
## mark], and the name [after the mark]).
## There are also some extra rules regarding identifier syntax,
## encoded on the parser.
-(def: identifier-separator Text ";")
+(def: identifier-separator Text ".")
## A Lux identifier is a pair of chunks of text, where the first-part
## refers to the module that gives context to the identifier, and the
@@ -511,13 +511,13 @@
## Additionally, the first character in an identifier's part cannot be
## a digit, to avoid confusion with regards to numbers.
(def: ident-part^
- (l;Lexer Text)
- (do p;Monad<Parser>
+ (l.Lexer Text)
+ (do p.Monad<Parser>
[#let [digits "0123456789"
delimiters (format "()[]{}#\"" identifier-separator)
space (format white-space new-line)
- head-lexer (l;none-of (format digits delimiters space))
- tail-lexer (l;some (l;none-of (format delimiters space)))]
+ head-lexer (l.none-of (format digits delimiters space))
+ tail-lexer (l.some (l.none-of (format delimiters space)))]
head head-lexer
tail tail-lexer]
(wrap (format head tail))))
@@ -525,28 +525,28 @@
(def: current-module-mark Text (format identifier-separator identifier-separator))
(def: (ident^ current-module aliases)
- (-> Text Aliases (l;Lexer [Ident Nat]))
- ($_ p;either
+ (-> Text Aliases (l.Lexer [Ident Nat]))
+ ($_ p.either
## When an identifier starts with 2 marks, its module is
## taken to be the current-module being compiled at the moment.
## This can be useful when mentioning identifiers and tags
## inside quoted/templated code in macros.
- (do p;Monad<Parser>
- [_ (l;this current-module-mark)
+ (do p.Monad<Parser>
+ [_ (l.this current-module-mark)
def-name ident-part^]
(wrap [[current-module def-name]
- (n/+ +2 (text;size def-name))]))
+ (n/+ +2 (text.size def-name))]))
## If the identifier is prefixed by the mark, but no module
## part, the module is assumed to be "lux" (otherwise known as
## the 'prelude').
## This makes it easy to refer to definitions in that module,
## since it is the most fundamental module in the entire
## standard library.
- (do p;Monad<Parser>
- [_ (l;this identifier-separator)
+ (do p.Monad<Parser>
+ [_ (l.this identifier-separator)
def-name ident-part^]
(wrap [["lux" def-name]
- (n/inc (text;size def-name))]))
+ (n/inc (text.size def-name))]))
## Not all identifiers must be specified with a module part.
## If that part is not provided, the identifier will be created
## with the empty "" text as the module.
@@ -556,19 +556,19 @@
## Function arguments and local-variables may not be referred-to
## using identifiers with module parts, so being able to specify
## identifiers with empty modules helps with those use-cases.
- (do p;Monad<Parser>
+ (do p.Monad<Parser>
[first-part ident-part^]
- (p;either (do @
- [_ (l;this identifier-separator)
+ (p.either (do @
+ [_ (l.this identifier-separator)
second-part ident-part^]
- (wrap [[(|> aliases (dict;get first-part) (maybe;default first-part))
+ (wrap [[(|> aliases (dict.get first-part) (maybe.default first-part))
second-part]
($_ n/+
- (text;size first-part)
+ (text.size first-part)
+1
- (text;size second-part))]))
+ (text.size second-part))]))
(wrap [["" first-part]
- (text;size first-part)])))))
+ (text.size first-part)])))))
## The only (syntactic) difference between a symbol and a tag (both
## being identifiers), is that tags must be prefixed with a hash-sign
@@ -579,26 +579,26 @@
## construction and de-structuring (during pattern-matching).
(do-template [<name> <tag> <lexer> <extra>]
[(def: #export (<name> current-module aliases where)
- (-> Text Aliases Cursor (l;Lexer [Cursor Code]))
- (do p;Monad<Parser>
+ (-> Text Aliases Cursor (l.Lexer [Cursor Code]))
+ (do p.Monad<Parser>
[[value length] <lexer>]
- (wrap [(update@ #;column (|>> ($_ n/+ <extra> length)) where)
+ (wrap [(update@ #.column (|>> ($_ n/+ <extra> length)) where)
[where (<tag> value)]])))]
- [symbol #;Symbol (ident^ current-module aliases) +0]
- [tag #;Tag (p;after (l;this "#") (ident^ current-module aliases)) +1]
+ [symbol #.Symbol (ident^ current-module aliases) +0]
+ [tag #.Tag (p.after (l.this "#") (ident^ current-module aliases)) +1]
)
(exception: #export End-Of-File)
(exception: #export Unrecognized-Input)
(def: (ast current-module aliases)
- (-> Text Aliases Cursor (l;Lexer [Cursor Code]))
- (: (-> Cursor (l;Lexer [Cursor Code]))
+ (-> Text Aliases Cursor (l.Lexer [Cursor Code]))
+ (: (-> Cursor (l.Lexer [Cursor Code]))
(function ast' [where]
- (do p;Monad<Parser>
+ (do p.Monad<Parser>
[where (left-padding^ where)]
- ($_ p;either
+ ($_ p.either
(form where ast')
(tuple where ast')
(record where ast')
@@ -611,17 +611,17 @@
(tag current-module aliases where)
(text where)
(do @
- [end? l;end?]
+ [end? l.end?]
(if end?
- (p;fail (End-Of-File current-module))
- (p;fail (Unrecognized-Input current-module))))
+ (p.fail (End-Of-File current-module))
+ (p.fail (Unrecognized-Input current-module))))
)))))
(def: #export (read current-module aliases [where offset source])
- (-> Text Aliases Source (e;Error [Source Code]))
- (case (p;run [offset source] (ast current-module aliases where))
- (#e;Error error)
- (#e;Error error)
+ (-> Text Aliases Source (e.Error [Source Code]))
+ (case (p.run [offset source] (ast current-module aliases where))
+ (#e.Error error)
+ (#e.Error error)
- (#e;Success [[offset' remaining] [where' output]])
- (#e;Success [[where' offset' remaining] output])))
+ (#e.Success [[offset' remaining] [where' output]])
+ (#e.Success [[where' offset' remaining] output])))