ebnf: fix syntax.

locals-and-roots
Doug Coleman 2016-06-06 16:26:02 -07:00
parent 552d323897
commit a33f643ec9
29 changed files with 165 additions and 165 deletions

View File

@ -51,7 +51,7 @@ exp = exp:a spaces "+" fac:b => [[ a b <add> ]]
| fac
main = exp:e spaces !(.) => [[ e ]]
;EBNF
EBNF;
GENERIC: eval-ast ( ast -- result ) ;

View File

@ -5,13 +5,13 @@ io.files io.encodings.ascii kernel ;
EBNF: test-Character
test = <foreign parse-smalltalk Character>
;EBNF
EBNF;
{ char: a } [ "a" test-Character ] unit-test
EBNF: test-Comment
test = <foreign parse-smalltalk Comment>
;EBNF
EBNF;
{ T{ ast-comment f "Hello, this is a comment." } }
[ "\"Hello, this is a comment.\"" test-Comment ]
@ -23,13 +23,13 @@ unit-test
EBNF: test-Identifier
test = <foreign parse-smalltalk Identifier>
;EBNF
EBNF;
{ "OrderedCollection" } [ "OrderedCollection" test-Identifier ] unit-test
EBNF: test-Literal
test = <foreign parse-smalltalk Literal>
;EBNF
EBNF;
{ nil } [ "nil" test-Literal ] unit-test
{ 123 } [ "123" test-Literal ] unit-test
@ -78,20 +78,20 @@ test = <foreign parse-smalltalk Literal>
EBNF: test-FormalBlockArgumentDeclarationList
test = <foreign parse-smalltalk FormalBlockArgumentDeclarationList>
;EBNF
EBNF;
{ V{ "x" "y" "elt" } } [ ":x :y :elt" test-FormalBlockArgumentDeclarationList ] unit-test
EBNF: test-Operand
test = <foreign parse-smalltalk Operand>
;EBNF
EBNF;
{ { 123 15.6 { t f } } } [ "#(123 15.6 (true false))" test-Operand ] unit-test
{ T{ ast-name f "x" } } [ "x" test-Operand ] unit-test
EBNF: test-Expression
test = <foreign parse-smalltalk Expression>
;EBNF
EBNF;
{ self } [ "self" test-Expression ] unit-test
{ { 123 15.6 { t f } } } [ "#(123 15.6 (true false))" test-Expression ] unit-test
@ -229,7 +229,7 @@ test = <foreign parse-smalltalk Expression>
EBNF: test-FinalStatement
test = <foreign parse-smalltalk FinalStatement>
;EBNF
EBNF;
{ T{ ast-name f "value" } } [ "value" test-FinalStatement ] unit-test
{ T{ ast-return f T{ ast-name f "value" } } } [ "^value" test-FinalStatement ] unit-test
@ -237,7 +237,7 @@ test = <foreign parse-smalltalk FinalStatement>
EBNF: test-LocalVariableDeclarationList
test = <foreign parse-smalltalk LocalVariableDeclarationList>
;EBNF
EBNF;
{ T{ ast-local-variables f { "i" "j" } } } [ " | i j |" test-LocalVariableDeclarationList ] unit-test

View File

@ -225,4 +225,4 @@ End = !(.)
Program = TopLevelForm End
;EBNF
EBNF;

View File

@ -35,7 +35,7 @@ UnknownError = .* => [[ >string <sql-unknown-error> ]]
PostgresqlSqlError = (TableError | DatabaseError | FunctionError | SyntaxError | UnknownError)
;EBNF
EBNF;
TUPLE: parse-postgresql-location column line text ;
@ -46,7 +46,7 @@ EBNF: parse-postgresql-line-error
Line = "LINE " [0-9]+:line ": " .+:sql
=> [[ f line >string string>number sql >string <parse-postgresql-location> ]]
;EBNF
EBNF;
:: set-caret-position ( error caret-line -- error )
caret-line length

View File

@ -25,4 +25,4 @@ SqliteError =
=> [[ table >string <sql-table-missing> ]]
| .*:error
=> [[ error >string <unparsed-sqlite-error> ]]
;EBNF
EBNF;

View File

@ -10,6 +10,6 @@ Times = .* => [[ "foo" ]]
Regexp = Times:t => [[ t <times> ]]
;EBNF
EBNF;
[ "foo" ] [ "a" parse-regexp ] unit-test

View File

@ -18,7 +18,7 @@ M: pipeline-expr blah ;
EBNF: expr
pipeline = "hello" => [[ ast>pipeline-expr ]]
;EBNF
EBNF;
use: tools.test

View File

@ -761,13 +761,13 @@ SYMBOLS: $1 $2 $3 $4 ;
! is the getter word for that register with stack effect
! ( cpu -- value ). The second item is the setter word with
! stack effect ( value cpu -- ).
<EBNF
EBNF<
main=("A" | "B" | "C" | "D" | "E" | "H" | "L") => [[ register-lookup ]]
EBNF> ;
: all-flags ( -- parser )
! A parser for 16-bit flags.
<EBNF
EBNF<
main=("NZ" | "NC" | "PO" | "PE" | "Z" | "C" | "P" | "M") => [[ flag-lookup ]]
EBNF> ;
@ -777,7 +777,7 @@ SYMBOLS: $1 $2 $3 $4 ;
! is the getter word for that register with stack effect
! ( cpu -- value ). The second item is the setter word with
! stack effect ( value cpu -- ).
<EBNF
EBNF<
main=("AF" | "BC" | "DE" | "HL" | "SP") => [[ register-lookup ]]
EBNF> ;

