diff options
author | Eduardo Julian | 2020-12-25 09:22:38 -0400 |
---|---|---|
committer | Eduardo Julian | 2020-12-25 09:22:38 -0400 |
commit | 4ca397765805eda5ddee393901ed3a02001a960a (patch) | |
tree | 2ab184a1a4e244f3a69e86c8a7bb3ad49c22b4a3 /stdlib/source/lux/control/parser/text.lux | |
parent | d29e091e98dabb8dfcf816899ada480ecbf7e357 (diff) |
Replaced kebab-case with snake_case for naming convention.
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/control/parser/text.lux | 128 |
1 files changed, 64 insertions, 64 deletions
diff --git a/stdlib/source/lux/control/parser/text.lux b/stdlib/source/lux/control/parser/text.lux index ebcf3c53a..919de78c4 100644 --- a/stdlib/source/lux/control/parser/text.lux +++ b/stdlib/source/lux/control/parser/text.lux @@ -19,7 +19,7 @@ (type: #export Offset Nat) -(def: start-offset Offset 0) +(def: start_offset Offset 0) (type: #export Parser (//.Parser [Offset Text])) @@ -32,37 +32,37 @@ (-> Offset Text Text) (|> tape (/.split offset) maybe.assume product.right)) -(exception: #export (unconsumed-input {offset Offset} {tape Text}) +(exception: #export (unconsumed_input {offset Offset} {tape Text}) (exception.report ["Offset" (n\encode offset)] ["Input size" (n\encode (/.size tape))] ["Remaining input" (remaining offset tape)])) -(exception: #export (expected-to-fail {offset Offset} {tape Text}) +(exception: #export (expected_to_fail {offset Offset} {tape Text}) (exception.report ["Offset" (n\encode offset)] ["Input" (remaining offset tape)])) -(exception: #export cannot-parse) -(exception: #export cannot-slice) +(exception: #export cannot_parse) +(exception: #export cannot_slice) (def: #export (run parser input) (All [a] (-> (Parser a) Text (Try a))) - (case (parser [start-offset input]) + (case (parser [start_offset input]) (#try.Failure msg) (#try.Failure msg) - (#try.Success [[end-offset _] output]) - (if (n.= end-offset (/.size input)) + (#try.Success [[end_offset _] output]) + (if (n.= end_offset (/.size input)) (#try.Success output) - (exception.throw ..unconsumed-input [end-offset input])))) + (exception.throw ..unconsumed_input [end_offset input])))) (def: #export offset (Parser Offset) (function (_ (^@ input [offset tape])) (#try.Success [input offset]))) -(def: (with-slices parser) +(def: (with_slices parser) (-> (Parser (List Slice)) (Parser Slice)) (do //.monad [offset ..offset @@ -80,10 +80,10 @@ (function (_ [offset tape]) (case (/.nth offset tape) (#.Some output) - (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)]) + (#try.Success [[("lux i64 +" 1 offset) tape] (/.from_code output)]) _ - (exception.throw ..cannot-parse [])))) + (exception.throw ..cannot_parse [])))) (def: #export any! {#.doc "Just returns the next character without applying any logic."} @@ -96,7 +96,7 @@ #distance 1}]) _ - (exception.throw ..cannot-slice [])))) + (exception.throw ..cannot_slice [])))) (template [<name> <type> <any>] [(def: #export (<name> p) @@ -108,13 +108,13 @@ (<any> input) _ - (exception.throw ..expected-to-fail input))))] + (exception.throw ..expected_to_fail input))))] [not Text ..any] [not! Slice ..any!] ) -(exception: #export (cannot-match {reference Text}) +(exception: #export (cannot_match {reference Text}) (exception.report ["Reference" (/.encode reference)])) @@ -122,15 +122,15 @@ {#.doc "Lex a text if it matches the given sample."} (-> Text (Parser Any)) (function (_ [offset tape]) - (case (/.index-of' reference offset tape) + (case (/.index_of' reference offset tape) (#.Some where) (if (n.= offset where) (#try.Success [[("lux i64 +" (/.size reference) offset) tape] []]) - (exception.throw ..cannot-match [reference])) + (exception.throw ..cannot_match [reference])) _ - (exception.throw ..cannot-match [reference])))) + (exception.throw ..cannot_match [reference])))) (def: #export end! {#.doc "Ensure the parser's input is empty."} @@ -138,7 +138,7 @@ (function (_ (^@ input [offset tape])) (if (n.= offset (/.size tape)) (#try.Success [input []]) - (exception.throw ..unconsumed-input input)))) + (exception.throw ..unconsumed_input input)))) (def: #export peek {#.doc "Lex the next character (without consuming it from the input)."} @@ -146,12 +146,12 @@ (function (_ (^@ input [offset tape])) (case (/.nth offset tape) (#.Some output) - (#try.Success [input (/.from-code output)]) + (#try.Success [input (/.from_code output)]) _ - (exception.throw ..cannot-parse [])))) + (exception.throw ..cannot_parse [])))) -(def: #export get-input +(def: #export get_input {#.doc "Get all of the remaining input (without consuming it)."} (Parser Text) (function (_ (^@ input [offset tape])) @@ -163,7 +163,7 @@ (do //.monad [char any #let [char' (maybe.assume (/.nth 0 char))] - _ (//.assert ($_ /\compose "Character is not within range: " (/.from-code bottom) "-" (/.from-code top)) + _ (//.assert ($_ /\compose "Character is not within range: " (/.from_code bottom) "-" (/.from_code top)) (.and (n.>= bottom char') (n.<= top char')))] (wrap char))) @@ -185,7 +185,7 @@ (Parser Text) (//.either lower upper)) -(def: #export alpha-num +(def: #export alpha_num {#.doc "Only lex alphanumeric characters."} (Parser Text) (//.either alpha decimal)) @@ -202,39 +202,39 @@ [(exception: #export (<name> {options Text} {character Char}) (exception.report ["Options" (/.encode options)] - ["Character" (/.encode (/.from-code character))]))] + ["Character" (/.encode (/.from_code character))]))] - [character-should-be] - [character-should-not-be] + [character_should_be] + [character_should_not_be] ) -(template [<name> <modifier> <exception> <description-modifier>] +(template [<name> <modifier> <exception> <description_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 (Parser Text)) (function (_ [offset tape]) (case (/.nth offset tape) (#.Some output) - (let [output' (/.from-code output)] + (let [output' (/.from_code output)] (if (<modifier> (/.contains? output' options)) (#try.Success [[("lux i64 +" 1 offset) tape] output']) (exception.throw <exception> [options output]))) _ - (exception.throw ..cannot-parse []))))] + (exception.throw ..cannot_parse []))))] - [one-of |> ..character-should-be ""] - [none-of .not ..character-should-not-be " not"] + [one_of |> ..character_should_be ""] + [none_of .not ..character_should_not_be " not"] ) -(template [<name> <modifier> <exception> <description-modifier>] +(template [<name> <modifier> <exception> <description_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 (Parser Slice)) (function (_ [offset tape]) (case (/.nth offset tape) (#.Some output) - (let [output' (/.from-code output)] + (let [output' (/.from_code output)] (if (<modifier> (/.contains? output' options)) (#try.Success [[("lux i64 +" 1 offset) tape] {#basis offset @@ -242,15 +242,15 @@ (exception.throw <exception> [options output]))) _ - (exception.throw ..cannot-slice []))))] + (exception.throw ..cannot_slice []))))] - [one-of! |> ..character-should-be ""] - [none-of! .not ..character-should-not-be " not"] + [one_of! |> ..character_should_be ""] + [none_of! .not ..character_should_not_be " not"] ) -(exception: #export (character-does-not-satisfy-predicate {character Char}) +(exception: #export (character_does_not_satisfy_predicate {character Char}) (exception.report - ["Character" (/.encode (/.from-code character))])) + ["Character" (/.encode (/.from_code character))])) (def: #export (satisfies p) {#.doc "Only lex characters that satisfy a predicate."} @@ -259,11 +259,11 @@ (case (/.nth offset tape) (#.Some output) (if (p output) - (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)]) - (exception.throw ..character-does-not-satisfy-predicate [output])) + (#try.Success [[("lux i64 +" 1 offset) tape] (/.from_code output)]) + (exception.throw ..character_does_not_satisfy_predicate [output])) _ - (exception.throw ..cannot-parse [])))) + (exception.throw ..cannot_parse [])))) (def: #export space {#.doc "Only lex white-space."} @@ -284,9 +284,9 @@ [right::basis right::distance] right] (wrap [left::basis ("lux i64 +" left::distance right::distance)]))) -(template [<name> <base> <doc-modifier>] +(template [<name> <base> <doc_modifier>] [(def: #export (<name> parser) - {#.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."))} (-> (Parser Text) (Parser Text)) (|> parser <base> (\ //.monad map /.concat)))] @@ -294,36 +294,36 @@ [many //.many "many"] ) -(template [<name> <base> <doc-modifier>] +(template [<name> <base> <doc_modifier>] [(def: #export (<name> parser) - {#.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."))} (-> (Parser Slice) (Parser Slice)) - (with-slices (<base> parser)))] + (with_slices (<base> parser)))] [some! //.some "some"] [many! //.many "many"] ) -(template [<name> <base> <doc-modifier>] +(template [<name> <base> <doc_modifier>] [(def: #export (<name> amount parser) - {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " N characters."))} + {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " N characters."))} (-> Nat (Parser Text) (Parser Text)) (|> parser (<base> amount) (\ //.monad map /.concat)))] [exactly //.exactly "exactly"] - [at-most //.at-most "at most"] - [at-least //.at-least "at least"] + [at_most //.at_most "at most"] + [at_least //.at_least "at least"] ) -(template [<name> <base> <doc-modifier>] +(template [<name> <base> <doc_modifier>] [(def: #export (<name> amount parser) - {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " N characters."))} + {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " N characters."))} (-> Nat (Parser Slice) (Parser Slice)) - (with-slices (<base> amount parser)))] + (with_slices (<base> amount parser)))] [exactly! //.exactly "exactly"] - [at-most! //.at-most "at most"] - [at-least! //.at-least "at least"] + [at_most! //.at_most "at most"] + [at_least! //.at_least "at least"] ) (def: #export (between from to parser) @@ -334,7 +334,7 @@ (def: #export (between! from to parser) {#.doc "Lex between N and M characters."} (-> Nat Nat (Parser Slice) (Parser Slice)) - (with-slices (//.between from to parser))) + (with_slices (//.between from to parser))) (def: #export (enclosed [start end] parser) (All [a] (-> [Text Text] (Parser a) (Parser a))) @@ -342,16 +342,16 @@ (//.before (this end)) (//.after (this start)))) -(def: #export (local local-input parser) +(def: #export (local local_input parser) {#.doc "Run a parser with the given input, instead of the real one."} (All [a] (-> Text (Parser a) (Parser a))) - (function (_ real-input) - (case (..run parser local-input) + (function (_ real_input) + (case (..run parser local_input) (#try.Failure error) (#try.Failure error) (#try.Success value) - (#try.Success [real-input value])))) + (#try.Success [real_input value])))) (def: #export (slice parser) (-> (Parser Slice) (Parser Text)) @@ -363,7 +363,7 @@ (#try.Success [input output]) #.None - (exception.throw ..cannot-slice []))))) + (exception.throw ..cannot_slice []))))) (def: #export (embed structured text) (All [s a] |