]> gitweb.factorcode.org Git - factor.git/commitdiff
peg.javascript: simplify to one file.
authorJohn Benediktsson <mrjbq7@gmail.com>
Thu, 24 Dec 2020 17:24:26 +0000 (09:24 -0800)
committerJohn Benediktsson <mrjbq7@gmail.com>
Thu, 24 Dec 2020 17:24:26 +0000 (09:24 -0800)
Then maybe modifying for new javascript syntax.

17 files changed:
extra/peg/javascript/ast/ast.factor [deleted file]
extra/peg/javascript/ast/authors.txt [deleted file]
extra/peg/javascript/ast/summary.txt [deleted file]
extra/peg/javascript/ast/tags.txt [deleted file]
extra/peg/javascript/javascript-tests.factor
extra/peg/javascript/javascript.factor
extra/peg/javascript/parser/authors.txt [deleted file]
extra/peg/javascript/parser/parser-tests.factor [deleted file]
extra/peg/javascript/parser/parser.factor [deleted file]
extra/peg/javascript/parser/summary.txt [deleted file]
extra/peg/javascript/parser/tags.txt [deleted file]
extra/peg/javascript/summary.txt
extra/peg/javascript/tokenizer/authors.txt [deleted file]
extra/peg/javascript/tokenizer/summary.txt [deleted file]
extra/peg/javascript/tokenizer/tags.txt [deleted file]
extra/peg/javascript/tokenizer/tokenizer-tests.factor [deleted file]
extra/peg/javascript/tokenizer/tokenizer.factor [deleted file]

diff --git a/extra/peg/javascript/ast/ast.factor b/extra/peg/javascript/ast/ast.factor
deleted file mode 100644 (file)
index 9f67af8..0000000
+++ /dev/null
@@ -1,43 +0,0 @@
-! Copyright (C) 2008 Chris Double.
-! See http://factorcode.org/license.txt for BSD license.
-USING: kernel ;
-IN: peg.javascript.ast
-
-TUPLE: ast-keyword value ;
-TUPLE: ast-name value ;
-TUPLE: ast-number value ;
-TUPLE: ast-string value ;
-TUPLE: ast-regexp body flags ;
-TUPLE: ast-cond-expr condition then else ;
-TUPLE: ast-set lhs rhs ;
-TUPLE: ast-get value ;
-TUPLE: ast-mset lhs rhs operator ;
-TUPLE: ast-binop lhs rhs operator ;
-TUPLE: ast-unop expr operator ;
-TUPLE: ast-postop expr operator ;
-TUPLE: ast-preop expr operator ;
-TUPLE: ast-getp index expr ;
-TUPLE: ast-send method expr args ;
-TUPLE: ast-call expr args ;
-TUPLE: ast-this ;
-TUPLE: ast-new name args ;
-TUPLE: ast-array values ;
-TUPLE: ast-json bindings ;
-TUPLE: ast-binding name value ;
-TUPLE: ast-func fs body ;
-TUPLE: ast-var name value ;
-TUPLE: ast-begin statements ;
-TUPLE: ast-if condition true false ;
-TUPLE: ast-while condition statements ;
-TUPLE: ast-do-while statements condition ;
-TUPLE: ast-for i c u statements ;
-TUPLE: ast-for-in v e statements ;
-TUPLE: ast-switch expr statements ;
-TUPLE: ast-break ;
-TUPLE: ast-continue ;
-TUPLE: ast-throw e ;
-TUPLE: ast-try t e c f ;
-TUPLE: ast-return e ;
-TUPLE: ast-with expr body ;
-TUPLE: ast-case c cs ;
-TUPLE: ast-default cs ;
diff --git a/extra/peg/javascript/ast/authors.txt b/extra/peg/javascript/ast/authors.txt
deleted file mode 100644 (file)
index 44b06f9..0000000
+++ /dev/null
@@ -1 +0,0 @@
-Chris Double
diff --git a/extra/peg/javascript/ast/summary.txt b/extra/peg/javascript/ast/summary.txt
deleted file mode 100644 (file)
index 543a2e6..0000000
+++ /dev/null
@@ -1 +0,0 @@
-Abstract Syntax Tree for JavaScript parser
diff --git a/extra/peg/javascript/ast/tags.txt b/extra/peg/javascript/ast/tags.txt
deleted file mode 100644 (file)
index 643ffaa..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-javascript
-parsing
-languages
index 5fa2b91fc7454ab9a4a56a59824b841256828b2e..b8a13187ee885dc5c9426d5e30b465764b245d99 100644 (file)
@@ -3,6 +3,85 @@
 
 USING: kernel tools.test peg.javascript peg.javascript.ast ;
 
+{
+  V{
+    T{ ast-number f 123 }
+    ";"
+    T{ ast-string f "hello" }
+    ";"
+    T{ ast-name f "foo" }
+    "("
+    T{ ast-name f "x" }
+    ")"
+    ";"
+  }
+} [
+  "123; 'hello'; foo(x);" tokenize-javascript
+] unit-test
+
+{ V{ T{ ast-regexp f "<(w+)[^>]*?)/>" "g" } } } [
+  "/<(\\w+)[^>]*?)\\/>/g" tokenize-javascript
+] unit-test
+
+{
+    V{ T{ ast-string { value "abc\"def\"" } } }
+} [ "\"abc\\\"def\\\"\"" tokenize-javascript ] unit-test
+
+{
+    V{ T{ ast-string { value "\b\f\n\r\t\v'\"\\" } } }
+} [ "\"\\b\\f\\n\\r\\t\\v\\'\\\"\\\\\"" tokenize-javascript ] unit-test
+
+{
+    V{ T{ ast-string { value "abc" } } }
+} [ "\"\\x61\\u0062\\u{63}\"" tokenize-javascript ] unit-test
+
+{
+  T{
+      ast-begin
+      f
+      V{
+          T{ ast-number f 123 }
+          T{ ast-string f "hello" }
+          T{
+              ast-call
+              f
+              T{ ast-get f "foo" }
+              V{ T{ ast-get f "x" } }
+          }
+      }
+  }
+} [
+  "123; 'hello'; foo(x);" parse-javascript
+] unit-test
+
+{ t } [
+"
+var x=5
+var y=10
+" main \ parse-javascript rule (parse) remaining>> length zero?
+] unit-test
+
+
+{ t } [
+"
+function foldl(f, initial, seq) {
+   for(var i=0; i< seq.length; ++i)
+     initial = f(initial, seq[i]);
+   return initial;
+}" main \ parse-javascript rule (parse) remaining>> length zero?
+] unit-test
+
+{ t } [
+"
+ParseState.prototype.from = function(index) {
+    var r = new ParseState(this.input, this.index + index);
+    r.cache = this.cache;
+    r.length = this.length - index;
+    return r;
+}" main \ parse-javascript rule (parse) remaining>> length zero?
+] unit-test
+
+
 { T{ ast-begin f V{ T{ ast-number f 123 } } } } [
   "123;" parse-javascript
 ] unit-test