View File

@ -3,8 +3,8 @@
USING: help.syntax help.markup peg peg.search words ;
in: peg.ebnf
HELP: <EBNF
{ $syntax "<EBNF ...ebnf... EBNF>" }
HELP: EBNF<
{ $syntax "EBNF<...ebnf... EBNF>" }
{ $values { "...ebnf..." "EBNF DSL text" } }
{ $description
"Creates a " { $vocab-link "peg" }
@ -15,13 +15,13 @@ HELP: <EBNF
{ $examples
{ $example
"USING: kernel prettyprint peg.ebnf peg.search ;"
"\"abcdab\" <EBNF rule=\"a\" \"b\" => [[ drop \"foo\" ]] EBNF> replace ."
"\"abcdab\" EBNF< rule=\"a\" \"b\" => [[ drop \"foo\" ]] EBNF> replace ."
"\"foocdfoo\""
}
} ;
HELP: [EBNF
{ $syntax "[EBNF ...ebnf... EBNF]" }
HELP: EBNF[
{ $syntax "EBNF[ ...ebnf... EBNF]" }
{ $values { "...ebnf..." "EBNF DSL text" } }
{ $description
"Creates and calls a quotation that parses a string using the syntax "
@ -33,13 +33,13 @@ HELP: [EBNF
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"ab\" [EBNF rule=\"a\" \"b\" EBNF] ."
"\"ab\" EBNF[ rule=\"a\" \"b\" EBNF] ."
"V{ \"a\" \"b\" }"
}
} ;
HELP: EBNF:
{ $syntax "EBNF: word ...ebnf... ;EBNF" }
{ $syntax "EBNF: word ...ebnf... EBNF;" }
{ $values { "word" word } { "...ebnf..." "EBNF DSL text" } }
{ $description
"Defines a word that when called will parse a string using the syntax "
@ -52,7 +52,7 @@ HELP: EBNF:
{ $example
"USING: prettyprint peg.ebnf ;"
"in: scratchpad"
"EBNF: foo rule=\"a\" \"b\" ;EBNF"
"EBNF: foo rule=\"a\" \"b\" EBNF;"
"\"ab\" foo ."
"V{ \"a\" \"b\" }"
}
@ -67,22 +67,22 @@ ARTICLE: "peg.ebnf.strings" "EBNF Rule: Strings"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"helloworld\" [EBNF rule=\"hello\" \"world\" EBNF] ."
"\"helloworld\" EBNF[ rule=\"hello\" \"world\" EBNF] ."
"V{ \"hello\" \"world\" }"
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"AΣ𝄞\" [EBNF rule='\\x41' '\\u{greek-capital-letter-sigma}' '\\u01D11E' EBNF] ."
"\"AΣ𝄞\" EBNF[ rule='\\x41' '\\u{greek-capital-letter-sigma}' '\\u01D11E' EBNF] ."
"V{ \"A\" \"Σ\" \"𝄞\" }"
}
{ $example
"USING: io peg.ebnf ;"
"\"A double quote: \\\"\" [EBNF rule='A double quote: \"' EBNF] print"
"\"A double quote: \\\"\" EBNF[ rule='A double quote: \"' EBNF] print"
"A double quote: \""
}
{ $example
"USING: io peg.ebnf ;"
"\"' and \\\"\" [EBNF rule=\"' and \\\"\" EBNF] print"
"\"' and \\\"\" EBNF[ rule=\"' and \\\"\" EBNF] print"
"' and \""
}
} ;
@ -93,7 +93,7 @@ ARTICLE: "peg.ebnf.any" "EBNF Rule: Any"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"abc\" [EBNF rule=\"a\" . \"c\" EBNF] ."
"\"abc\" EBNF[ rule=\"a\" . \"c\" EBNF] ."
"V{ \"a\" 98 \"c\" }"
}
} ;
@ -106,7 +106,7 @@ ARTICLE: "peg.ebnf.sequence" "EBNF Rule: Sequence"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"abbba\" [EBNF rule=\"a\" (\"b\")* \"a\" EBNF] ."
"\"abbba\" EBNF[ rule=\"a\" (\"b\")* \"a\" EBNF] ."
"V{ \"a\" V{ \"b\" \"b\" \"b\" } \"a\" }"
}
}
@ -123,12 +123,12 @@ $nl
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"abcca\" [EBNF rule=\"a\" (\"b\" | \"c\")* \"a\" EBNF] ."
"\"abcca\" EBNF[ rule=\"a\" (\"b\" | \"c\")* \"a\" EBNF] ."
"V{ \"a\" V{ \"b\" \"c\" \"c\" } \"a\" }"
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"ab c\nd \" [EBNF rule={\"a\" \"b\" \"c\" \"d\"} EBNF] ."
"\"ab c\nd \" EBNF[ rule={\"a\" \"b\" \"c\" \"d\"} EBNF] ."
"V{ \"a\" \"b\" \"c\" \"d\" }"
}
}
@ -141,17 +141,17 @@ ARTICLE: "peg.ebnf.choice" "EBNF Rule: Choice"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"a\" [EBNF rule=\"a\" | \"b\" | \"c\" EBNF] ."
"\"a\" EBNF[ rule=\"a\" | \"b\" | \"c\" EBNF] ."
"\"a\""
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"b\" [EBNF rule=\"a\" | \"b\" | \"c\" EBNF] ."
"\"b\" EBNF[ rule=\"a\" | \"b\" | \"c\" EBNF] ."
"\"b\""
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"d\" [EBNF rule=\"a\" | \"b\" | \"c\" EBNF] ."
"\"d\" EBNF[ rule=\"a\" | \"b\" | \"c\" EBNF] ."
"Peg parsing error at character position 0.\nExpected 'a' or 'b' or 'c'\nGot 'd'"
}
}
@ -164,7 +164,7 @@ ARTICLE: "peg.ebnf.ignore" "EBNF Rule: Ignore"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"abc\" [EBNF rule=\"a\" \"b\"~ \"c\" EBNF] ."
"\"abc\" EBNF[ rule=\"a\" \"b\"~ \"c\" EBNF] ."
"V{ \"a\" \"c\" }"
}
}
@ -177,12 +177,12 @@ ARTICLE: "peg.ebnf.option" "EBNF Rule: Option"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"abc\" [EBNF rule=\"a\" \"b\"? \"c\" EBNF] ."
"\"abc\" EBNF[ rule=\"a\" \"b\"? \"c\" EBNF] ."
"V{ \"a\" \"b\" \"c\" }"
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"ac\" [EBNF rule=\"a\" \"b\"? \"c\" EBNF] ."
"\"ac\" EBNF[ rule=\"a\" \"b\"? \"c\" EBNF] ."
"V{ \"a\" f \"c\" }"
}
}
@ -198,7 +198,7 @@ ARTICLE: "peg.ebnf.character-class" "EBNF Rule: Character Class"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"123\" [EBNF rule=[0-9]+ EBNF] ."
"\"123\" EBNF[ rule=[0-9]+ EBNF] ."
"V{ 49 50 51 }"
}
}
@ -211,7 +211,7 @@ ARTICLE: "peg.ebnf.one-or-more" "EBNF Rule: One or more"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"aab\" [EBNF rule=\"a\"+ \"b\" EBNF] ."
"\"aab\" EBNF[ rule=\"a\"+ \"b\" EBNF] ."
"V{ V{ \"a\" \"a\" } \"b\" }"
}
}
@ -224,12 +224,12 @@ ARTICLE: "peg.ebnf.zero-or-more" "EBNF Rule: Zero or more"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"aab\" [EBNF rule=\"a\"* \"b\" EBNF] ."
"\"aab\" EBNF[ rule=\"a\"* \"b\" EBNF] ."
"V{ V{ \"a\" \"a\" } \"b\" }"
}
{ $example
"USING: prettyprint peg.ebnf ;"
"\"b\" [EBNF rule=\"a\"* \"b\" EBNF] ."
"\"b\" EBNF[ rule=\"a\"* \"b\" EBNF] ."
"V{ V{ } \"b\" }"
}
}
@ -245,7 +245,7 @@ ARTICLE: "peg.ebnf.and" "EBNF Rule: And"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"ab\" [EBNF rule=&(\"a\") \"a\" \"b\" EBNF] ."
"\"ab\" EBNF[ rule=&(\"a\") \"a\" \"b\" EBNF] ."
"V{ \"a\" \"b\" }"
}
}
@ -261,7 +261,7 @@ ARTICLE: "peg.ebnf.not" "EBNF Rule: Not"
{ $examples
{ $example
"USING: prettyprint peg.ebnf ;"
"\"<abcd>\" [EBNF rule=\"<\" (!(\">\") .)* \">\" EBNF] ."
"\"<abcd>\" EBNF[ rule=\"<\" (!(\">\") .)* \">\" EBNF] ."
"V{ \"<\" V{ 97 98 99 100 } \">\" }"
}
}
@ -282,12 +282,12 @@ ARTICLE: "peg.ebnf.action" "EBNF Action"
{ $examples
{ $example
"USING: prettyprint peg.ebnf strings ;"
"\"<abcd>\" [EBNF rule=\"<\" ((!(\">\") .)* => [[ >string ]]) \">\" EBNF] ."
"\"<abcd>\" EBNF[ rule=\"<\" ((!(\">\") .)* => [[ >string ]]) \">\" EBNF] ."
"V{ \"<\" \"abcd\" \">\" }"
}
{ $example
"USING: prettyprint peg.ebnf math.parser ;"
"\"123\" [EBNF rule=[0-9]+ => [[ string>number ]] EBNF] ."
"\"123\" EBNF[ rule=[0-9]+ => [[ string>number ]] EBNF] ."
"123"
}
}
@ -302,12 +302,12 @@ ARTICLE: "peg.ebnf.semantic-action" "EBNF Semantic Action"
{ $examples
{ $example
"USING: prettyprint peg.ebnf math math.parser ;"
"\"1\" [EBNF rule=[0-9] ?[ digit> odd? ]? EBNF] ."
"\"1\" EBNF[ rule=[0-9] ?[ digit> odd? ]? EBNF] ."
"49"
}
{ $example
"USING: prettyprint peg.ebnf math math.parser ;"
"\"2\" [EBNF rule=[0-9] ?[ digit> odd? ]? EBNF] ."
"\"2\" EBNF[ rule=[0-9] ?[ digit> odd? ]? EBNF] ."
"Peg parsing error at character position 0.\nExpected \nGot '2'"
}
}
@ -320,7 +320,7 @@ ARTICLE: "peg.ebnf.variable" "EBNF Variable"
{ $examples
{ $example
"USING: prettyprint peg.ebnf math.parser ;"
"\"1+2\" [EBNF rule=[0-9]:a \"+\" [0-9]:b => [[ a digit> b digit> + ]] EBNF] ."
"\"1+2\" EBNF[ rule=[0-9]:a \"+\" [0-9]:b => [[ a digit> b digit> + ]] EBNF] ."
"3"
}
}
@ -341,19 +341,19 @@ ARTICLE: "peg.ebnf.foreign-rules" "EBNF Foreign Rules"
"EBNF: parse-string"
"StringBody = (!('\"') .)*"
"String= '\"' StringBody:b '\"' => [[ b >string ]]"
";EBNF"
"EBNF;"
"EBNF: parse-two-strings"
"TwoStrings = <foreign parse-string String> <foreign parse-string String>"
";EBNF"
"EBNF;"
"EBNF: parse-two-strings"
"TwoString = <foreign parse-string> <foreign parse-string>"
";EBNF"
"EBNF;"
}
{ $code
": a-token ( -- parser ) \"a\" token ;"
"EBNF: parse-abc"
"abc = <foreign a-token> 'b' 'c'"
";EBNF"
"EBNF;"
}
}
;
@ -366,7 +366,7 @@ ARTICLE: "peg.ebnf.tokenizers" "EBNF Tokenizers"
{ $code
"EBNF: foo"
"rule = \"++\" \"--\""
";EBNF"
"EBNF;"
}
}
"This parser when run with the string \"++--\" or the array "
@ -379,7 +379,7 @@ ARTICLE: "peg.ebnf.tokenizers" "EBNF Tokenizers"
"space = (\" \" | \"\\r\" | \"\\t\" | \"\\n\")"
"spaces = space* => [[ drop ignore ]]"
"rule = spaces \"++\" spaces \"--\" spaces"
";EBNF"
"EBNF;"
}
}
"In a large grammar this gets tedious and makes the grammar hard to read. "
@ -393,7 +393,7 @@ ARTICLE: "peg.ebnf.tokenizers" "EBNF Tokenizers"
"spaces = space* => [[ drop ignore ]]"
"tokenizer = spaces ( \"++\" | \"--\" )"
"rule = \"++\" \"--\""
";EBNF"
"EBNF;"
}
}
"'tokenizer' is the name of a built in rule. Once defined it is called to "
@ -427,7 +427,7 @@ $nl
""
"token = spaces ( number | operator )"
"tokens = token*"
";EBNF"
"EBNF;"
""
"EBNF: foo"
"tokenizer = <foreign foo-tokenizer token>"
@ -436,7 +436,7 @@ $nl
"string = . ?[ ast-string? ]? => [[ value>> ]]"
""
"rule = string:a number:b \"+\" number:c => [[ a b c + 2array ]]"
";EBNF"
"EBNF;"
""
"\"123 456 +\" foo-tokenizer ."
"V{\n T{ ast-number { value 123 } }\n T{ ast-number { value 456 } }\n \"+\"\n}"
@ -489,9 +489,9 @@ ARTICLE: "peg.ebnf" "EBNF"
"EBNF syntax. It provides three parsing words described below. These words all "
"accept the same EBNF syntax. The difference is in how they are used. "
{ $subsections
postpone\ <EBNF
postpone\ [EBNF
postpone\ EBNF:
\ EBNF<
\ EBNF[
\ EBNF:
}
"The EBNF syntax is composed of a series of rules of the form:"
{ $code

View File

@ -145,142 +145,142 @@ in: peg.ebnf.tests
] unit-test
{ V{ "a" "b" } } [
"ab" [EBNF foo='a' 'b' EBNF]
"ab" EBNF[ foo='a' 'b' EBNF]
] unit-test
{ V{ 1 "b" } } [
"ab" [EBNF foo=('a')[[ drop 1 ]] 'b' EBNF]
"ab" EBNF[ foo=('a')[[ drop 1 ]] 'b' EBNF]
] unit-test
{ V{ 1 2 } } [
"ab" [EBNF foo=('a') [[ drop 1 ]] ('b') [[ drop 2 ]] EBNF]
"ab" EBNF[ foo=('a') [[ drop 1 ]] ('b') [[ drop 2 ]] EBNF]
] unit-test
{ char: A } [
"A" [EBNF foo=[A-Z] EBNF]
"A" EBNF[ foo=[A-Z] EBNF]
] unit-test
{ char: Z } [
"Z" [EBNF foo=[A-Z] EBNF]
"Z" EBNF[ foo=[A-Z] EBNF]
] unit-test
[
"0" [EBNF foo=[A-Z] EBNF]
"0" EBNF[ foo=[A-Z] EBNF]
] must-fail
{ char: 0 } [
"0" [EBNF foo=[^A-Z] EBNF]
"0" EBNF[ foo=[^A-Z] EBNF]
] unit-test
[
"A" [EBNF foo=[^A-Z] EBNF]
"A" EBNF[ foo=[^A-Z] EBNF]
] must-fail
[
"Z" [EBNF foo=[^A-Z] EBNF]
"Z" EBNF[ foo=[^A-Z] EBNF]
] must-fail
{ V{ "1" "+" "foo" } } [
"1+1" [EBNF foo='1' '+' '1' [[ drop "foo" ]] EBNF]
"1+1" EBNF[ foo='1' '+' '1' [[ drop "foo" ]] EBNF]
] unit-test
{ "foo" } [
"1+1" [EBNF foo='1' '+' '1' => [[ drop "foo" ]] EBNF]
"1+1" EBNF[ foo='1' '+' '1' => [[ drop "foo" ]] EBNF]
] unit-test
{ "foo" } [
"1+1" [EBNF foo='1' '+' '1' => [[ drop "foo" ]] | '1' '-' '1' => [[ drop "bar" ]] EBNF]
"1+1" EBNF[ foo='1' '+' '1' => [[ drop "foo" ]] | '1' '-' '1' => [[ drop "bar" ]] EBNF]
] unit-test
{ "bar" } [
"1-1" [EBNF foo='1' '+' '1' => [[ drop "foo" ]] | '1' '-' '1' => [[ drop "bar" ]] EBNF]
"1-1" EBNF[ foo='1' '+' '1' => [[ drop "foo" ]] | '1' '-' '1' => [[ drop "bar" ]] EBNF]
] unit-test
{ 6 } [
"4+2" [EBNF num=[0-9] => [[ digit> ]] foo=num:x '+' num:y => [[ x y + ]] EBNF]
"4+2" EBNF[ num=[0-9] => [[ digit> ]] foo=num:x '+' num:y => [[ x y + ]] EBNF]
] unit-test
{ 6 } [
"4+2" [EBNF foo=[0-9]:x '+' [0-9]:y => [[ x digit> y digit> + ]] EBNF]
"4+2" EBNF[ foo=[0-9]:x '+' [0-9]:y => [[ x digit> y digit> + ]] EBNF]
] unit-test
{ 10 } [
{ 1 2 3 4 } [EBNF num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
{ 1 2 3 4 } EBNF[ num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
] unit-test
[
{ "a" 2 3 4 } [EBNF num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
{ "a" 2 3 4 } EBNF[ num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
] must-fail
{ 3 } [
{ 1 2 "a" 4 } [EBNF num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
{ 1 2 "a" 4 } EBNF[ num=. ?[ number? ]? list=list:x num:y => [[ x y + ]] | num EBNF]
] unit-test
[
"ab" [EBNF -=" " | "\t" | "\n" foo="a" - "b" EBNF]
"ab" EBNF[ -=" " | "\t" | "\n" foo="a" - "b" EBNF]
] must-fail
{ V{ "a" " " "b" } } [
"a b" [EBNF -=" " | "\t" | "\n" foo="a" - "b" EBNF]
"a b" EBNF[ -=" " | "\t" | "\n" foo="a" - "b" EBNF]
] unit-test
{ V{ "a" "\t" "b" } } [
"a\tb" [EBNF -=" " | "\t" | "\n" foo="a" - "b" EBNF]
"a\tb" EBNF[ -=" " | "\t" | "\n" foo="a" - "b" EBNF]
] unit-test
{ V{ "a" "\n" "b" } } [
"a\nb" [EBNF -=" " | "\t" | "\n" foo="a" - "b" EBNF]
"a\nb" EBNF[ -=" " | "\t" | "\n" foo="a" - "b" EBNF]
] unit-test
{ V{ "a" f "b" } } [
"ab" [EBNF -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
"ab" EBNF[ -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
] unit-test
{ V{ "a" " " "b" } } [
"a b" [EBNF -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
"a b" EBNF[ -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
] unit-test
{ V{ "a" "\t" "b" } } [
"a\tb" [EBNF -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
"a\tb" EBNF[ -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
] unit-test
{ V{ "a" "\n" "b" } } [
"a\nb" [EBNF -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
"a\nb" EBNF[ -=" " | "\t" | "\n" foo="a" (-)? "b" EBNF]
] unit-test
{ V{ "a" "b" } } [
"ab" [EBNF -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
"ab" EBNF[ -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
] unit-test
{ V{ "a" "b" } } [
"a\tb" [EBNF -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
"a\tb" EBNF[ -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
] unit-test
{ V{ "a" "b" } } [
"a\nb" [EBNF -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
"a\nb" EBNF[ -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
] unit-test
[
"axb" [EBNF -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
"axb" EBNF[ -=(" " | "\t" | "\n")? => [[ drop ignore ]] foo="a" - "b" EBNF]
] must-fail
{ V{ V{ 49 } "+" V{ 49 } } } [
! Test direct left recursion.
! Using packrat, so first part of expr fails, causing 2nd choice to be used
"1+1" [EBNF num=([0-9])+ expr=expr "+" num | num EBNF]
"1+1" EBNF[ num=([0-9])+ expr=expr "+" num | num EBNF]
] unit-test
{ V{ V{ V{ 49 } "+" V{ 49 } } "+" V{ 49 } } } [
! Test direct left recursion.
! Using packrat, so first part of expr fails, causing 2nd choice to be used
"1+1+1" [EBNF num=([0-9])+ expr=expr "+" num | num EBNF]
"1+1+1" EBNF[ num=([0-9])+ expr=expr "+" num | num EBNF]
] unit-test
{ V{ V{ V{ 49 } "+" V{ 49 } } "+" V{ 49 } } } [
! Test indirect left recursion.
! Using packrat, so first part of expr fails, causing 2nd choice to be used
"1+1+1" [EBNF num=([0-9])+ x=expr expr=x "+" num | num EBNF]
"1+1+1" EBNF[ num=([0-9])+ x=expr expr=x "+" num | num EBNF]
] unit-test
{ t } [
@ -310,7 +310,7 @@ MethodName = "m" | "n"
ExpressionName = Identifier
Expression = "i" | "j"
main = Primary
;EBNF
EBNF;
{ "this" } [
"this" primary
@ -333,113 +333,113 @@ main = Primary
] unit-test
{ V{ V{ "a" "b" } "c" } } [
"abc" [EBNF a="a" "b" foo=(a "c") EBNF]
"abc" EBNF[ a="a" "b" foo=(a "c") EBNF]
] unit-test
{ V{ "a" "c" } } [
"abc" [EBNF a="a" "b"~ foo=(a "c") EBNF]
"abc" EBNF[ a="a" "b"~ foo=(a "c") EBNF]
] unit-test
{ V{ V{ "a" V{ "b" "b" } } "c" } } [
"abbc" [EBNF a=("a" "b"*) foo=(a "c") EBNF]
"abbc" EBNF[ a=("a" "b"*) foo=(a "c") EBNF]
] unit-test
{ V{ "a" "c" } } [
"abc" [EBNF a=("a" ("b")~) foo=(a "c") EBNF]
"abc" EBNF[ a=("a" ("b")~) foo=(a "c") EBNF]
] unit-test
{ V{ "a" "c" } } [
"abc" [EBNF a=("a" "b"~) foo=(a "c") EBNF]
"abc" EBNF[ a=("a" "b"~) foo=(a "c") EBNF]
] unit-test
{ "c" } [
"abc" [EBNF a=("a" "b")~ foo=(a "c") EBNF]
"abc" EBNF[ a=("a" "b")~ foo=(a "c") EBNF]
] unit-test
{ V{ V{ "a" "b" } "c" } } [
"abc" [EBNF a="a" "b" foo={a "c"} EBNF]
"abc" EBNF[ a="a" "b" foo={a "c"} EBNF]
] unit-test
{ V{ V{ "a" "b" } "c" } } [
"abc" [EBNF a="a" "b" foo=a "c" EBNF]
"abc" EBNF[ a="a" "b" foo=a "c" EBNF]
] unit-test
[
"a bc" [EBNF a="a" "b" foo=(a "c") EBNF]
"a bc" EBNF[ a="a" "b" foo=(a "c") EBNF]
] must-fail
[
"a bc" [EBNF a="a" "b" foo=a "c" EBNF]
"a bc" EBNF[ a="a" "b" foo=a "c" EBNF]
] must-fail
[
"a bc" [EBNF a="a" "b" foo={a "c"} EBNF]
"a bc" EBNF[ a="a" "b" foo={a "c"} EBNF]
] must-fail
[
"ab c" [EBNF a="a" "b" foo=a "c" EBNF]
"ab c" EBNF[ a="a" "b" foo=a "c" EBNF]
] must-fail
{ V{ V{ "a" "b" } "c" } } [
"ab c" [EBNF a="a" "b" foo={a "c"} EBNF]
"ab c" EBNF[ a="a" "b" foo={a "c"} EBNF]
] unit-test
[
"ab c" [EBNF a="a" "b" foo=(a "c") EBNF]
"ab c" EBNF[ a="a" "b" foo=(a "c") EBNF]
] must-fail
[
"a b c" [EBNF a="a" "b" foo=a "c" EBNF]
"a b c" EBNF[ a="a" "b" foo=a "c" EBNF]
] must-fail
[
"a b c" [EBNF a="a" "b" foo=(a "c") EBNF]
"a b c" EBNF[ a="a" "b" foo=(a "c") EBNF]
] must-fail
[
"a b c" [EBNF a="a" "b" foo={a "c"} EBNF]
"a b c" EBNF[ a="a" "b" foo={a "c"} EBNF]
] must-fail
{ V{ V{ V{ "a" "b" } "c" } V{ V{ "a" "b" } "c" } } } [
"ab cab c" [EBNF a="a" "b" foo={a "c"}* EBNF]
"ab cab c" EBNF[ a="a" "b" foo={a "c"}* EBNF]
] unit-test
{ V{ } } [
"ab cab c" [EBNF a="a" "b" foo=(a "c")* EBNF]
"ab cab c" EBNF[ a="a" "b" foo=(a "c")* EBNF]
] unit-test
{ V{ V{ V{ "a" "b" } "c" } V{ V{ "a" "b" } "c" } } } [
"ab c ab c" [EBNF a="a" "b" foo={a "c"}* EBNF]
"ab c ab c" EBNF[ a="a" "b" foo={a "c"}* EBNF]
] unit-test
{ V{ V{ "a" "c" } V{ "a" "c" } } } [
"ab c ab c" [EBNF a="a" "b"~ foo={a "c"}* EBNF]
"ab c ab c" EBNF[ a="a" "b"~ foo={a "c"}* EBNF]
] unit-test
{ V{ } } [
"ab c ab c" [EBNF a="a" "b" foo=(a "c")* EBNF]
"ab c ab c" EBNF[ a="a" "b" foo=(a "c")* EBNF]
] unit-test
{ V{ } } [
"ab c ab c" [EBNF a="a" "b" foo=(a "c")* EBNF]
"ab c ab c" EBNF[ a="a" "b" foo=(a "c")* EBNF]
] unit-test
{ V{ "a" "a" "a" } } [
"aaa" [EBNF a=('a')* b=!('b') a:x => [[ x ]] EBNF]
"aaa" EBNF[ a=('a')* b=!('b') a:x => [[ x ]] EBNF]
] unit-test
{ t } [
"aaa" [EBNF a=('a')* b=!('b') a:x => [[ x ]] EBNF]
"aaa" [EBNF a=('a')* b=!('b') (a):x => [[ x ]] EBNF] =
"aaa" EBNF[ a=('a')* b=!('b') a:x => [[ x ]] EBNF]
"aaa" EBNF[ a=('a')* b=!('b') (a):x => [[ x ]] EBNF] =
] unit-test
{ V{ "a" "a" "a" } } [
"aaa" [EBNF a=('a')* b=a:x => [[ x ]] EBNF]
"aaa" EBNF[ a=('a')* b=a:x => [[ x ]] EBNF]
] unit-test
{ t } [
"aaa" [EBNF a=('a')* b=a:x => [[ x ]] EBNF]
"aaa" [EBNF a=('a')* b=(a):x => [[ x ]] EBNF] =
"aaa" EBNF[ a=('a')* b=a:x => [[ x ]] EBNF]
"aaa" EBNF[ a=('a')* b=(a):x => [[ x ]] EBNF] =
] unit-test
{ t } [
@ -471,20 +471,20 @@ main = Primary
<<
EBNF: parser1
foo='a'
;EBNF
EBNF;
>>
EBNF: parser2
foo=<foreign parser1 foo> 'b'
;EBNF
EBNF;
EBNF: parser3
foo=<foreign parser1> 'c'
;EBNF
EBNF;
EBNF: parser4
foo=<foreign any-char> 'd'
;EBNF
EBNF;
{ "a" } [
"a" parser1
@ -503,11 +503,11 @@ foo=<foreign any-char> 'd'
] unit-test
{ } [
"USING: kernel peg.ebnf ; \"a\\n\" [EBNF foo='a' '\n' => [[ drop \"\n\" ]] EBNF] drop" eval( -- )
"USING: kernel peg.ebnf ; \"a\\n\" EBNF[ foo='a' '\n' => [[ drop \"\n\" ]] EBNF] drop" eval( -- )
] unit-test
[
"USING: peg.ebnf ; <EBNF foo='a' foo='b' EBNF>" eval( -- ) drop
"USING: peg.ebnf ; EBNF< foo='a' foo='b' EBNF>" eval( -- ) drop
] must-fail
{ t } [
@ -518,7 +518,7 @@ foo=<foreign any-char> 'd'
! Tokenizer tests
{ V{ "a" char: b } } [
"ab" [EBNF tokenizer=default foo="a" . EBNF]
"ab" EBNF[ tokenizer=default foo="a" . EBNF]
] unit-test
TUPLE: ast-number value ;
@ -539,10 +539,10 @@ Special = "(" | ")" | "{" | "}" | "[" | "]" | "," | "
| "-" | "*=" | "*" | "/=" | "/" | "%=" | "%" | "&&="
| "&&" | "||=" | "||" | "." | "!"
Tok = Spaces (Number | Special )
;EBNF
EBNF;
{ V{ char: 1 T{ ast-number f 23 } ";" char: x } } [
"123;x" [EBNF bar = .
"123;x" EBNF[ bar = .
tokenizer = <foreign a-tokenizer Tok> foo=.
tokenizer=default baz=.
main = bar foo foo baz
@ -550,7 +550,7 @@ Tok = Spaces (Number | Special )
] unit-test
{ V{ char: 5 "+" char: 2 } } [
"5+2" [EBNF
"5+2" EBNF[
space=(" " | "\n")
number=[0-9]
operator=("*" | "+")
@ -561,7 +561,7 @@ Tok = Spaces (Number | Special )
] unit-test
{ V{ char: 5 "+" char: 2 } } [
"5 + 2" [EBNF
"5 + 2" EBNF[
space=(" " | "\n")
number=[0-9]
operator=("*" | "+")
@ -572,16 +572,16 @@ Tok = Spaces (Number | Special )
] unit-test
{ "++" } [
"++--" [EBNF tokenizer=("++" | "--") main="++" EBNF]
"++--" EBNF[ tokenizer=("++" | "--") main="++" EBNF]
] unit-test
{ "\\" } [
"\\" [EBNF foo="\\" EBNF]
"\\" EBNF[ foo="\\" EBNF]
] unit-test
[ "use: peg.ebnf [EBNF EBNF]" eval( -- ) ] must-fail
[ "use: peg.ebnf EBNF[ EBNF]" eval( -- ) ] must-fail
[ "use: peg.ebnf [EBNF
[ "use: peg.ebnf EBNF[
lol = a
lol = b
EBNF]" eval( -- )
@ -592,13 +592,13 @@ Tok = Spaces (Number | Special )
{
{ "a" "a" }
} [
EBNF: foo Bar = "a":a1 "a":a2 => [[ a1 a2 2array ]] ;EBNF
EBNF: foo Bar = "a":a1 "a":a2 => [[ a1 a2 2array ]] EBNF;
"aa" foo
] unit-test
{
{ "a" "a" }
} [
EBNF: foo2 Bar = "a":a-1 "a":a-2 => [[ a-1 a-2 2array ]] ;EBNF
EBNF: foo2 Bar = "a":a-1 "a":a-2 => [[ a-1 a-2 2array ]] EBNF;
"aa" foo2
] unit-test

View File

@ -66,7 +66,7 @@ loop = "[" {loop|ops}+ "]" => [[ second compose-all '[ [ (?) ] _ while ] ]]
code = (loop|ops|unknown)* => [[ compose-all ]]
;EBNF
EBNF;
PRIVATE>

View File

@ -90,7 +90,7 @@ plain-text = (!("%").)+ => [[ >string ]]
text = (formats|plain-text)* => [[ ]]
;EBNF
EBNF;
: printf-quot ( format-string -- format-quot n )
parse-printf [ [ callable? ] count ] keep [
@ -191,7 +191,7 @@ plain-text = (!("%").)+ => [[ >string ]]
text = (formats|plain-text)* => [[ ]]
;EBNF
EBNF;
PRIVATE>

View File

@ -45,7 +45,7 @@ End = !(.)
Main = Concatenation End
;EBNF
EBNF;
: glob-matches? ( input glob -- ? )
[ >case-fold ] bi@ <glob> matches? ;

View File

@ -124,4 +124,4 @@ Tokens = Token* => [[ [ comment? ] reject ]]
Program = Tokens Spaces !(.) => [[ parse-proc ]]
;EBNF
EBNF;

View File

@ -29,7 +29,7 @@ Sum = Sum:s ("+"|"-"):op Product:p => [[ s p op ast-op boa ]]
End = !(.)
Expression = Sum End
;EBNF
EBNF;
: build-infix-ast ( string -- ast )
tokenize-infix parse-infix ;

View File

@ -21,4 +21,4 @@ Special = [+*/%(),] | "-" => [[ char: - ]]
Tok = Spaces (Name | Number | Special )
End = !(.)
Toks = Tok* Spaces End
;EBNF
EBNF;

View File

@ -16,4 +16,4 @@ fac = fac "*" value => [[ first3 nip * ]]
exp = exp "+" fac => [[ first3 nip + ]]
| exp "-" fac => [[ first3 nip - ]]
| fac
;EBNF
EBNF;

View File

@ -197,4 +197,4 @@ SrcElem = "function" Name:n FuncRest:f => [[ n f a
| Stmt
SrcElems = SrcElem* => [[ ast-begin boa ]]
TopLevel = SrcElems Spaces
;EBNF
EBNF;

View File

@ -87,4 +87,4 @@ Special = "(" | ")" | "{" | "}" | "[" | "]" | "," |
| "^"
Tok = Spaces (Name | Keyword | Number | Str | RegExp | Special )
Toks = Tok* Spaces
;EBNF
EBNF;

View File

@ -24,4 +24,4 @@ factor = ident | number | "(" expression ")"
ident = (([a-zA-Z])+) => [[ >string ]]
number = ([0-9])+ => [[ string>number ]]
program = { block "." }
;EBNF
EBNF;

View File

@ -217,4 +217,4 @@ Alternation = Concatenation:c ("|" Concatenation)*:a
End = !(.)
Main = Alternation End
;EBNF
EBNF;

View File

@ -89,4 +89,4 @@ pipeline = _ command _ (in-file)? _ "|" _ (command _ "|" _)* command _ (to-file
submission = (pipeline | basic)
;EBNF
EBNF;

View File

@ -10,4 +10,4 @@ quoted = '"' (escaped-char | [^"])*:a '"' => [[ a ]]
unquoted = (escaped-char | [^ \t\n\r"])+
argument = (quoted | unquoted) => [[ >string ]]
command = space* (argument:a space* => [[ a ]])+:c !(.) => [[ c ]]
;EBNF
EBNF;

View File

@ -76,7 +76,7 @@ wsp = [ \t\r\n]
transform-list = wsp* transforms?:t wsp*
=> [[ t [ identity-transform ] unless* ]]
;EBNF
EBNF;
: tag-transform ( tag -- transform )
"transform" svg-name attr svg-transform>affine-transform ;
@ -218,7 +218,7 @@ wsp = [ \t\r\n]
svg-path = wsp* moveto-drawto-command-groups?:x wsp* => [[ x ]]
;EBNF
EBNF;
: tag-d ( tag -- d )
"d" svg-name attr svg-path>array ;

View File

@ -57,7 +57,7 @@ url = (((protocol "://") => [[ first ]] auth hostname)
("?" query => [[ second ]])?
("#" anchor => [[ second ]])?
;EBNF
EBNF;
PRIVATE>

View File

@ -77,7 +77,7 @@ param = "," " "* type " "* => [[ third ]]
params = "<" " "* type " "* param* ">" => [[ [ 4 swap nth ] [ third ] bi prefix ]]
type = name " "* params? " "* ptr? => [[ { 0 2 4 } [ swap nth ] with map first3 <c++-type> ]]
;EBNF
EBNF;
: parse-c++-type ( str -- c++-type )
factorize-type (parse-c++-type) ;

View File

@ -241,6 +241,6 @@ Type = WhiteSpace T:t WhiteSpace => [[ t ]]
Program = Type
;EBNF
EBNF;
SYNTAX: TYPE: ";" parse-multiline-string parse-type suffix! ;

View File

@ -10,7 +10,7 @@ s = ':' => [[ drop ignore ]]
rpc = tokenpart s s tokenpart => [[ first2 remote-vocab ]]
remote = tokenpart s tokenpart => [[ first2 remote-load ]]
module = rpc | remote | tokenpart
;EBNF
EBNF;
ON-BNF: USING*:
tokenizer = <foreign factor>

View File

@ -61,4 +61,4 @@ space = " " | "\n" | "\t"
spaces = space* => [[ drop ignore ]]
chunk = (!(space) .)+ => [[ >string ]]
expr = spaces chunk
;EBNF
EBNF;