]> gitweb.factorcode.org Git - factor.git/commitdiff
Refactor JavaScript parser
authorChris Double <chris@bethia.(none)>
Wed, 18 Jun 2008 12:42:11 +0000 (00:42 +1200)
committerChris Double <chris@bethia.(none)>
Wed, 18 Jun 2008 12:42:11 +0000 (00:42 +1200)
20 files changed:
extra/peg/javascript/ast/ast.factor [new file with mode: 0644]
extra/peg/javascript/ast/authors.txt [new file with mode: 0644]
extra/peg/javascript/ast/summary.txt [new file with mode: 0644]
extra/peg/javascript/ast/tags.txt [new file with mode: 0644]
extra/peg/javascript/authors.txt [new file with mode: 0644]
extra/peg/javascript/javascript-docs.factor [new file with mode: 0644]
extra/peg/javascript/javascript-tests.factor
extra/peg/javascript/javascript.factor
extra/peg/javascript/parser/authors.txt [new file with mode: 0644]
extra/peg/javascript/parser/parser-tests.factor [new file with mode: 0644]
extra/peg/javascript/parser/parser.factor [new file with mode: 0644]
extra/peg/javascript/parser/summary.txt [new file with mode: 0644]
extra/peg/javascript/parser/tags.txt [new file with mode: 0644]
extra/peg/javascript/summary.txt [new file with mode: 0644]
extra/peg/javascript/tags.txt [new file with mode: 0644]
extra/peg/javascript/tokenizer/authors.txt [new file with mode: 0644]
extra/peg/javascript/tokenizer/summary.txt [new file with mode: 0644]
extra/peg/javascript/tokenizer/tags.txt [new file with mode: 0644]
extra/peg/javascript/tokenizer/tokenizer-tests.factor [new file with mode: 0644]
extra/peg/javascript/tokenizer/tokenizer.factor [new file with mode: 0644]

diff --git a/extra/peg/javascript/ast/ast.factor b/extra/peg/javascript/ast/ast.factor
new file mode 100644 (file)
index 0000000..b857dc5
--- /dev/null
@@ -0,0 +1,42 @@
+! 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 value ;
+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-case c cs ;
+TUPLE: ast-default cs ;
diff --git a/extra/peg/javascript/ast/authors.txt b/extra/peg/javascript/ast/authors.txt
new file mode 100644 (file)
index 0000000..44b06f9
--- /dev/null
@@ -0,0 +1 @@
+Chris Double
diff --git a/extra/peg/javascript/ast/summary.txt b/extra/peg/javascript/ast/summary.txt
new file mode 100644 (file)
index 0000000..543a2e6
--- /dev/null
@@ -0,0 +1 @@
+Abstract Syntax Tree for JavaScript parser
diff --git a/extra/peg/javascript/ast/tags.txt b/extra/peg/javascript/ast/tags.txt
new file mode 100644 (file)
index 0000000..c2aac29
--- /dev/null
@@ -0,0 +1,3 @@
+text
+javascript
+parsing
diff --git a/extra/peg/javascript/authors.txt b/extra/peg/javascript/authors.txt
new file mode 100644 (file)
index 0000000..44b06f9
--- /dev/null
@@ -0,0 +1 @@
+Chris Double
diff --git a/extra/peg/javascript/javascript-docs.factor b/extra/peg/javascript/javascript-docs.factor
new file mode 100644 (file)
index 0000000..5fdc3e8
--- /dev/null
@@ -0,0 +1,14 @@
+! Copyright (C) 2007 Chris Double.\r
+! See http://factorcode.org/license.txt for BSD license.\r
+USING: help.markup help.syntax ;\r
+IN: peg.javascript\r
+\r
+HELP: parse-javascript\r
+{ $values \r
+  { "string" "a string" } \r
+  { "ast" "a JavaScript abstract syntax tree" } \r
+}\r
+{ $description \r
+    "Parse the input string using the JavaScript parser. Throws an error if "\r
+    "the string does not contain valid JavaScript. Returns the abstract syntax tree "\r
+    "if successful." } ;\r
index 70410a38385279e57f87613bdf9631a0d52a1656..0d6899714d3e46204173bf953a6bbe279f721b4d 100644 (file)
@@ -1,42 +1,11 @@
 ! Copyright (C) 2008 Chris Double.
 ! See http://factorcode.org/license.txt for BSD license.
 !
-USING: kernel tools.test peg peg.javascript accessors ;
+USING: kernel tools.test peg.javascript peg.javascript.ast accessors ;
 IN: peg.javascript.tests
 