index 4a919cf39f0ad0cec4a1e4301af01ebf631b6f49..5b3510e8206f30b8d416ee0a3d3af2b5242f2928 100644 (file)
@@ -1,7 +1,329 @@
 ! Copyright (C) 2008 Chris Double.
 ! See http://factorcode.org/license.txt for BSD license.
-USING: kernel accessors peg.javascript.tokenizer peg.javascript.parser ;
+USING: accessors arrays kernel math.parser multiline peg
+peg.ebnf sequences strings ;
 IN: peg.javascript
 
-: parse-javascript ( string -- ast )
-  javascript ;
+<PRIVATE
+
+TUPLE: ast-keyword value ;
+TUPLE: ast-name value ;
+TUPLE: ast-number value ;
+TUPLE: ast-string value ;
+TUPLE: ast-regexp body flags ;
+TUPLE: ast-cond-expr condition then else ;
+TUPLE: ast-set lhs rhs ;
+TUPLE: ast-get value ;
+TUPLE: ast-mset lhs rhs operator ;
+TUPLE: ast-binop lhs rhs operator ;
+TUPLE: ast-unop expr operator ;
+TUPLE: ast-postop expr operator ;
+TUPLE: ast-preop expr operator ;
+TUPLE: ast-getp index expr ;
+TUPLE: ast-send method expr args ;
+TUPLE: ast-call expr args ;
+TUPLE: ast-this ;
+TUPLE: ast-new name args ;
+TUPLE: ast-array values ;
+TUPLE: ast-json bindings ;
+TUPLE: ast-binding name value ;
+TUPLE: ast-func fs body ;
+TUPLE: ast-var name value ;
+TUPLE: ast-begin statements ;
+TUPLE: ast-if condition true false ;
+TUPLE: ast-while condition statements ;
+TUPLE: ast-do-while statements condition ;
+TUPLE: ast-for i c u statements ;
+TUPLE: ast-for-in v e statements ;
+TUPLE: ast-switch expr statements ;
+TUPLE: ast-break ;
+TUPLE: ast-continue ;
+TUPLE: ast-throw e ;
+TUPLE: ast-try t e c f ;
+TUPLE: ast-return e ;
+TUPLE: ast-with expr body ;
+TUPLE: ast-case c cs ;
+TUPLE: ast-default cs ;
+
+PRIVATE>
+
+! Grammar for JavaScript. Based on OMeta-JS example from:
+! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler
+
+EBNF: tokenize-javascript [=[
+Letter            = [a-zA-Z]
+Digit             = [0-9]
+Digits            = Digit+
+SingleLineComment = "//" (!("\n") .)* "\n" => [[ ignore ]]
+MultiLineComment  = "/*" (!("*/") .)* "*/" => [[ ignore ]]
+Space             = [ \t\r\n] | SingleLineComment | MultiLineComment
+Spaces            = Space* => [[ ignore ]]
+NameFirst         = Letter | "$" => [[ CHAR: $ ]] | "_" => [[ CHAR: _ ]]
+NameRest          = NameFirst | Digit
+iName             = NameFirst NameRest* => [[ first2 swap prefix >string ]]
+Keyword           =  ("break"
+                    | "case"
+                    | "catch"
+                    | "continue"
+                    | "default"
+                    | "delete"
+                    | "do"
+                    | "else"
+                    | "finally"
+                    | "for"
+                    | "function"
+                    | "if"
+                    | "in"
+                    | "instanceof"
+                    | "new"
+                    | "return"
+                    | "switch"
+                    | "this"
+                    | "throw"
+                    | "try"
+                    | "typeof"
+                    | "var"
+                    | "void"
+                    | "while"
+                    | "with") !(NameRest)
+Name              = !(Keyword) iName  => [[ ast-name boa ]]
+Number            =   Digits:ws '.' Digits:fs => [[ ws "." fs 3array "" concat-as string>number ast-number boa ]]
+                    | Digits => [[ >string string>number ast-number boa ]]
+
+SingleEscape      =   "b"  => [[ CHAR: \b ]]
+                    | "f"  => [[ CHAR: \f ]]
+                    | "n"  => [[ CHAR: \n ]]
+                    | "r"  => [[ CHAR: \r ]]
+                    | "t"  => [[ CHAR: \t ]]
+                    | "v"  => [[ CHAR: \v ]]
+                    | "'"  => [[ CHAR: '  ]]
+                    | "\"" => [[ CHAR: \"  ]]
+                    | "\\" => [[ CHAR: \\ ]]
+HexDigit          = [0-9a-fA-F]
+HexEscape         = "x" (HexDigit HexDigit):d => [[ d hex> ]]
+UnicodeEscape     = "u" (HexDigit HexDigit HexDigit HexDigit):d => [[ d hex> ]]
+                    | "u{" HexDigit+:d "}" => [[ d hex> ]]
+EscapeChar         = "\\" (SingleEscape | HexEscape | UnicodeEscape):c => [[ c ]]
+StringChars1       = (EscapeChar | !('"""') .)* => [[ >string ]]
+StringChars2       = (EscapeChar | !('"') .)* => [[ >string ]]
+StringChars3       = (EscapeChar | !("'") .)* => [[ >string ]]
+Str                =   '"""' StringChars1:cs '"""' => [[ cs ast-string boa ]]
+                     | '"' StringChars2:cs '"' => [[ cs ast-string boa ]]
+                     | "'" StringChars3:cs "'" => [[ cs ast-string boa ]]
+RegExpFlags        = NameRest* => [[ >string ]]
+NonTerminator      = !([\n\r]) .
+BackslashSequence  = "\\" NonTerminator => [[ second ]]
+RegExpFirstChar    =   !([*\\/]) NonTerminator
+                     | BackslashSequence
+RegExpChar         =   !([\\/]) NonTerminator
+                     | BackslashSequence
+RegExpChars        = RegExpChar*
+RegExpBody         = RegExpFirstChar RegExpChars => [[ first2 swap prefix >string ]]
+RegExp             = "/" RegExpBody:b "/" RegExpFlags:fl => [[ b fl ast-regexp boa ]]
+Special            =   "("    | ")"   | "{"   | "}"   | "["   | "]"   | ","   | ";"
+                     | "?"    | ":"   | "!==" | "!="  | "===" | "=="  | "="   | ">="
+                     | ">>>=" | ">>>" | ">>=" | ">>"  | ">"   | "<="  | "<<=" | "<<"
+                     | "<"    | "++"  | "+="  | "+"   | "--"  | "-="  | "-"   | "*="
+                     | "*"    | "/="  | "/"   | "%="  | "%"   | "&&=" | "&&"  | "||="
+                     | "||"   | "."   | "!"   | "&="  | "&"   | "|="  | "|"   | "^="
+                     | "^"
+Tok                = Spaces (Name | Keyword | Number | Str | RegExp | Special )
+Toks               = Tok* Spaces
+]=]
+
+! Grammar for JavaScript. Based on OMeta-JS example from:
+! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler
+
+! The interesting thing about this parser is the mixing of
+! a default and non-default tokenizer. The JavaScript tokenizer
+! removes all newlines. So when operating on tokens there is no
+! need for newline and space skipping in the grammar. But JavaScript
+! uses the newline in the 'automatic semicolon insertion' rule.
+!
+! If a statement ends in a newline, sometimes the semicolon can be
+! skipped. So we define an 'nl' rule using the default tokenizer.
+! This operates a character at a time. Using this 'nl' in the parser
+! allows us to detect newlines when we need to for the semicolon
+! insertion rule, but ignore it in all other places.
+
+EBNF: parse-javascript [=[
+tokenizer         = default
+nl                = "\r\n" | "\n"
+
+tokenizer         = <foreign tokenize-javascript Tok>
+End               = !(.)
+Space             = [ \t\r\n]
+Spaces            = Space* => [[ ignore ]]
+Comment           = "/*" [^*/]* "*/" => [[ ignore ]]
+Name               = . ?[ ast-name?   ]?   => [[ value>> ]]
+Number             = . ?[ ast-number? ]?
+String             = . ?[ ast-string? ]?
+RegExp             = . ?[ ast-regexp? ]?
+SpacesNoNl         = (!(nl) Space)* => [[ ignore ]]
+
+Expr               =   OrExpr:e "?" Expr:t ":" Expr:f   => [[ e t f ast-cond-expr boa ]]
+                     | OrExpr:e "=" Expr:rhs            => [[ e rhs ast-set boa ]]
+                     | OrExpr:e "+=" Expr:rhs           => [[ e rhs "+" ast-mset boa ]]
+                     | OrExpr:e "-=" Expr:rhs           => [[ e rhs "-" ast-mset boa ]]
+                     | OrExpr:e "*=" Expr:rhs           => [[ e rhs "*" ast-mset boa ]]
+                     | OrExpr:e "/=" Expr:rhs           => [[ e rhs "/" ast-mset boa ]]
+                     | OrExpr:e "%=" Expr:rhs           => [[ e rhs "%" ast-mset boa ]]
+                     | OrExpr:e "&&=" Expr:rhs          => [[ e rhs "&&" ast-mset boa ]]
+                     | OrExpr:e "||=" Expr:rhs          => [[ e rhs "||" ast-mset boa ]]
+                     | OrExpr:e "^=" Expr:rhs           => [[ e rhs "^" ast-mset boa ]]
+                     | OrExpr:e "&=" Expr:rhs           => [[ e rhs "&" ast-mset boa ]]
+                     | OrExpr:e "|=" Expr:rhs           => [[ e rhs "|" ast-mset boa ]]
+                     | OrExpr:e "<<=" Expr:rhs          => [[ e rhs "<<" ast-mset boa ]]
+                     | OrExpr:e ">>=" Expr:rhs          => [[ e rhs ">>" ast-mset boa ]]
+                     | OrExpr:e ">>>=" Expr:rhs         => [[ e rhs ">>>" ast-mset boa ]]
+                     | OrExpr:e                         => [[ e ]]
+
+ExprNoIn           =   OrExprNoIn:e "?" ExprNoIn:t ":" ExprNoIn:f => [[ e t f ast-cond-expr boa ]]
+                     | OrExprNoIn:e "=" ExprNoIn:rhs              => [[ e rhs ast-set boa ]]
+                     | OrExprNoIn:e "+=" ExprNoIn:rhs             => [[ e rhs "+" ast-mset boa ]]
+                     | OrExprNoIn:e "-=" ExprNoIn:rhs             => [[ e rhs "-" ast-mset boa ]]
+                     | OrExprNoIn:e "*=" ExprNoIn:rhs             => [[ e rhs "*" ast-mset boa ]]
+                     | OrExprNoIn:e "/=" ExprNoIn:rhs             => [[ e rhs "/" ast-mset boa ]]
+                     | OrExprNoIn:e "%=" ExprNoIn:rhs             => [[ e rhs "%" ast-mset boa ]]
+                     | OrExprNoIn:e "&&=" ExprNoIn:rhs            => [[ e rhs "&&" ast-mset boa ]]
+                     | OrExprNoIn:e "||=" ExprNoIn:rhs            => [[ e rhs "||" ast-mset boa ]]
+                     | OrExprNoIn:e "^=" ExprNoIn:rhs             => [[ e rhs "^" ast-mset boa ]]
+                     | OrExprNoIn:e "&=" ExprNoIn:rhs             => [[ e rhs "&" ast-mset boa ]]
+                     | OrExprNoIn:e "|=" ExprNoIn:rhs             => [[ e rhs "|" ast-mset boa ]]
+                     | OrExprNoIn:e "<<=" ExprNoIn:rhs            => [[ e rhs "<<" ast-mset boa ]]
+                     | OrExprNoIn:e ">>=" ExprNoIn:rhs            => [[ e rhs ">>" ast-mset boa ]]
+                     | OrExprNoIn:e ">>>=" ExprNoIn:rhs           => [[ e rhs ">>>" ast-mset boa ]]
+                     | OrExprNoIn:e                               => [[ e ]]
+
+OrExpr             =   OrExpr:x "||" AndExpr:y          => [[ x y "||" ast-binop boa ]]
+                     | AndExpr
+OrExprNoIn         =   OrExprNoIn:x "||" AndExprNoIn:y  => [[ x y "||" ast-binop boa ]]
+                     | AndExprNoIn
+AndExpr            =   AndExpr:x "&&" BitOrExpr:y       => [[ x y "&&" ast-binop boa ]]
+                     | BitOrExpr
+AndExprNoIn        =   AndExprNoIn:x "&&" BitOrExprNoIn:y => [[ x y "&&" ast-binop boa ]]
+                     | BitOrExprNoIn
+BitOrExpr          =   BitOrExpr:x "|" BitXORExpr:y     => [[ x y "|" ast-binop boa ]]
+                     | BitXORExpr
+BitOrExprNoIn      =   BitOrExprNoIn:x "|" BitXORExprNoIn:y => [[ x y "|" ast-binop boa ]]
+                     | BitXORExprNoIn
+BitXORExpr         =   BitXORExpr:x "^" BitANDExpr:y    => [[ x y "^" ast-binop boa ]]
+                     | BitANDExpr
+BitXORExprNoIn     =   BitXORExprNoIn:x "^" BitANDExprNoIn:y => [[ x y "^" ast-binop boa ]]
+                     | BitANDExprNoIn
+BitANDExpr         =   BitANDExpr:x "&" EqExpr:y        => [[ x y "&" ast-binop boa ]]
+                     | EqExpr
+BitANDExprNoIn     =   BitANDExprNoIn:x "&" EqExprNoIn:y => [[ x y "&" ast-binop boa ]]
+                     | EqExprNoIn
+EqExpr             =   EqExpr:x "==" RelExpr:y          => [[ x y "==" ast-binop boa ]]
+                     | EqExpr:x "!=" RelExpr:y          => [[ x y "!=" ast-binop boa ]]
+                     | EqExpr:x "===" RelExpr:y         => [[ x y "===" ast-binop boa ]]
+                     | EqExpr:x "!==" RelExpr:y         => [[ x y "!==" ast-binop boa ]]
+                     | RelExpr
+EqExprNoIn         =   EqExprNoIn:x "==" RelExprNoIn:y    => [[ x y "==" ast-binop boa ]]
+                     | EqExprNoIn:x "!=" RelExprNoIn:y    => [[ x y "!=" ast-binop boa ]]
+                     | EqExprNoIn:x "===" RelExprNoIn:y   => [[ x y "===" ast-binop boa ]]
+                     | EqExprNoIn:x "!==" RelExprNoIn:y   => [[ x y "!==" ast-binop boa ]]
+                     | RelExprNoIn
+RelExpr            =   RelExpr:x ">" ShiftExpr:y          => [[ x y ">" ast-binop boa ]]
+                     | RelExpr:x ">=" ShiftExpr:y         => [[ x y ">=" ast-binop boa ]]
+                     | RelExpr:x "<" ShiftExpr:y          => [[ x y "<" ast-binop boa ]]
+                     | RelExpr:x "<=" ShiftExpr:y         => [[ x y "<=" ast-binop boa ]]
+                     | RelExpr:x "instanceof" ShiftExpr:y => [[ x y "instanceof" ast-binop boa ]]
+                     | RelExpr:x "in" ShiftExpr:y         => [[ x y "in" ast-binop boa ]]
+                     | ShiftExpr
+RelExprNoIn        =   RelExprNoIn:x ">" ShiftExpr:y          => [[ x y ">" ast-binop boa ]]
+                     | RelExprNoIn:x ">=" ShiftExpr:y         => [[ x y ">=" ast-binop boa ]]
+                     | RelExprNoIn:x "<" ShiftExpr:y          => [[ x y "<" ast-binop boa ]]
+                     | RelExprNoIn:x "<=" ShiftExpr:y         => [[ x y "<=" ast-binop boa ]]
+                     | RelExprNoIn:x "instanceof" ShiftExpr:y => [[ x y "instanceof" ast-binop boa ]]
+                     | ShiftExpr
+ShiftExpr          =   ShiftExpr:x "<<" AddExpr:y       => [[ x y "<<" ast-binop boa ]]
+                     | ShiftExpr:x ">>>" AddExpr:y      => [[ x y ">>>" ast-binop boa ]]
+                     | ShiftExpr:x ">>" AddExpr:y       => [[ x y ">>" ast-binop boa ]]
+                     | AddExpr
+AddExpr            =   AddExpr:x "+" MulExpr:y          => [[ x y "+" ast-binop boa ]]
+                     | AddExpr:x "-" MulExpr:y          => [[ x y "-" ast-binop boa ]]
+                     | MulExpr
+MulExpr            =   MulExpr:x "*" Unary:y            => [[ x y "*" ast-binop boa ]]
+                     | MulExpr:x "/" Unary:y            => [[ x y "/" ast-binop boa ]]
+                     | MulExpr:x "%" Unary:y            => [[ x y "%" ast-binop boa ]]
+                     | Unary
+Unary              =   "-" Unary:p                      => [[ p "-" ast-unop boa ]]
+                     | "+" Unary:p                      => [[ p ]]
+                     | "++" Unary:p                     => [[ p "++" ast-preop boa ]]
+                     | "--" Unary:p                     => [[ p "--" ast-preop boa ]]
+                     | "!" Unary:p                      => [[ p "!" ast-unop boa ]]
+                     | "typeof" Unary:p                 => [[ p "typeof" ast-unop boa ]]
+                     | "void" Unary:p                   => [[ p "void" ast-unop boa ]]
+                     | "delete" Unary:p                 => [[ p "delete" ast-unop boa ]]
+                     | Postfix
+Postfix            =   PrimExpr:p SpacesNoNl "++"       => [[ p "++" ast-postop boa ]]
+                     | PrimExpr:p SpacesNoNl "--"       => [[ p "--" ast-postop boa ]]
+                     | PrimExpr
+Args               =   (Expr ("," Expr => [[ second ]])* => [[ first2 swap prefix ]])?
+PrimExpr           =   PrimExpr:p "[" Expr:i "]"             => [[ i p ast-getp boa ]]
+                     | PrimExpr:p "." Name:m "(" Args:as ")" => [[ m p as ast-send boa ]]
+                     | PrimExpr:p "." Name:f                 => [[ f p ast-getp boa ]]
+                     | PrimExpr:p "(" Args:as ")"            => [[ p as ast-call boa ]]
+                     | PrimExprHd
+PrimExprHd         =   "(" Expr:e ")"                        => [[ e ]]
+                     | "this"                                => [[ ast-this boa ]]
+                     | Name                                  => [[ ast-get boa ]]
+                     | Number
+                     | String
+                     | RegExp
+                     | "function" FuncRest:fr                => [[ fr ]]
+                     | "new" PrimExpr:n "(" Args:as ")"      => [[ n as ast-new boa ]]
+                     | "new" PrimExpr:n                      => [[ n f  ast-new boa ]]
+                     | "[" Args:es "]"                       => [[ es ast-array boa ]]
+                     | Json
+JsonBindings       = (JsonBinding ("," JsonBinding => [[ second ]])* => [[ first2 swap prefix ]])?
+Json               = "{" JsonBindings:bs "}"                  => [[ bs ast-json boa ]]
+JsonBinding        = JsonPropName:n ":" Expr:v               => [[ n v ast-binding boa ]]
+JsonPropName       = Name | Number | String | RegExp
+Formal             = Spaces Name
+Formals            = (Formal ("," Formal => [[ second ]])*  => [[ first2 swap prefix ]])?
+FuncRest           = "(" Formals:fs ")" "{" SrcElems:body "}" => [[ fs body ast-func boa ]]
+Sc                 = SpacesNoNl (nl | &("}") | End)| ";"
+Binding            =   Name:n "=" Expr:v                      => [[ n v ast-var boa ]]
+                     | Name:n                                 => [[ n "undefined" ast-get boa ast-var boa ]]
+Block              = "{" SrcElems:ss "}"                      => [[ ss ]]
+Bindings           = (Binding ("," Binding => [[ second ]])* => [[ first2 swap prefix ]])?
+For1               =   "var" Bindings => [[ second ]] 
+                     | ExprNoIn 
+                     | Spaces => [[ "undefined" ast-get boa ]] 
+For2               =   Expr
+                     | Spaces => [[ "true" ast-get boa ]] 
+For3               =   Expr
+                     | Spaces => [[ "undefined" ast-get boa ]] 
+ForIn1             =   "var" Name:n => [[ n "undefined" ast-get boa ast-var boa ]]
+                     | PrimExprHd
+Switch1            =   "case" Expr:c ":" SrcElems:cs => [[ c cs ast-case boa ]]
+                     | "default" ":" SrcElems:cs => [[ cs ast-default boa ]]  
+SwitchBody         = Switch1*
+Finally            =   "finally" Block:b => [[ b ]]
+                     | Spaces => [[ "undefined" ast-get boa ]]
+Stmt               =   Block
+                     | "var" Bindings:bs Sc                   => [[ bs ast-begin boa ]]
+                     | "if" "(" Expr:c ")" Stmt:t "else" Stmt:f => [[ c t f ast-if boa ]]
+                     | "if" "(" Expr:c ")" Stmt:t               => [[ c t "undefined" ast-get boa ast-if boa ]]
+                     | "while" "(" Expr:c ")" Stmt:s            => [[ c s ast-while boa ]]
+                     | "do" Stmt:s "while" "(" Expr:c ")" Sc    => [[ s c ast-do-while boa ]]
+                     | "for" "(" For1:i ";" For2:c ";" For3:u ")" Stmt:s => [[ i c u s ast-for boa ]]
+                     | "for" "(" ForIn1:v "in" Expr:e ")" Stmt:s => [[ v e s ast-for-in boa ]]
+                     | "switch" "(" Expr:e ")" "{" SwitchBody:cs "}" => [[ e cs ast-switch boa ]]
+                     | "break" Sc                                    => [[ ast-break boa ]]
+                     | "continue" Sc                                 => [[ ast-continue boa ]]
+                     | "throw" SpacesNoNl Expr:e Sc                  => [[ e ast-throw boa ]]
+                     | "try" Block:t "catch" "(" Name:e ")" Block:c Finally:f => [[ t e c f ast-try boa ]]
+                     | "return" Expr:e Sc                            => [[ e ast-return boa ]]
+                     | "return" Sc                                   => [[ "undefined" ast-get boa ast-return boa ]]
+                     | "with" "(" Expr:e ")" Stmt:b                  => [[ e b ast-with boa ]]
+                     | Expr:e Sc                                     => [[ e ]]
+                     | ";"                                           => [[ "undefined" ast-get boa ]]
+SrcElem            =   "function" Name:n FuncRest:f                  => [[ n f ast-var boa ]]
+                     | Stmt
+SrcElems           = SrcElem*                                      => [[ ast-begin boa ]]
+TopLevel           = SrcElems Spaces Comment
+]=]
diff --git a/extra/peg/javascript/parser/authors.txt b/extra/peg/javascript/parser/authors.txt
deleted file mode 100644 (file)
index 44b06f9..0000000
+++ /dev/null
@@ -1 +0,0 @@
-Chris Double
diff --git a/extra/peg/javascript/parser/parser-tests.factor b/extra/peg/javascript/parser/parser-tests.factor
deleted file mode 100644 (file)
index 7bde029..0000000
+++ /dev/null
@@ -1,52 +0,0 @@
-! Copyright (C) 2008 Chris Double.
-! See http://factorcode.org/license.txt for BSD license.
-
-USING: kernel tools.test peg peg.javascript.ast
-peg.javascript.parser accessors sequences math peg.ebnf
-peg.ebnf.private ;
-
-{
-  T{
-      ast-begin
-      f
-      V{
-          T{ ast-number f 123 }
-          T{ ast-string f "hello" }
-          T{
-              ast-call
-              f
-              T{ ast-get f "foo" }
-              V{ T{ ast-get f "x" } }
-          }
-      }
-  }
-} [
-  "123; 'hello'; foo(x);" javascript
-] unit-test
-
-{ t } [
-"
-var x=5
-var y=10
-" main \ javascript rule (parse) remaining>> length zero?
-] unit-test
-
-
-{ t } [
-"
-function foldl(f, initial, seq) {
-   for(var i=0; i< seq.length; ++i)
-     initial = f(initial, seq[i]);
-   return initial;
-}" main \ javascript rule (parse) remaining>> length zero?
-] unit-test
-
-{ t } [
-"
-ParseState.prototype.from = function(index) {
-    var r = new ParseState(this.input, this.index + index);
-    r.cache = this.cache;
-    r.length = this.length - index;
-    return r;
-}" main \ javascript rule (parse) remaining>> length zero?
-] unit-test
diff --git a/extra/peg/javascript/parser/parser.factor b/extra/peg/javascript/parser/parser.factor
deleted file mode 100644 (file)
index 32cdd16..0000000
+++ /dev/null
@@ -1,200 +0,0 @@
-! Copyright (C) 2008 Chris Double.
-! See http://factorcode.org/license.txt for BSD license.
-USING: kernel accessors sequences multiline
-peg peg.ebnf peg.javascript.ast peg.javascript.tokenizer ;
-IN: peg.javascript.parser
-
-! Grammar for JavaScript. Based on OMeta-JS example from:
-! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler
-
-! The interesting thing about this parser is the mixing of
-! a default and non-default tokenizer. The JavaScript tokenizer
-! removes all newlines. So when operating on tokens there is no
-! need for newline and space skipping in the grammar. But JavaScript
-! uses the newline in the 'automatic semicolon insertion' rule.
-!
-! If a statement ends in a newline, sometimes the semicolon can be
-! skipped. So we define an 'nl' rule using the default tokenizer.
-! This operates a character at a time. Using this 'nl' in the parser
-! allows us to detect newlines when we need to for the semicolon
-! insertion rule, but ignore it in all other places.
-EBNF: javascript [=[
-tokenizer         = default
-nl                = "\r\n" | "\n"
-
-tokenizer         = <foreign tokenize-javascript Tok>
-End               = !(.)
-Space             = [ \t\n]
-Spaces            = Space* => [[ ignore ]]
-Name               = . ?[ ast-name?   ]?   => [[ value>> ]]
-Number             = . ?[ ast-number? ]?
-String             = . ?[ ast-string? ]?
-RegExp             = . ?[ ast-regexp? ]?
-SpacesNoNl         = (!(nl) Space)* => [[ ignore ]]
-
-Expr               =   OrExpr:e "?" Expr:t ":" Expr:f   => [[ e t f ast-cond-expr boa ]]
-                     | OrExpr:e "=" Expr:rhs            => [[ e rhs ast-set boa ]]
-                     | OrExpr:e "+=" Expr:rhs           => [[ e rhs "+" ast-mset boa ]]
-                     | OrExpr:e "-=" Expr:rhs           => [[ e rhs "-" ast-mset boa ]]
-                     | OrExpr:e "*=" Expr:rhs           => [[ e rhs "*" ast-mset boa ]]
-                     | OrExpr:e "/=" Expr:rhs           => [[ e rhs "/" ast-mset boa ]]
-                     | OrExpr:e "%=" Expr:rhs           => [[ e rhs "%" ast-mset boa ]]
-                     | OrExpr:e "&&=" Expr:rhs          => [[ e rhs "&&" ast-mset boa ]]
-                     | OrExpr:e "||=" Expr:rhs          => [[ e rhs "||" ast-mset boa ]]
-                     | OrExpr:e "^=" Expr:rhs           => [[ e rhs "^" ast-mset boa ]]
-                     | OrExpr:e "&=" Expr:rhs           => [[ e rhs "&" ast-mset boa ]]
-                     | OrExpr:e "|=" Expr:rhs           => [[ e rhs "|" ast-mset boa ]]
-                     | OrExpr:e "<<=" Expr:rhs          => [[ e rhs "<<" ast-mset boa ]]
-                     | OrExpr:e ">>=" Expr:rhs          => [[ e rhs ">>" ast-mset boa ]]
-                     | OrExpr:e ">>>=" Expr:rhs         => [[ e rhs ">>>" ast-mset boa ]]
-                     | OrExpr:e                         => [[ e ]]
-
-ExprNoIn           =   OrExprNoIn:e "?" ExprNoIn:t ":" ExprNoIn:f => [[ e t f ast-cond-expr boa ]]
-                     | OrExprNoIn:e "=" ExprNoIn:rhs              => [[ e rhs ast-set boa ]]
-                     | OrExprNoIn:e "+=" ExprNoIn:rhs             => [[ e rhs "+" ast-mset boa ]]
-                     | OrExprNoIn:e "-=" ExprNoIn:rhs             => [[ e rhs "-" ast-mset boa ]]
-                     | OrExprNoIn:e "*=" ExprNoIn:rhs             => [[ e rhs "*" ast-mset boa ]]
-                     | OrExprNoIn:e "/=" ExprNoIn:rhs             => [[ e rhs "/" ast-mset boa ]]
-                     | OrExprNoIn:e "%=" ExprNoIn:rhs             => [[ e rhs "%" ast-mset boa ]]
-                     | OrExprNoIn:e "&&=" ExprNoIn:rhs            => [[ e rhs "&&" ast-mset boa ]]
-                     | OrExprNoIn:e "||=" ExprNoIn:rhs            => [[ e rhs "||" ast-mset boa ]]
-                     | OrExprNoIn:e "^=" ExprNoIn:rhs             => [[ e rhs "^" ast-mset boa ]]
-                     | OrExprNoIn:e "&=" ExprNoIn:rhs             => [[ e rhs "&" ast-mset boa ]]
-                     | OrExprNoIn:e "|=" ExprNoIn:rhs             => [[ e rhs "|" ast-mset boa ]]
-                     | OrExprNoIn:e "<<=" ExprNoIn:rhs            => [[ e rhs "<<" ast-mset boa ]]
-                     | OrExprNoIn:e ">>=" ExprNoIn:rhs            => [[ e rhs ">>" ast-mset boa ]]
-                     | OrExprNoIn:e ">>>=" ExprNoIn:rhs           => [[ e rhs ">>>" ast-mset boa ]]
-                     | OrExprNoIn:e                               => [[ e ]]
-
-OrExpr             =   OrExpr:x "||" AndExpr:y          => [[ x y "||" ast-binop boa ]]
-                     | AndExpr
-OrExprNoIn         =   OrExprNoIn:x "||" AndExprNoIn:y  => [[ x y "||" ast-binop boa ]]
-                     | AndExprNoIn
-AndExpr            =   AndExpr:x "&&" BitOrExpr:y       => [[ x y "&&" ast-binop boa ]]
-                     | BitOrExpr
-AndExprNoIn        =   AndExprNoIn:x "&&" BitOrExprNoIn:y => [[ x y "&&" ast-binop boa ]]
-                     | BitOrExprNoIn
-BitOrExpr          =   BitOrExpr:x "|" BitXORExpr:y     => [[ x y "|" ast-binop boa ]]
-                     | BitXORExpr
-BitOrExprNoIn      =   BitOrExprNoIn:x "|" BitXORExprNoIn:y => [[ x y "|" ast-binop boa ]]
-                     | BitXORExprNoIn
-BitXORExpr         =   BitXORExpr:x "^" BitANDExpr:y    => [[ x y "^" ast-binop boa ]]
-                     | BitANDExpr
-BitXORExprNoIn     =   BitXORExprNoIn:x "^" BitANDExprNoIn:y => [[ x y "^" ast-binop boa ]]
-                     | BitANDExprNoIn
-BitANDExpr         =   BitANDExpr:x "&" EqExpr:y        => [[ x y "&" ast-binop boa ]]
-                     | EqExpr
-BitANDExprNoIn     =   BitANDExprNoIn:x "&" EqExprNoIn:y => [[ x y "&" ast-binop boa ]]
-                     | EqExprNoIn
-EqExpr             =   EqExpr:x "==" RelExpr:y          => [[ x y "==" ast-binop boa ]]
-                     | EqExpr:x "!=" RelExpr:y          => [[ x y "!=" ast-binop boa ]]
-                     | EqExpr:x "===" RelExpr:y         => [[ x y "===" ast-binop boa ]]
-                     | EqExpr:x "!==" RelExpr:y         => [[ x y "!==" ast-binop boa ]]
-                     | RelExpr
-EqExprNoIn         =   EqExprNoIn:x "==" RelExprNoIn:y    => [[ x y "==" ast-binop boa ]]
-                     | EqExprNoIn:x "!=" RelExprNoIn:y    => [[ x y "!=" ast-binop boa ]]
-                     | EqExprNoIn:x "===" RelExprNoIn:y   => [[ x y "===" ast-binop boa ]]
-                     | EqExprNoIn:x "!==" RelExprNoIn:y   => [[ x y "!==" ast-binop boa ]]
-                     | RelExprNoIn
-RelExpr            =   RelExpr:x ">" ShiftExpr:y          => [[ x y ">" ast-binop boa ]]
-                     | RelExpr:x ">=" ShiftExpr:y         => [[ x y ">=" ast-binop boa ]]
-                     | RelExpr:x "<" ShiftExpr:y          => [[ x y "<" ast-binop boa ]]
-                     | RelExpr:x "<=" ShiftExpr:y         => [[ x y "<=" ast-binop boa ]]
-                     | RelExpr:x "instanceof" ShiftExpr:y => [[ x y "instanceof" ast-binop boa ]]
-                     | RelExpr:x "in" ShiftExpr:y         => [[ x y "in" ast-binop boa ]]
-                     | ShiftExpr
-RelExprNoIn        =   RelExprNoIn:x ">" ShiftExpr:y          => [[ x y ">" ast-binop boa ]]
-                     | RelExprNoIn:x ">=" ShiftExpr:y         => [[ x y ">=" ast-binop boa ]]
-                     | RelExprNoIn:x "<" ShiftExpr:y          => [[ x y "<" ast-binop boa ]]
-                     | RelExprNoIn:x "<=" ShiftExpr:y         => [[ x y "<=" ast-binop boa ]]
-                     | RelExprNoIn:x "instanceof" ShiftExpr:y => [[ x y "instanceof" ast-binop boa ]]
-                     | ShiftExpr
-ShiftExpr          =   ShiftExpr:x "<<" AddExpr:y       => [[ x y "<<" ast-binop boa ]]
-                     | ShiftExpr:x ">>>" AddExpr:y      => [[ x y ">>>" ast-binop boa ]]
-                     | ShiftExpr:x ">>" AddExpr:y       => [[ x y ">>" ast-binop boa ]]
-                     | AddExpr
-AddExpr            =   AddExpr:x "+" MulExpr:y          => [[ x y "+" ast-binop boa ]]
-                     | AddExpr:x "-" MulExpr:y          => [[ x y "-" ast-binop boa ]]
-                     | MulExpr
-MulExpr            =   MulExpr:x "*" Unary:y            => [[ x y "*" ast-binop boa ]]
-                     | MulExpr:x "/" Unary:y            => [[ x y "/" ast-binop boa ]]
-                     | MulExpr:x "%" Unary:y            => [[ x y "%" ast-binop boa ]]
-                     | Unary
-Unary              =   "-" Unary:p                      => [[ p "-" ast-unop boa ]]
-                     | "+" Unary:p                      => [[ p ]]
-                     | "++" Unary:p                     => [[ p "++" ast-preop boa ]]
-                     | "--" Unary:p                     => [[ p "--" ast-preop boa ]]
-                     | "!" Unary:p                      => [[ p "!" ast-unop boa ]]
-                     | "typeof" Unary:p                 => [[ p "typeof" ast-unop boa ]]
-                     | "void" Unary:p                   => [[ p "void" ast-unop boa ]]
-                     | "delete" Unary:p                 => [[ p "delete" ast-unop boa ]]
-                     | Postfix
-Postfix            =   PrimExpr:p SpacesNoNl "++"       => [[ p "++" ast-postop boa ]]
-                     | PrimExpr:p SpacesNoNl "--"       => [[ p "--" ast-postop boa ]]
-                     | PrimExpr
-Args               =   (Expr ("," Expr => [[ second ]])* => [[ first2 swap prefix ]])?
-PrimExpr           =   PrimExpr:p "[" Expr:i "]"             => [[ i p ast-getp boa ]]
-                     | PrimExpr:p "." Name:m "(" Args:as ")" => [[ m p as ast-send boa ]]
-                     | PrimExpr:p "." Name:f                 => [[ f p ast-getp boa ]]
-                     | PrimExpr:p "(" Args:as ")"            => [[ p as ast-call boa ]]
-                     | PrimExprHd
-PrimExprHd         =   "(" Expr:e ")"                        => [[ e ]]
-                     | "this"                                => [[ ast-this boa ]]
-                     | Name                                  => [[ ast-get boa ]]
-                     | Number
-                     | String
-                     | RegExp
-                     | "function" FuncRest:fr                => [[ fr ]]
-                     | "new" PrimExpr:n "(" Args:as ")"      => [[ n as ast-new boa ]]
-                     | "new" PrimExpr:n                      => [[ n f  ast-new boa ]]
-                     | "[" Args:es "]"                       => [[ es ast-array boa ]]
-                     | Json
-JsonBindings       = (JsonBinding ("," JsonBinding => [[ second ]])* => [[ first2 swap prefix ]])?
-Json               = "{" JsonBindings:bs "}"                  => [[ bs ast-json boa ]]
-JsonBinding        = JsonPropName:n ":" Expr:v               => [[ n v ast-binding boa ]]
-JsonPropName       = Name | Number | String | RegExp
-Formal             = Spaces Name
-Formals            = (Formal ("," Formal => [[ second ]])*  => [[ first2 swap prefix ]])?
-FuncRest           = "(" Formals:fs ")" "{" SrcElems:body "}" => [[ fs body ast-func boa ]]
-Sc                 = SpacesNoNl (nl | &("}") | End)| ";"
-Binding            =   Name:n "=" Expr:v                      => [[ n v ast-var boa ]]
-                     | Name:n                                 => [[ n "undefined" ast-get boa ast-var boa ]]
-Block              = "{" SrcElems:ss "}"                      => [[ ss ]]
-Bindings           = (Binding ("," Binding => [[ second ]])* => [[ first2 swap prefix ]])?
-For1               =   "var" Bindings => [[ second ]] 
-                     | ExprNoIn 
-                     | Spaces => [[ "undefined" ast-get boa ]] 
-For2               =   Expr
-                     | Spaces => [[ "true" ast-get boa ]] 
-For3               =   Expr
-                     | Spaces => [[ "undefined" ast-get boa ]] 
-ForIn1             =   "var" Name:n => [[ n "undefined" ast-get boa ast-var boa ]]
-                     | PrimExprHd
-Switch1            =   "case" Expr:c ":" SrcElems:cs => [[ c cs ast-case boa ]]
-                     | "default" ":" SrcElems:cs => [[ cs ast-default boa ]]  
-SwitchBody         = Switch1*
-Finally            =   "finally" Block:b => [[ b ]]
-                     | Spaces => [[ "undefined" ast-get boa ]]
-Stmt               =   Block
-                     | "var" Bindings:bs Sc                   => [[ bs ast-begin boa ]]
-                     | "if" "(" Expr:c ")" Stmt:t "else" Stmt:f => [[ c t f ast-if boa ]]
-                     | "if" "(" Expr:c ")" Stmt:t               => [[ c t "undefined" ast-get boa ast-if boa ]]
-                     | "while" "(" Expr:c ")" Stmt:s            => [[ c s ast-while boa ]]
-                     | "do" Stmt:s "while" "(" Expr:c ")" Sc    => [[ s c ast-do-while boa ]]
-                     | "for" "(" For1:i ";" For2:c ";" For3:u ")" Stmt:s => [[ i c u s ast-for boa ]]
-                     | "for" "(" ForIn1:v "in" Expr:e ")" Stmt:s => [[ v e s ast-for-in boa ]]
-                     | "switch" "(" Expr:e ")" "{" SwitchBody:cs "}" => [[ e cs ast-switch boa ]]
-                     | "break" Sc                                    => [[ ast-break boa ]]
-                     | "continue" Sc                                 => [[ ast-continue boa ]]
-                     | "throw" SpacesNoNl Expr:e Sc                  => [[ e ast-throw boa ]]
-                     | "try" Block:t "catch" "(" Name:e ")" Block:c Finally:f => [[ t e c f ast-try boa ]]
-                     | "return" Expr:e Sc                            => [[ e ast-return boa ]]
-                     | "return" Sc                                   => [[ "undefined" ast-get boa ast-return boa ]]
-                     | "with" "(" Expr:e ")" Stmt:b                  => [[ e b ast-with boa ]]
-                     | Expr:e Sc                                     => [[ e ]]
-                     | ";"                                           => [[ "undefined" ast-get boa ]]
-SrcElem            =   "function" Name:n FuncRest:f                  => [[ n f ast-var boa ]]
-                     | Stmt
-SrcElems           = SrcElem*                                      => [[ ast-begin boa ]]
-TopLevel           = SrcElems Spaces
-]=]
diff --git a/extra/peg/javascript/parser/summary.txt b/extra/peg/javascript/parser/summary.txt
deleted file mode 100644 (file)
index bae5a46..0000000
+++ /dev/null
@@ -1 +0,0 @@
-JavaScript Parser
diff --git a/extra/peg/javascript/parser/tags.txt b/extra/peg/javascript/parser/tags.txt
deleted file mode 100644 (file)
index 643ffaa..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-javascript
-parsing
-languages
index 12f092dcf78ab933a553d69f8e68c0ef12dec241..bae5a461d29775ba3f914fa04723fdf67cbd3a1f 100644 (file)
@@ -1 +1 @@
-JavaScript parser
+JavaScript Parser
diff --git a/extra/peg/javascript/tokenizer/authors.txt b/extra/peg/javascript/tokenizer/authors.txt
deleted file mode 100644 (file)
index 44b06f9..0000000
+++ /dev/null
@@ -1 +0,0 @@
-Chris Double
diff --git a/extra/peg/javascript/tokenizer/summary.txt b/extra/peg/javascript/tokenizer/summary.txt
deleted file mode 100644 (file)
index ce94386..0000000
+++ /dev/null
@@ -1 +0,0 @@
-Tokenizer for JavaScript language
diff --git a/extra/peg/javascript/tokenizer/tags.txt b/extra/peg/javascript/tokenizer/tags.txt
deleted file mode 100644 (file)
index 643ffaa..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-javascript
-parsing
-languages
diff --git a/extra/peg/javascript/tokenizer/tokenizer-tests.factor b/extra/peg/javascript/tokenizer/tokenizer-tests.factor
deleted file mode 100644 (file)
index 4490702..0000000
+++ /dev/null
@@ -1,37 +0,0 @@
-! Copyright (C) 2008 Chris Double.
-! See http://factorcode.org/license.txt for BSD license.
-
-USING: kernel tools.test peg peg.javascript.ast
-peg.javascript.tokenizer accessors ;
-
-{
-  V{
-    T{ ast-number f 123 }
-    ";"
-    T{ ast-string f "hello" }
-    ";"
-    T{ ast-name f "foo" }
-    "("
-    T{ ast-name f "x" }
-    ")"
-    ";"
-  }
-} [
-  "123; 'hello'; foo(x);" tokenize-javascript
-] unit-test
-
-{ V{ T{ ast-regexp f "<(w+)[^>]*?)/>" "g" } } } [
-  "/<(\\w+)[^>]*?)\\/>/g" tokenize-javascript
-] unit-test
-
-{
-    V{ T{ ast-string { value "abc\"def\"" } } }
-} [ "\"abc\\\"def\\\"\"" tokenize-javascript ] unit-test
-
-{
-    V{ T{ ast-string { value "\b\f\n\r\t\v'\"\\" } } }
-} [ "\"\\b\\f\\n\\r\\t\\v\\'\\\"\\\\\"" tokenize-javascript ] unit-test
-
-{
-    V{ T{ ast-string { value "abc" } } }
-} [ "\"\\x61\\u0062\\u{63}\"" tokenize-javascript ] unit-test
diff --git a/extra/peg/javascript/tokenizer/tokenizer.factor b/extra/peg/javascript/tokenizer/tokenizer.factor
deleted file mode 100644 (file)
index 1cb7279..0000000
+++ /dev/null
@@ -1,91 +0,0 @@
-! Copyright (C) 2008 Chris Double.
-! See http://factorcode.org/license.txt for BSD license.
-USING: kernel sequences strings arrays math.parser peg peg.ebnf
-peg.javascript.ast multiline ;
-IN: peg.javascript.tokenizer
-
-! Grammar for JavaScript. Based on OMeta-JS example from:
-! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler
-
-USE: prettyprint
-
-EBNF: tokenize-javascript [=[
-Letter            = [a-zA-Z]
-Digit             = [0-9]
-Digits            = Digit+
-SingleLineComment = "//" (!("\n") .)* "\n" => [[ ignore ]]
-MultiLineComment  = "/*" (!("*/") .)* "*/" => [[ ignore ]]
-Space             = [ \t\r\n] | SingleLineComment | MultiLineComment
-Spaces            = Space* => [[ ignore ]]
-NameFirst         = Letter | "$" => [[ CHAR: $ ]] | "_" => [[ CHAR: _ ]]
-NameRest          = NameFirst | Digit
-iName             = NameFirst NameRest* => [[ first2 swap prefix >string ]]
-Keyword           =  ("break"
-                    | "case"
-                    | "catch"
-                    | "continue"
-                    | "default"
-                    | "delete"
-                    | "do"
-                    | "else"
-                    | "finally"
-                    | "for"
-                    | "function"
-                    | "if"
-                    | "in"
-                    | "instanceof"
-                    | "new"
-                    | "return"
-                    | "switch"
-                    | "this"
-                    | "throw"
-                    | "try"
-                    | "typeof"
-                    | "var"
-                    | "void"
-                    | "while"
-                    | "with") !(NameRest)
-Name              = !(Keyword) iName  => [[ ast-name boa ]]
-Number            =   Digits:ws '.' Digits:fs => [[ ws "." fs 3array "" concat-as string>number ast-number boa ]]
-                    | Digits => [[ >string string>number ast-number boa ]]
-
-SingleEscape      =   "b"  => [[ CHAR: \b ]]
-                    | "f"  => [[ CHAR: \f ]]
-                    | "n"  => [[ CHAR: \n ]]
-                    | "r"  => [[ CHAR: \r ]]
-                    | "t"  => [[ CHAR: \t ]]
-                    | "v"  => [[ CHAR: \v ]]
-                    | "'"  => [[ CHAR: '  ]]
-                    | "\"" => [[ CHAR: \"  ]]
-                    | "\\" => [[ CHAR: \\ ]]
-HexDigit          = [0-9a-fA-F]
-HexEscape         = "x" (HexDigit HexDigit):d => [[ d hex> ]]
-UnicodeEscape     = "u" (HexDigit HexDigit HexDigit HexDigit):d => [[ d hex> ]]
-                    | "u{" HexDigit+:d "}" => [[ d hex> ]]
-EscapeChar         = "\\" (SingleEscape | HexEscape | UnicodeEscape):c => [[ c ]]
-StringChars1       = (EscapeChar | !('"""') .)* => [[ >string ]]
-StringChars2       = (EscapeChar | !('"') .)* => [[ >string ]]
-StringChars3       = (EscapeChar | !("'") .)* => [[ >string ]]
-Str                =   '"""' StringChars1:cs '"""' => [[ cs ast-string boa ]]
-                     | '"' StringChars2:cs '"' => [[ cs ast-string boa ]]
-                     | "'" StringChars3:cs "'" => [[ cs ast-string boa ]]
-RegExpFlags        = NameRest* => [[ >string ]]
-NonTerminator      = !([\n\r]) .
-BackslashSequence  = "\\" NonTerminator => [[ second ]]
-RegExpFirstChar    =   !([*\\/]) NonTerminator
-                     | BackslashSequence
-RegExpChar         =   !([\\/]) NonTerminator
-                     | BackslashSequence
-RegExpChars        = RegExpChar*
-RegExpBody         = RegExpFirstChar RegExpChars => [[ first2 swap prefix >string ]]
-RegExp             = "/" RegExpBody:b "/" RegExpFlags:fl => [[ b fl ast-regexp boa ]]
-Special            =   "("    | ")"   | "{"   | "}"   | "["   | "]"   | ","   | ";"
-                     | "?"    | ":"   | "!==" | "!="  | "===" | "=="  | "="   | ">="
-                     | ">>>=" | ">>>" | ">>=" | ">>"  | ">"   | "<="  | "<<=" | "<<"
-                     | "<"    | "++"  | "+="  | "+"   | "--"  | "-="  | "-"   | "*="
-                     | "*"    | "/="  | "/"   | "%="  | "%"   | "&&=" | "&&"  | "||="
-                     | "||"   | "."   | "!"   | "&="  | "&"   | "|="  | "|"   | "^="
-                     | "^"
-Tok                = Spaces (Name | Keyword | Number | Str | RegExp | Special )
-Toks               = Tok* Spaces
-]=]