diff options
author | Eduardo Julian | 2019-04-19 01:13:00 -0400 |
---|---|---|
committer | Eduardo Julian | 2019-04-19 01:13:00 -0400 |
commit | 692f9751f36fbfc4a5f1148c7b1fadc03495fa6b (patch) | |
tree | 66f543bc153f50ab63b0aa78e5cc9a110b7107fe /stdlib/source/lux/control/parser/text.lux | |
parent | 7ac0905fd80dce045d6608c4a3c449c466ae43ab (diff) |
Moved the text lexers under "lux/control/parser/".
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/control/parser/text.lux (renamed from stdlib/source/lux/data/text/lexer.lux) | 145 |
1 files changed, 73 insertions, 72 deletions
diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/control/parser/text.lux index 958011b1c..22f49a572 100644 --- a/stdlib/source/lux/data/text/lexer.lux +++ b/stdlib/source/lux/control/parser/text.lux @@ -3,26 +3,26 @@ [abstract [monad (#+ Monad do)]] [control - ["p" parser] - ["ex" exception (#+ exception:)]] + ["." exception (#+ exception:)]] [data ["." product] ["." maybe] ["." error (#+ Error)] + ["/" text ("#@." monoid)] [number ["." nat ("#@." decimal)]] [collection ["." list ("#@." fold)]]] [macro ["." code]]] - ["." // ("#@." monoid)]) + ["." //]) (type: #export Offset Nat) (def: start-offset Offset 0) (type: #export Lexer - (p.Parser [Offset Text])) + (//.Parser [Offset Text])) (type: #export Slice {#basis Offset @@ -32,12 +32,13 @@ (def: (remaining offset tape) (-> Offset Text Text) - (|> tape (//.split offset) maybe.assume product.right)) + (|> tape (/.split offset) maybe.assume product.right)) (exception: #export (unconsumed-input {offset Offset} {tape Text}) - (ex.report ["Offset" (nat@encode offset)] - ["Input size" (nat@encode (//.size tape))] - ["Remaining input" (remaining offset tape)])) + (exception.report + ["Offset" (nat@encode offset)] + ["Input size" (nat@encode (/.size tape))] + ["Remaining input" (remaining offset tape)])) (def: #export (run input lexer) (All [a] (-> Text (Lexer a) (Error a))) @@ -46,9 +47,9 @@ (#error.Failure msg) (#error.Success [[end-offset _] output]) - (if (n/= end-offset (//.size input)) + (if (n/= end-offset (/.size input)) (#error.Success output) - (ex.throw unconsumed-input [end-offset input])))) + (exception.throw unconsumed-input [end-offset input])))) (def: #export offset (Lexer Offset) @@ -57,7 +58,7 @@ (def: (with-slices lexer) (-> (Lexer (List Slice)) (Lexer Slice)) - (do p.monad + (do //.monad [offset ..offset slices lexer] (wrap (list@fold (function (_ [slice::basis slice::distance] @@ -71,9 +72,9 @@ {#.doc "Just returns the next character without applying any logic."} (Lexer Text) (function (_ [offset tape]) - (case (//.nth offset tape) + (case (/.nth offset tape) (#.Some output) - (#error.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)]) + (#error.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)]) _ (#error.Failure cannot-lex-error)))) @@ -106,23 +107,23 @@ {#.doc "Lex a text if it matches the given sample."} (-> Text (Lexer Any)) (function (_ [offset tape]) - (case (//.index-of' reference offset tape) + (case (/.index-of' reference offset tape) (#.Some where) (if (n/= offset where) - (#error.Success [[("lux i64 +" (//.size reference) offset) tape] + (#error.Success [[("lux i64 +" (/.size reference) offset) tape] []]) - (#error.Failure ($_ //@compose "Could not match: " (//.encode reference) " @ " (maybe.assume (//.clip' offset tape))))) + (#error.Failure ($_ /@compose "Could not match: " (/.encode reference) " @ " (maybe.assume (/.clip' offset tape))))) _ - (#error.Failure ($_ //@compose "Could not match: " (//.encode reference)))))) + (#error.Failure ($_ /@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 (//.index-of' reference offset tape) + (case (/.index-of' reference offset tape) (^multi (#.Some where) (n/= offset where)) - (#error.Success [[("lux i64 +" (//.size reference) offset) tape] + (#error.Success [[("lux i64 +" (/.size reference) offset) tape] #1]) _ @@ -132,23 +133,23 @@ {#.doc "Ensure the lexer's input is empty."} (Lexer Any) (function (_ (^@ input [offset tape])) - (if (n/= offset (//.size tape)) + (if (n/= offset (/.size tape)) (#error.Success [input []]) - (ex.throw unconsumed-input [offset tape])))) + (exception.throw unconsumed-input [offset tape])))) (def: #export end? {#.doc "Ask if the lexer's input is empty."} (Lexer Bit) (function (_ (^@ input [offset tape])) - (#error.Success [input (n/= offset (//.size tape))]))) + (#error.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 (//.nth offset tape) + (case (/.nth offset tape) (#.Some output) - (#error.Success [input (//.from-code output)]) + (#error.Success [input (/.from-code output)]) _ (#error.Failure cannot-lex-error)))) @@ -162,17 +163,17 @@ (def: #export (range bottom top) {#.doc "Only lex characters within a range."} (-> Nat Nat (Lexer Text)) - (do p.monad + (do //.monad [char any - #let [char' (maybe.assume (//.nth 0 char))] - _ (p.assert ($_ //@compose "Character is not within range: " (//.from-code bottom) "-" (//.from-code top)) - (.and (n/>= bottom char') - (n/<= top char')))] + #let [char' (maybe.assume (/.nth 0 char))] + _ (//.assert ($_ /@compose "Character is not within range: " (/.from-code bottom) "-" (/.from-code top)) + (.and (n/>= bottom char') + (n/<= top char')))] (wrap char))) (template [<name> <bottom> <top> <desc>] [(def: #export <name> - {#.doc (code.text ($_ //@compose "Only lex " <desc> " characters."))} + {#.doc (code.text ($_ /@compose "Only lex " <desc> " characters."))} (Lexer Text) (range (char <bottom>) (char <top>)))] @@ -185,32 +186,32 @@ (def: #export alpha {#.doc "Only lex alphabetic characters."} (Lexer Text) - (p.either lower upper)) + (//.either lower upper)) (def: #export alpha-num {#.doc "Only lex alphanumeric characters."} (Lexer Text) - (p.either alpha decimal)) + (//.either alpha decimal)) (def: #export hexadecimal {#.doc "Only lex hexadecimal digits."} (Lexer Text) - ($_ p.either + ($_ //.either decimal (range (char "a") (char "f")) (range (char "A") (char "F")))) (template [<name> <description-modifier> <modifier>] [(def: #export (<name> options) - {#.doc (code.text ($_ //@compose "Only lex characters that are" <description-modifier> " part of a piece of text."))} + {#.doc (code.text ($_ /@compose "Only lex characters that are" <description-modifier> " part of a piece of text."))} (-> Text (Lexer Text)) (function (_ [offset tape]) - (case (//.nth offset tape) + (case (/.nth offset tape) (#.Some output) - (let [output (//.from-code output)] - (if (<modifier> (//.contains? output options)) + (let [output (/.from-code output)] + (if (<modifier> (/.contains? output options)) (#error.Success [[("lux i64 +" 1 offset) tape] output]) - (#error.Failure ($_ //@compose "Character (" output + (#error.Failure ($_ /@compose "Character (" output ") is should " <description-modifier> "be one of: " options)))) @@ -223,17 +224,17 @@ (template [<name> <description-modifier> <modifier>] [(def: #export (<name> options) - {#.doc (code.text ($_ //@compose "Only lex characters that are" <description-modifier> " part of a piece of text."))} + {#.doc (code.text ($_ /@compose "Only lex characters that are" <description-modifier> " part of a piece of text."))} (-> Text (Lexer Slice)) (function (_ [offset tape]) - (case (//.nth offset tape) + (case (/.nth offset tape) (#.Some output) - (let [output (//.from-code output)] - (if (<modifier> (//.contains? output options)) + (let [output (/.from-code output)] + (if (<modifier> (/.contains? output options)) (#error.Success [[("lux i64 +" 1 offset) tape] {#basis offset #distance 1}]) - (#error.Failure ($_ //@compose "Character (" output + (#error.Failure ($_ /@compose "Character (" output ") is should " <description-modifier> "be one of: " options)))) @@ -248,11 +249,11 @@ {#.doc "Only lex characters that satisfy a predicate."} (-> (-> Nat Bit) (Lexer Text)) (function (_ [offset tape]) - (case (//.nth offset tape) + (case (/.nth offset tape) (#.Some output) (if (p output) - (#error.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)]) - (#error.Failure ($_ //@compose "Character does not satisfy predicate: " (//.from-code output)))) + (#error.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)]) + (#error.Failure ($_ /@compose "Character does not satisfy predicate: " (/.from-code output)))) _ (#error.Failure cannot-lex-error)))) @@ -260,79 +261,79 @@ (def: #export space {#.doc "Only lex white-space."} (Lexer Text) - (satisfies //.space?)) + (satisfies /.space?)) (def: #export (and left right) (-> (Lexer Text) (Lexer Text) (Lexer Text)) - (do p.monad + (do //.monad [=left left =right right] - (wrap ($_ //@compose =left =right)))) + (wrap ($_ /@compose =left =right)))) (def: #export (and! left right) (-> (Lexer Slice) (Lexer Slice) (Lexer Slice)) - (do p.monad + (do //.monad [[left::basis left::distance] left [right::basis right::distance] right] (wrap [left::basis ("lux i64 +" left::distance right::distance)]))) (template [<name> <base> <doc-modifier>] [(def: #export (<name> lexer) - {#.doc (code.text ($_ //@compose "Lex " <doc-modifier> " characters as a single continuous text."))} + {#.doc (code.text ($_ /@compose "Lex " <doc-modifier> " characters as a single continuous text."))} (-> (Lexer Text) (Lexer Text)) - (|> lexer <base> (:: p.monad map //.concat)))] + (|> lexer <base> (:: //.monad map /.concat)))] - [some p.some "some"] - [many p.many "many"] + [some //.some "some"] + [many //.many "many"] ) (template [<name> <base> <doc-modifier>] [(def: #export (<name> lexer) - {#.doc (code.text ($_ //@compose "Lex " <doc-modifier> " characters as a single continuous text."))} + {#.doc (code.text ($_ /@compose "Lex " <doc-modifier> " characters as a single continuous text."))} (-> (Lexer Slice) (Lexer Slice)) (with-slices (<base> lexer)))] - [some! p.some "some"] - [many! p.many "many"] + [some! //.some "some"] + [many! //.many "many"] ) (template [<name> <base> <doc-modifier>] [(def: #export (<name> amount lexer) - {#.doc (code.text ($_ //@compose "Lex " <doc-modifier> " N characters."))} + {#.doc (code.text ($_ /@compose "Lex " <doc-modifier> " N characters."))} (-> Nat (Lexer Text) (Lexer Text)) - (|> lexer (<base> amount) (:: p.monad map //.concat)))] + (|> lexer (<base> amount) (:: //.monad map /.concat)))] - [exactly p.exactly "exactly"] - [at-most p.at-most "at most"] - [at-least p.at-least "at least"] + [exactly //.exactly "exactly"] + [at-most //.at-most "at most"] + [at-least //.at-least "at least"] ) (template [<name> <base> <doc-modifier>] [(def: #export (<name> amount lexer) - {#.doc (code.text ($_ //@compose "Lex " <doc-modifier> " N characters."))} + {#.doc (code.text ($_ /@compose "Lex " <doc-modifier> " N characters."))} (-> Nat (Lexer Slice) (Lexer Slice)) (with-slices (<base> amount lexer)))] - [exactly! p.exactly "exactly"] - [at-most! p.at-most "at most"] - [at-least! p.at-least "at least"] + [exactly! //.exactly "exactly"] + [at-most! //.at-most "at most"] + [at-least! //.at-least "at least"] ) (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 map //.concat))) + (|> lexer (//.between from to) (:: //.monad map /.concat))) (def: #export (between! from to lexer) {#.doc "Lex between N and M characters."} (-> Nat Nat (Lexer Slice) (Lexer Slice)) - (with-slices (p.between from to lexer))) + (with-slices (//.between from to lexer))) (def: #export (enclosed [start end] lexer) (All [a] (-> [Text Text] (Lexer a) (Lexer a))) (|> lexer - (p.before (this end)) - (p.after (this start)))) + (//.before (this end)) + (//.after (this start)))) (def: #export (local local-input lexer) {#.doc "Run a lexer with the given input, instead of the real one."} @@ -347,10 +348,10 @@ (def: #export (slice lexer) (-> (Lexer Slice) (Lexer Text)) - (do p.monad + (do //.monad [[basis distance] lexer] (function (_ (^@ input [offset tape])) - (case (//.clip basis ("lux i64 +" basis distance) tape) + (case (/.clip basis ("lux i64 +" basis distance) tape) (#.Some output) (#error.Success [input output]) |