-\ javascript must-infer
+\ parse-javascript must-infer
 
-{
-  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);" tokenizer ast>>
-] 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);" tokenizer ast>> javascript ast>>
+{ T{ ast-begin f V{ T{ ast-number f 123 } } } } [
+  "123;" parse-javascript
 ] unit-test
\ No newline at end of file
index 127b13130a21fd3131e49a884cdc7a072dd81347..23a4b4f7f0682a7caea5700d775552f78faa363b 100644 (file)
 ! Copyright (C) 2008 Chris Double.
 ! See http://factorcode.org/license.txt for BSD license.
-USING: kernel arrays strings math.parser sequences sequences.deep
-peg peg.ebnf peg.parsers memoize namespaces math accessors ;
+USING: kernel accessors peg.javascript.tokenizer peg.javascript.parser ;
 IN: peg.javascript
 
-#! Grammar for JavaScript. Based on OMeta-JS example from:
-#! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler 
+: parse-javascript ( string -- ast )
+  tokenizer [
+    ast>> javascript [
+      ast>>
+    ] [
+      "Unable to parse JavaScript" throw
+    ] if*
+  ] [
+    "Unable to tokenize JavaScript" throw
+  ] if* ;
 
-USE: prettyprint
-
-TUPLE: ast-keyword value ;
-TUPLE: ast-name value ;
-TUPLE: ast-number value ;
-TUPLE: ast-string value ;
-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-case c cs ;
-TUPLE: ast-default cs ;
-
-EBNF: tokenizer 
-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 | "$" | "_"
-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") 
-Name              = !(Keyword) (iName):n => [[ n ast-name boa ]]
-Number            =   Digits:ws '.' Digits:fs => [[ ws "." fs 3array concat >string string>number ast-number boa ]]
-                    | Digits => [[ >string string>number ast-number boa ]]  
-
-EscapeChar        =   "\\n" => [[ 10 ]] 
-                    | "\\r" => [[ 13 ]]
-                    | "\\t" => [[ 9 ]]
-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 ]]
-Special            =   "("   | ")"   | "{"   | "}"   | "["   | "]"   | ","   | ";"
-                     | "?"   | ":"   | "!==" | "~="  | "===" | "=="  | "="   | ">="
-                     | ">"   | "<="  | "<"   | "++"  | "+="  | "+"   | "--"  | "-="
-                     | "-"   | "*="  | "*"   | "/="  | "/"   | "%="  | "%"   | "&&="
-                     | "&&"  | "||=" | "||"  | "."   | "!"
-Tok                = Spaces (Name | Keyword | Number | Str | Special )
-Toks               = Tok* Spaces 
-;EBNF
-
-EBNF: javascript
-Space             = " " | "\t" | "\n" 
-Spaces            = Space* => [[ ignore ]]
-Name               = . ?[ ast-name?   ]?   => [[ value>> ]] 
-Number             = . ?[ ast-number? ]?   => [[ value>> ]]
-String             = . ?[ ast-string? ]?   => [[ value>> ]]
-SpacesNoNl         = (!("\n") 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                         => [[ e ]]
-
-OrExpr             =   OrExpr:x "||" AndExpr:y          => [[ x y "||" ast-binop boa ]]
-                     | AndExpr
-AndExpr            =   AndExpr:x "&&" EqExpr:y          => [[ x y "&&" ast-binop boa ]]
-                     | EqExpr
-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
-RelExpr            =   RelExpr:x ">" AddExpr:y          => [[ x y ">" ast-binop boa ]]
-                     | RelExpr:x ">=" AddExpr:y         => [[ x y ">=" ast-binop boa ]]
-                     | RelExpr:x "<" AddExpr:y          => [[ x y "<" ast-binop boa ]]
-                     | RelExpr:x "<=" AddExpr:y         => [[ x y "<=" ast-binop boa ]]
-                     | RelExpr:x "instanceof" AddExpr:y => [[ x y "instanceof" 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 "*" MulExpr:y          => [[ x y "*" ast-binop boa ]]
-                     | MulExpr:x "/" MulExpr:y          => [[ x y "/" ast-binop boa ]]
-                     | MulExpr:x "%" MulExpr:y          => [[ x y "%" ast-binop boa ]]
-                     | Unary
-Unary              =   "-" Postfix:p                    => [[ p "-" ast-unop boa ]]
-                     | "+" Postfix:p                    => [[ p ]]
-                     | "++" Postfix:p                   => [[ p "++" ast-preop boa ]]
-                     | "--" Postfix:p                   => [[ p "--" ast-preop boa ]]
-                     | "!" Postfix:p                    => [[ p "!" 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                                => [[ ast-number boa ]]
-                     | String                                => [[ ast-string boa ]]
-                     | "function" FuncRest:fr                => [[ fr ]]
-                     | "new" Name:n "(" Args:as ")"          => [[ n as 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
-Formal             = Spaces Name
-Formals            = (Formal ("," Formal => [[ second ]])*  => [[ first2 swap prefix ]])?
-FuncRest           = "(" Formals:fs ")" "{" SrcElems:body "}" => [[ fs body ast-func boa ]]
-Sc                 = SpacesNoNl ("\n" | &("}"))| ";"
-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" Binding => [[ second ]] 
-                     | Expr 
-                     | 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 ]]
-                     | Expr
-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 ]]
-                     | 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                               
-;EBNF
\ No newline at end of file
diff --git a/extra/peg/javascript/parser/authors.txt b/extra/peg/javascript/parser/authors.txt
new file mode 100644 (file)
index 0000000..44b06f9
--- /dev/null
@@ -0,0 +1 @@
+Chris Double
diff --git a/extra/peg/javascript/parser/parser-tests.factor b/extra/peg/javascript/parser/parser-tests.factor
new file mode 100644 (file)
index 0000000..933d4cf
--- /dev/null
@@ -0,0 +1,27 @@
+! 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  
+       peg.javascript.parser accessors ;
+IN: peg.javascript.parser.tests
+
+\ javascript must-infer
+
+{
+  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);" tokenizer ast>> javascript ast>>
+] unit-test
\ No newline at end of file
diff --git a/extra/peg/javascript/parser/parser.factor b/extra/peg/javascript/parser/parser.factor
new file mode 100644 (file)
index 0000000..a38cf4a
--- /dev/null
@@ -0,0 +1,121 @@
+! Copyright (C) 2008 Chris Double.
+! See http://factorcode.org/license.txt for BSD license.
+USING: kernel accessors peg peg.ebnf peg.javascript.ast ;
+IN: peg.javascript.parser
+
+#! Grammar for JavaScript. Based on OMeta-JS example from:
+#! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler 
+
+EBNF: javascript
+Space             = " " | "\t" | "\n" 
+Spaces            = Space* => [[ ignore ]]
+Name               = . ?[ ast-name?   ]?   => [[ value>> ]] 
+Number             = . ?[ ast-number? ]?   => [[ value>> ]]
+String             = . ?[ ast-string? ]?   => [[ value>> ]]
+SpacesNoNl         = (!("\n") 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                         => [[ e ]]
+
+OrExpr             =   OrExpr:x "||" AndExpr:y          => [[ x y "||" ast-binop boa ]]
+                     | AndExpr
+AndExpr            =   AndExpr:x "&&" EqExpr:y          => [[ x y "&&" ast-binop boa ]]
+                     | EqExpr
+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
+RelExpr            =   RelExpr:x ">" AddExpr:y          => [[ x y ">" ast-binop boa ]]
+                     | RelExpr:x ">=" AddExpr:y         => [[ x y ">=" ast-binop boa ]]
+                     | RelExpr:x "<" AddExpr:y          => [[ x y "<" ast-binop boa ]]
+                     | RelExpr:x "<=" AddExpr:y         => [[ x y "<=" ast-binop boa ]]
+                     | RelExpr:x "instanceof" AddExpr:y => [[ x y "instanceof" 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 "*" MulExpr:y          => [[ x y "*" ast-binop boa ]]
+                     | MulExpr:x "/" MulExpr:y          => [[ x y "/" ast-binop boa ]]
+                     | MulExpr:x "%" MulExpr:y          => [[ x y "%" ast-binop boa ]]
+                     | Unary
+Unary              =   "-" Postfix:p                    => [[ p "-" ast-unop boa ]]
+                     | "+" Postfix:p                    => [[ p ]]
+                     | "++" Postfix:p                   => [[ p "++" ast-preop boa ]]
+                     | "--" Postfix:p                   => [[ p "--" ast-preop boa ]]
+                     | "!" Postfix:p                    => [[ p "!" 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                                => [[ ast-number boa ]]
+                     | String                                => [[ ast-string boa ]]
+                     | "function" FuncRest:fr                => [[ fr ]]
+                     | "new" Name:n "(" Args:as ")"          => [[ n as 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
+Formal             = Spaces Name
+Formals            = (Formal ("," Formal => [[ second ]])*  => [[ first2 swap prefix ]])?
+FuncRest           = "(" Formals:fs ")" "{" SrcElems:body "}" => [[ fs body ast-func boa ]]
+Sc                 = SpacesNoNl ("\n" | &("}"))| ";"
+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" Binding => [[ second ]] 
+                     | Expr 
+                     | 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 ]]
+                     | Expr
+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 ]]
+                     | 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                               
+;EBNF
\ No newline at end of file
diff --git a/extra/peg/javascript/parser/summary.txt b/extra/peg/javascript/parser/summary.txt
new file mode 100644 (file)
index 0000000..bae5a46
--- /dev/null
@@ -0,0 +1 @@
+JavaScript Parser
diff --git a/extra/peg/javascript/parser/tags.txt b/extra/peg/javascript/parser/tags.txt
new file mode 100644 (file)
index 0000000..c2aac29
--- /dev/null
@@ -0,0 +1,3 @@
+text
+javascript
+parsing
diff --git a/extra/peg/javascript/summary.txt b/extra/peg/javascript/summary.txt
new file mode 100644 (file)
index 0000000..12f092d
--- /dev/null
@@ -0,0 +1 @@
+JavaScript parser
diff --git a/extra/peg/javascript/tags.txt b/extra/peg/javascript/tags.txt
new file mode 100644 (file)
index 0000000..c2aac29
--- /dev/null
@@ -0,0 +1,3 @@
+text
+javascript
+parsing
diff --git a/extra/peg/javascript/tokenizer/authors.txt b/extra/peg/javascript/tokenizer/authors.txt
new file mode 100644 (file)
index 0000000..44b06f9
--- /dev/null
@@ -0,0 +1 @@
+Chris Double
diff --git a/extra/peg/javascript/tokenizer/summary.txt b/extra/peg/javascript/tokenizer/summary.txt
new file mode 100644 (file)
index 0000000..ce94386
--- /dev/null
@@ -0,0 +1 @@
+Tokenizer for JavaScript language
diff --git a/extra/peg/javascript/tokenizer/tags.txt b/extra/peg/javascript/tokenizer/tags.txt
new file mode 100644 (file)
index 0000000..c2aac29
--- /dev/null
@@ -0,0 +1,3 @@
+text
+javascript
+parsing
diff --git a/extra/peg/javascript/tokenizer/tokenizer-tests.factor b/extra/peg/javascript/tokenizer/tokenizer-tests.factor
new file mode 100644 (file)
index 0000000..1300b3c
--- /dev/null
@@ -0,0 +1,23 @@
+! 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 ;
+IN: peg.javascript.tokenizer.tests
+
+\ tokenizer must-infer
+
+{
+  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);" tokenizer ast>>
+] unit-test
diff --git a/extra/peg/javascript/tokenizer/tokenizer.factor b/extra/peg/javascript/tokenizer/tokenizer.factor
new file mode 100644 (file)
index 0000000..d62bb93
--- /dev/null
@@ -0,0 +1,68 @@
+! 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 ;
+IN: peg.javascript.tokenizer
+
+#! Grammar for JavaScript. Based on OMeta-JS example from:
+#! http://jarrett.cs.ucla.edu/ometa-js/#JavaScript_Compiler 
+
+EBNF: tokenizer 
+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 | "$" | "_"
+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") 
+Name              = !(Keyword) (iName):n => [[ n ast-name boa ]]
+Number            =   Digits:ws '.' Digits:fs => [[ ws "." fs 3array concat >string string>number ast-number boa ]]
+                    | Digits => [[ >string string>number ast-number boa ]]  
+
+EscapeChar        =   "\\n" => [[ 10 ]] 
+                    | "\\r" => [[ 13 ]]
+                    | "\\t" => [[ 9 ]]
+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 ]]
+RegExpBody         = (!("/" | "\n" | "\r") .)* => [[ >string ]]
+RegExp             = "/" RegExpBody:r "/" => [[ r ast-regexp boa ]]
+Special            =   "("   | ")"   | "{"   | "}"   | "["   | "]"   | ","   | ";"
+                     | "?"   | ":"   | "!==" | "~="  | "===" | "=="  | "="   | ">="
+                     | ">"   | "<="  | "<"   | "++"  | "+="  | "+"   | "--"  | "-="
+                     | "-"   | "*="  | "*"   | "/="  | "/"   | "%="  | "%"   | "&&="
+                     | "&&"  | "||=" | "||"  | "."   | "!"
+Tok                = Spaces (Name | Keyword | Number | Str | RegExp | Special )
+Toks               = Tok* Spaces 
+;EBNF
+