eXept Software AG Logo

Smalltalk/X Webserver

Documentation of class 'JavaScriptParser':

Home

Documentation
www.exept.de
Everywhere
for:
[back]

Class: JavaScriptParser


Inheritance:

   Object
   |
   +--Scanner
      |
      +--JavaScriptScanner
         |
         +--JavaScriptParser
            |
            +--JavaScriptCompiler
            |
            +--JavaScriptCompletionParser
            |
            +--JavaScriptSyntaxHighlighter

Package:
stx:libjavascript
Category:
Languages-JavaScript-Compiling & Parsing
Version:
rev: 1.395 date: 2024/02/09 12:34:09
user: stefan
file: JavaScriptParser.st directory: libjavascript
module: stx stc-classLibrary: libjavascript

Description:


reads JavaScript-like syntax, builds up an AST similar to the ST-AST.
Used for expecco, so be careful when changing.

copyright

COPYRIGHT (c) 1998 by eXept Software AG All Rights Reserved This software is furnished under a license and may be used only in accordance with the terms of that license and with the inclusion of the above copyright notice. This software may not be provided or otherwise made available to, or used by, any other person. No title to or ownership of the software is hereby transferred.

example1

a little script as it may be in a scriptfile

example2

|env val source| source := ' STXScriptingServer.errorDebugging(true); Stdout.showCR(''hello''); var filename; var verdict, result; filename = ''~/SuiteA.ets''; verdict = Expecco::ExpeccoAPI.executeTestsFromFile_filteredByName_filteredByTag_testIDList_verboseInfoHandler_parameterFile_reporter( filename, null, /* namefilter */ null, /* tagFilter */ null, /* id-list */ null, /* info handler */ null, /* parameter file */ (function (rslt) { result = rslt; }) /* reporter */ ); if (verdict.isSuccess) { alert(''ok''); } else { alert(''not ok''); } '. env := STXScriptingEnvironment new. val := JavaScriptParser new source:source readStream; evaluateDeclarationsFor:env. self assert:(env _localVariables at:#'filename') value = '~/SuiteA.ets'. self assert:(env _localVariables at:#'verdict') value isSuccess. (env _localVariables at:#'result') value inspect.

expression_examples

TestCase assert:(JavaScriptParser evaluate:'3*3') = 9 TestCase assert:(JavaScriptParser evaluate:'(8+7) % 13') = 2 TestCase assert:(JavaScriptParser evaluate:'(5*4) % 13') = 7 TestCase assert:(JavaScriptParser evaluate:'Math.floor(7/2)') = 3 (JavaScriptParser evaluate:'Stdout.showCR(''hello'')') TestCase assert:(JavaScriptParser evaluate:'Math.gcd(5,64)') = 1 (JavaScriptParser evaluate:'var x = { foo: ''hello'', bar:''world'' }; return x;' ) inspect

other_examples

<<END [exBegin] |env| env := JavaScriptEnvironment new. env _defineVariable:#UIMap value:(Expecco::SeleniumUIMap). JavaScriptParser evaluateDeclarationsFrom:'C:\Temp\selenium\ui_map_expecconet.js' asFilename readStream for:env. self halt. [exEnd] [exBegin] |env rslt1 rslt2| env := JavaScriptEnvironment new. env _defineVariable:#foo value:'abc'. env _defineVariable:#bar value:'def'. rslt1 := JavaScriptParser evaluate:' "this is foo: $(foo) and this is bar: $(bar)" ' in:env. rslt2 := JavaScriptParser evaluate:' `this is foo: $(foo) and this is bar: $(bar)` ' in:env. self halt. [exEnd] [exBegin] |dummyReceiver code mthd| code := ('C:\Temp\selenium\ui_map_expecconet.js' asFilename contentsAsString). Class nameSpaceQuerySignal answer:ExpeccoDummyNameSpaceForSeleniumScripts do:[ mthd := JavaScriptCompiler compile: ('doIt() { ',code ,' return(thisContext()); };') forClass:nil inCategory:nil notifying:nil install:false ]. dummyReceiver := JavaScriptObject new. mthd valueWithReceiver:dummyReceiver arguments:#() [exEnd] END>>"

Class protocol:

configuration
o  forInAllowed
do we allow for(var in expr) {...} ?

o  forOfAllowed
do we allow for(var of expr) {...} ?

evaluation
o  evaluate: aStringOrStream
evaluate a javaScript expression.
A new environment is created, where variables are defined.

Usage example(s):

     self evaluate:'1 + 2 * 3 + 4'

Usage example(s):

     self evaluate:'
if (1 > 2) {
    Transcript.showCR(1);
} else {
    Transcript.showCR(2);
}
'

Usage example(s):

     self evaluate:'
if (1 > 2) {
    Transcript.foo(1,2,3,4,5,6,7,8,9,10);
} else {
    Transcript.bar(1,2,3,4,5,6,7,8,9,10);
}
'

Usage example(s):

     self evaluate:'
if (1 > 2) {
    Transcript.show(hello);
} else {
    Transcript.show(world);
}
Transcript.cr;
'

o  evaluate: aStringOrStream in: anEnvironment
like #evaluate, but take anEnvironment for variable/function declarations.
New vars/functions will be added to that one; lookup for vars/methods
is done there.
If a nil environment is given, a new one will be created for the
evaluation and discarded afterwards.

o  evaluate: aString in: anEnvironment receiver: someObject notifying: requestor logged: logged ifFail: failBlock

o  evaluate: aStringOrStream in: anEnvironment receiver: anObject notifying: requestor logged: logged ifFail: failBlock compile: compile
return the result of evaluating aStringOrStream, errors are reported to requestor.
Allow access to anObject as self and to its instVars (used in the inspector).
If logged is true, an entry is added to the change-file. If the failBlock argument
is non-nil, it is evaluated if an error occurs.
Finally, compile specifies if the string should be compiled down to
bytecode or instead be interpreted from the parseTree.
The first should be done for doIts etc, where a readable walkback is
required.
The latter is better done for constants, styleSheet and resource
reading and simple sends, where the overhead of compilation is bigger
than the interpretation overhead.

o  evaluate: aStringOrStream receiver: receiver in: anEnvironment
like #evaluate, but take anEnvironment for variable/function declarations.
New vars/functions will be added to that one; lookup for vars/methods
is done there.
If a nil environment is given, a new one will be created for the
evaluation and discarded afterwards.

o  evaluateDeclarationsFrom: aStringOrStream for: anEnvironment

o  evaluateFrom: aStringOrStream ifFail: exceptionValue
evaluate a javaScript expression.
A new environment is created, where variables are defined.

initialization
o  initialize
ActionArray := nil

o  postAutoload
(comment from inherited method)
postAutoload is sent to a class after it has been autoloaded.
This gives it a chance to arrange for automatic unloading to be done
after a while ...
This is NOT sent to statically compiled in or explicitely filedIn
classes.
The default action here is to do nothing.

instance creation
o  for: aStringOrStream in: aClass
return a new parser, reading code for aClass from aStringOrStream

parsing
o  methodCommentFromSource: aStringOrStream
here, the methodComment is usually outside of the method's code,
so comments before the function are included in the search, but after it are not.

Usage example(s):

     JavaScriptParser methodCommentFromSource:'
// foo bar baz
function x() { 
    halt(); 
}
// bla bla
'                 

o  methodCommentsFromSource: aStringOrStream
returns all comments found in aStringOrStream.
Here, the methodComment is usually outside of the method's code,
so comments before the function are included, but after it are not.

Usage example(s):

     JavaScriptParser methodCommentsFromSource:'
// foo bar baz
function x() { 
    halt(); 
}
// bla bla
'            

o  parse: aStringOrStream class: aClass
parse whatever is the unit of compilation in ST/X's browser

Usage example(s):

     self parse:'function foo(a, b, c) {}' class:nil

Usage example(s):

     self parse:'function foo(a, b, c) { return a+b; }' class:nil

o  parseClassDefinition: aStringOrStream

o  parseClassFile: aStringOrStream
aStringOrStream

o  parseExpression: aStringOrStream
self
parseExpression:'1 + 2 * 3 + 4'

Usage example(s):

     self
        parseExpression:'1.1 + 2.2'

o  parseExpression: aStringOrStream setup: setupBlock onError: aBlock
self
parseExpression:'1 + 2 * 3 + 4'

Usage example(s):

     self
        parseExpression:'1.1 + 2.2'

o  parseFunction: aStringOrStream
self
parseFunction:'function foo(a, b, c) {}'

Usage example(s):

     self
        parseFunction:'function foo(a, b, c) { return a+b; }'

o  parseFunction: aStringOrStream in: aClass
self
parseFunction:'function foo(a, b, c) {}'

Usage example(s):

     self
        parseFunction:'function foo(a, b, c) { return a+b; }'

o  parseMethod: aStringOrStream
parse a method in a given class. Return a parser (instance of myself).
The parser can be queried for selector, receiver, args, locals,
used selectors, modified instvars, referenced classvars etc.

o  parseMethod: aStringOrStream in: aClass
parse a method in a given class. Return a parser (instance of myself).
The parser can be queried for selector, receiver, args, locals,
used selectors, modified instvars, referenced classvars etc.

o  parseMethod: aStringOrStream in: aClass ignoreErrors: ignoreErrors ignoreWarnings: ignoreWarnings
parse a method in a given class.
Return a parser (instance of myself).
The parser can be queried for selector, receiver, args, locals,
used selectors, modified instvars, referenced classvars etc.

o  parseMethodArgAndVarSpecificationSilent: aStringOrStream

o  parseMethodSilent: aString
parse a method.
Return a parser (if ok), nil (empty) or #Error (syntax).
The parser can be queried for selector, receiver, args, locals,
used selectors etc.
Like #parseMethod:, but warning/error messages are suppressed.

o  parseMethodSilent: aStringOrStream in: aClass

o  parseMethodSpecificationSilent: aStringOrStream

o  parseStatementBlockBody: aStringOrStream
self
parseStatementBlockBody:'1+2'

Usage example(s):

     self
        parseStatementBlockBody:'var a; a'

Usage example(s):

    Class nameSpaceQuerySignal
    answer:JavaScriptEnvironment
    do:[
     self
        parseStatementBlockBody:'Math.PI'
    ]

o  xx_parseMethodSpecification: aStringOrStream in: aClass ignoreErrors: ignoreErrors ignoreWarnings: ignoreWarnings

queries
o  parseNodeVisitorClass

selector translation
o  commonTranslatedSelectorFor: jsSelector
common translation (both JS-in-ST and JS-in-HTML).
Given a javascript operator or function name,
translate it into a corresponding smalltalk selector for a message send

Usage example(s):

     self commonTranslatedSelectorFor:#'%'
     self commonTranslatedSelectorFor:#'split'    
     self commonTranslatedSelectorFor:#'fooBar'  

o  reverseCommonTranslatedSelectorFor: smalltalkSelector
reverse translation.
Given a smalltalk selector, return a corresponding JavaScript
operator or function name.
Used by the document generator only

o  reverseTranslatedJavaScriptSelectorFor: smalltalkSelector
return the javaScript selector for a given smalltalk selector.
Given a javascript operator or function name,
translate it into a corresponding smalltalk selector.
THIS IS ONLY TO BE USED FOR DOCUMENTATION PURPOSES

Usage example(s):

     self reverseTranslatedJavaScriptSelectorFor:#show:    
     self reverseTranslatedJavaScriptSelectorFor:#at:      
     self reverseTranslatedJavaScriptSelectorFor:#at:put:  
     self reverseTranslatedJavaScriptSelectorFor:#+    
     self reverseTranslatedJavaScriptSelectorFor:#-    

o  selectorForFunctionName: jsName numArgs: nargs
given a javaScript function name,
return an appropriate valid smalltalk selector.
This is used when methods are compiled

Usage example(s):

     self selectorForFunctionName:'foo' numArgs:0
     self selectorForFunctionName:'foo' numArgs:1 
     self selectorForFunctionName:'foo' numArgs:2 
     self selectorForFunctionName:'foo' numArgs:3 

o  selectorMapping
this table defines the selector translation common for both JS-in-ST and JS-in-HTML.

temporary hacks for DWIM
o  parseMethod: aStringOrStream setup: setupBlock onError: onErrorBlock
nodesSoFar


Instance protocol:

accessing
o  currentEnvironment

o  currentNameSpace: aNameSpace

o  currentNamespace: aNameSpace

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  interactiveMode: something
support for stx-scripting service

o  methodCategory

o  methodCategory: something

o  moreSharedPools: aCollection

o  selector

o  smalltalkSelector

o  targetClass

o  targetClass: aClass

o  translateCallsToSelfSends: something

o  tree
return the value of the instance variable 'tree' (automatically generated)

o  tree: something
set the value of the instance variable 'tree' (automatically generated)

debugging
o  inspector2TabParseTreeInspector

dummy-syntax detection
o  markArgumentIdentifierFrom: pos1 to: pos2
intentionally left blank here

o  markFieldNameFrom: pos to: endPos
intentionally left blank here

o  markFunctionNameFrom: pos1 to: pos2
intentionally left blank here

o  markGlobalIdentifierFrom: pos1 to: pos2
intentionally left blank here

o  markIdentifierFrom: pos1 to: pos2
intentionally left blank here

o  markKeyword: kw from: pos1 to: pos2
intentionally left blank here

o  markKeywordToken
intentionally left blank here

o  markLocalIdentifierFrom: pos1 to: pos2
intentionally left blank here

o  markSelector: id from: pos1 to: pos2 receiverNode: aReceiverNodeOrNil numArgs: numArgs
intentionally left blank here

o  markSelfFrom: pos1 to: pos2
intentionally left blank here

o  markSuperFrom: pos1 to: pos2
intentionally left blank here

o  markVariable: v
intentionally left blank here

o  markVariable: v from: pos to: endPos
intentionally left blank here

error handling
o  parseError: aMessage position: position to: endPos
ParseError raiseRequestErrorString:aMessage

o  undefError: varName
self parseError:'unknown global: ' , varName.

o  warning: msg
^ super warning:msg

evaluation
o  evaluate: aString in: anEnvironment receiver: someObject notifying: requestor logged: logged ifFail: failBlock
true -- assuming that subclasses can compile

o  evaluate: aStringOrStream in: anEnvironment receiver: anObject notifying: requestor logged: logged ifFail: failBlock compile: compile
return the result of evaluating aStringOrStream, errors are reported to requestor.
Allow access to anObject as self and to its instVars (used in the inspector).
If logged is true, an entry is added to the change-file. If the failBlock argument
is non-nil, it is evaluated if an error occurs.
Finally, compile specifies if the string should be compiled down to
bytecode or instead be interpreted from the parseTree.
The first should be done for doIts etc, where a readable walkback is
required.
The latter is better done for constants, styleSheet and resource
reading and simple sends, where the overhead of compilation is bigger
than the interpretation overhead.

o  evaluateDeclarationFor: anEnvironment
this is used with the scripting interpreter, where an existing environment
is used and manipulated (i.e. declared variables are persistent across evaluations).
Reads a single decl; for function decls, declare them;
for statements & expressions, evaluate them.

o  evaluateDeclarationsFor: anEnvironment
read; for function decls, declare them; for statements & expressions,
evaluate them.
Returns the value of the last expression

helpers
o  commonTranslatedSelectorFor: jsSelector

o  currentNameSpace

o  expect: expected

o  expectKeyword: expected

o  findNameSpaceWith: aVariableName
"/ private names have already been searched for.

o  ifRequiredTranslateSelectorIn: aNode
we are compiling a javaScript-script in a browser.

o  isOpAssignSymbol: token

o  selectorForFunctionName: arg1 numArgs: arg2

o  topEnvironment

o  translatedJSSelectorFor: selector numArgs: numArgs
translate selectors as req'd for HTML-scripts.
All selectors get a js_ prepended, to avoid conflicts with corresponding
smalltalk selectors.
This is especially req'd, as at:/at:put: in JS are 0-based,
while being 1-based in ST.
Thus, the translation allows for indexOf: to remain unchanged, and js_indexOf: returns a 0-based index.

o  translatedSmalltalkSelectorFor: jsSelector numArgs: numArgs
translate javaScript selectors as req'd for compiled JTalk.
Given a javascript operator or function name,
translate it into a corresponding smalltalk selector for a message send

initialization
o  environment: anEnvironment

o  foldConstants: aBoolean

o  initialize
(comment from inherited method)
initialize the scanner

o  isDoIt

o  isDoIt: aBoolean

o  parseForCode

o  setAllClassVarNames: aCollectionOfNameStrings
set the collection of classvar names.
This is provided for subclasses (Node, Groovy)

o  setAllInstVarNames: aCollectionOfNameStrings
set the collection of instvar names.
This is provided for subclasses (Node, Groovy)

o  setClassToCompileFor: aClass
set the class to be used for parsing/evaluating

o  setSelf: anObject
(classToCompileFor ~~ PrevClass) ifTrue:[

o  smalltalkCompatibilityMode
in smalltalk mode, array indexing is 1-based,
and conditions must be booleans.
in non-smalltalk (i.e. javaScript) mode, indexing is 0 based
and conditions can also be integers (treating 0 as false).
The default is true (and MUST remain so for expecco)

o  smalltalkCompatibilityMode: aBoolean
in smalltalk mode, array indexing is 1-based,
and conditions must be booleans.
in non-smalltalk (i.e. javaScript) mode, indexing is 0 based
and conditions can also be integers (treating 0 as false).
The default is true (and MUST remain so for expecco)

o  untranslatedJavaScriptSelectors1

o  untranslatedJavaScriptSelectors1: anArray
Modified (format): / 28-02-2022 / 10:01:47 / Stefan_Vogel

o  untranslatedJavaScriptSelectors2

o  untranslatedJavaScriptSelectors2: anArray
Modified (format): / 28-02-2022 / 10:02:23 / Stefan_Vogel

parsing
o  argList
arg | argList , arg

o  classDefinition
public class <name> extends <superName> {
<varDecls>
}

o  classNameIdentifier

o  constDeclaration
'const' name [ '=' constExpression ]';'

o  constDeclarationFor: anEnvironment
[ 'static' ] 'const' name ['=' initExpr] ';'

o  constOrVarDeclarationFor: anEnvironment isConst: isConstIn
[ 'static' ] ('const'|'var') name ['=' initExpr] ';'
| 'let' name ['=' initExpr] ';'

o  declareConstant: varName inEnvironment: anEnvironment

o  declareStaticConstant: varName
name (not eaten)

o  declareStaticVariable: varName
name (not eaten)

o  declareStaticVariable: varName isConstant: isConstant
name (not eaten)

o  declareVariable: varName inEnvironment: anEnvironment

o  declareVariable: varName inEnvironment: anEnvironment isConstant: isConstant
caveat: isConstant is currently ignored

o  fileSource
process a complete file's source (multiple declarations)

o  function
function(args) stats ;

o  function: readOverClosingBrace
function(args) stats ;

o  functionBodyFor: functionNameOrNil asInnerFunction: asInnerFunction
(args) stats ;

o  functionBodyFor: functionNameOrNil asInnerFunction: asInnerFunction withStatements: withStatements
(args) stats ;

o  functionName
function name(args) stats ;
| function className.name(args) stats ;
| function className.class.name(args) stats ;

o  functionOrStaticFunction: readFinalBrace
[static] function(args) stats ;

o  functionOrStaticFunctionOrClass: readFinalBrace
[static] function(args) stats ;
[static] class ...

o  lambdaFunctionBodyWithArguments: argList

{ stats }
| expr

o  needSemi
;
possibly omitted

o  parseClass: isStatic readFinalBrace: readOverClosingBrace
class (args) stats ;

Usage example(s):

     self parseClass:'class Foo {}'

o  parseDeclarationsFor: anEnvironment
read; for function decls, declare them; for statements & expressions,
parse (but do not evaluate) them.

o  parseExpressionWithSelf: anObject notifying: someOne ignoreErrors: ignoreErrors ignoreWarnings: ignoreWarnings inNameSpace: aNameSpaceOrNil
parse aString as an expression with self set to anObject;
Return the parseTree (if ok), nil (for an empty string
or comment only ) or #Error (syntactic error).

Errors and warnings are forwarded to someOne (usually some
codeView) which can highlight it and show a popup box,
iff ignoreErrors/ignoreWarnings is true respectively.

o  parseMethod
parse the next function (aka method) from my current source stream

o  parseMethod: theCode in: aClass ignoreErrors: ignoreErrorsArg ignoreWarnings: ignoreWarningsArg
parse a function (aka method) from a different code stream.
After parsing, I can be queried for selector, receiver, args, locals,
used selectors, modified instvars, referenced classvars etc.

o  parseTopLevelElement
these are consts, vars, functions.
Can be redefined to eg. parse imports

o  rememberAssignmentTo: var
type == #PoolVariable ifTrue:[

o  rememberReadOf: var
type == #PoolVariable ifTrue:[

o  varDeclaration
[ 'static' ] 'var' name ['=' initExpr] ';'
[ 'static' ] 'const' name ['=' initExpr] ';'
| 'let' name ['=' initExpr] ';'

o  varDeclarationFor: anEnvironment
[ 'static' ] 'var' name ['=' initExpr] ';'
[ 'static' ] 'const' name ['=' initExpr] ';'
| 'let' name ['=' initExpr] ';'

parsing-expressions
o  addExpression
addExpr -> mulExpr addOp mulExpr

o  arrayConstant
arrayConstant -> Integer-constant
| Float-constant
| String-constant
| true
| false
| null
| arrayLiteral
| objectLiteral

o  arrayIndexing: expr
arrayIndexing -> [...]

o  arrayIndexingExpression: recIn
an initial 'recIn.' has already been scanned;

arrayIndexingExpression -> variableOrFunctionExpression
| variableOrFunctionExpression[ indexExpr ]

o  arrayIndexingExpressionList: exprIn
arrayIndexingExpressionList ->
.identifier(...)
| [ array-expr ]

o  arrayLiteral
arrayLiteral -> [ nonCommaExpression { , nonCommaExpression } ] ']'
initial opening bracket has NOT been read.

o  awaitExpression

o  bitAndExpression
bitAndExpression -> equalityExpr & equalityExpr

o  bitOrExpression
bitOrExpression -> bitXorExpr | bitXorExpr

o  bitShiftExpression
conditionalExpr -> addExpr shiftOp addExpr

o  bitXorExpression
bitXorExpression -> bitAndExpr ^ bitAndExpr

o  booleanAndExpression
booleanAndExpression -> bitOrExpr && bitOrExpr

o  booleanOrExpression
booleanAndExpression -> bitOrExpr || bitOrExpr

o  commaExpression
commaExpression -> conditionalExpression [, commaExpression ]

o  compareExpr
compareExpr -> bitShiftExpr relOp bitShiftExpr

o  compoundExpression

o  conditionalExpression
conditionalExpr -> boolOrExpr ? boolOrExpr

o  constantExpression

o  equalityExpression
equalityExpression -> compareExpr relOp compareExpr

o  expression
expression -> commaExpression

o  expressionList
expression | expressionList , expression

o  functionCallExpression: recIn
functionCallExpression -> var
| var(argList)

o  mulExpression
mulExpr -> powerExpression mulOp powerExpression

o  newExpression
for now, we do not support full expressions here...

o  nonCommaExpression

o  objectLiteral
objectLiteral -> '{' [ slotName ':' literal { , slotName ':' literal } ] '}'
opening brace has already been read

o  objectLiteralOrDescructuringExpression
opening brace has already been read

objectLiteral -> '{' [ slotName ':' literal { , slotName ':' literal } ] '}'
desctruct -> '{' [ slotName , slotName , ... '}'

o  powerExpression
powerExpr -> unaryExpr ** unaryExpr

o  primaryExpression
primaryExpr ->
'(' expr ')'
| '(' id1,...idN ')' '=>' lambdaFunctionBody
| '(' ')' '=>' lambdaFunctionBody
| variable '=>' lambdaFunctionBody
| constant
| 'this'
| 'super'
| variable
| 'new' class
| 'new' funcOrClass '(' dim ')'
| 'function' '(' argList ')' '{' statements '}'

o  typeofExpression

o  unaryExpression
unaryExpr -> ! unaryExpression
| ~ unaryExpression
| - unaryExpression
| ++unaryExpression
| --unaryExpression
| primaryExpression
| primaryExpression--
| primaryExpression++
| typeof primaryExpression
| await expression

o  varDeclaringExpression
an expression inside a for loop;
slightly different, allowing an already declared varName to be (re)-defined

o  variable: idAlreadyScanned

o  variable: idAlreadyScanned ignoreErrors: ignoreErrors
if there is one in the current evaluationContext,

parsing-statements
o  breakStatement
breakStatement -> break ';'

o  catchPartFor: tryBlockNode
tryCatchStatement -> try {
...
statements
...
}
catch([Error] [exVar] ) {
...
statements
...
}
[ finally {
...
statements
...
}

Notice: try { ... } has already been parsed.
Either Error-name or exVar or both may be present in the catch
(but one of them at least)

o  continueStatement
continueStatement -> continue ';'

o  doWhileStatement
doWhileStatement -> do stat while (expression)

o  finallyPart
finallyPart -> finally {
...
statements
...
}

o  forStatement
forStatement -> for (initexpr ; condexpr ; increxpression) stat
| for (variable in array) stat

o  functionDefinition
ok without semi

o  ifStatement
ifStatement -> if (expression) stat [ else stat ]

o  returnStatement
returnStatement -> return [ expression ] ['from' outerFunctionName ] ';'

o  statement
statement -> expression ;

o  statementBlock
statementBlock -> { statList } | statement

o  statementBlock: readClosingBraceBoolean
statementBlock -> { statList } | statement

o  statementBlockBody
statementBlock -> [ var decl ] statList

o  statementBlockBodyFor: anEnvironment
statementBlock -> [ var decl ] statList

o  statementWithSemi: needSemi
statement ->
var varName ....
let varName ....
const varName ....
static var varName ....
function ....
ifStatement
whileStatement
doStatement
returnStatement
forStatement
switchStatement
breakStatement
continueStatement
tryStatement
throwStatement
{ statementBlock }
expression ;

o  statements
statement -> expression ;

o  switchStatement
switchStatement -> switch (expression) {
case constant-expression1:
...
stat
...
break ;
case constant-expression2:
...
default:
...
}

o  throwStatement
throwStatement -> throw expression ';'

o  tryStatement
tryStatement -> try {
...
statements
...
}
( catchPart | finallyPart ]

o  whileStatement
whileStatement -> while (expression) stat

private
o  addDoItTemporary: varName

o  doItTemporaries

o  functionCallNodeForReceiver: rec selector: id args: argList fold: fold

o  handleCategoryDirective: categoryString
callback from the scanner, whenever it encountered a category comment-directive

o  implicitFunctionCallNodeForReceiver: rec selector: id args: argList fold: fold

o  isKeywordUsedAsIdentifier: tokenType

o  isSyntaxHighlighter

o  nameSpaceSelectorFor: aSymbol
Caring for the current namespace, return the real selector used for a send.

o  realFunctionCallNodeForReceiver: rec args: argList fold: fold
block evaluation - generate a value-send

o  realFunctionCallNodeForReceiver: rec selector: id args: argList fold: fold
block evaluation - generate a value-send

o  saveParseAheadDo: aBlock
restore old scanner state

queries
o  isEmptyMethod
return true (after a parse) if this is an empty (documentation) method

o  methodArgs

o  methodVars

o  wasParsedForCode
a kludge for compatibility

queries-statistic
o  messagesPossiblySent
return a collection with possible message selectors (valid after parsing).
Includes things known or possibly used with #perform or in specs.
Not yet implemented here.

Usage example(s):

^ (messagesPossiblySent ? #()) collect:[:each | each asSymbol]

o  messagesSent
return a set with sent message selectors (valid after parsing).
Includes all sent messages (i.e. also sent super messages)

o  messagesSentToSelf
that is not true - for now, to make the browser happy

o  messagesSentToSuper
that is not true - for now, to make the browser happy

o  modifiedClassVars

o  modifiedGlobals

o  modifiedInstVars

o  usedClassVars

o  usedGlobals

o  usedInstVars

o  usedVars

o  usesSuper
return true if the parsed method uses super (valid after parsing)

statistic
o  rememberClassVarModified: name

o  rememberClassVarRead: name

o  rememberClassVarUsed: name

o  rememberGlobalModified: name

o  rememberGlobalRead: name

o  rememberGlobalUsed: name

o  rememberInstVarModified: name

o  rememberInstVarRead: name

o  rememberInstVarUsed: name

o  rememberLocalModified: name
modifiedLocalVars isNil ifTrue:[

o  rememberLocalRead: name
readLocalVars isNil ifTrue:[

o  rememberLocalUsed: name
usedLocalVars isNil ifTrue:[

o  rememberVariableUsed: name

syntax detection
o  postProcessTree: aParseTree forText: text
allows for additional checks to be done on the tree
(checking arguments to a call-node in expecco, for example)

temporary hacks for DWIM
o  nodeGenerationCallback: nodeGenerationHook

o  rememberNodes: aBoolean
enable node remembering.
In case of an error, this allows for the nodes which have been collected
so far to be fetched. Useful for code completion of incomplete (erroneous) code.

o  rememberTokens: aBoolean
enable token remembering.
In case of an error, this allows for the tokens which have been collected
so far to be fetched. Useful for code completion of incomplete (erroneous) code.

o  rememberedNodes
In case of an error, this allows for the nodes which have been collected
so far to be fetched. Useful for code completion of incomplete (erroneous) code.

o  rememberedTokens
In case of an error, this allows for the tokens which have been collected
so far to be fetched. Useful for code completion of incomplete (erroneous) code.

utilities
o  ensureBooleanExpression: expr
relops are guaranteed to return booleans...


Private classes:

    AndExpressionNode
    ArrayAccessNode
    ArrayStoreNode
    AwaitNode
    BreakStatementNode
    CommaExpression
    ConditionalNode
    ContinueStatementNode
    DoWhileStatementNode
    ForStatementNode
    FunctionCallNode
    IfStatementNode
    ImplicitFunctionCallNode
    IncDecNode
    InnerJavaBlockNode
    JavaScriptAssignmentNode
    JavaScriptBinaryNode
    JavaScriptMultiVariableNode
    JavaScriptReturnNode
    JavaScriptStatementNode
    JavaScriptUnaryNode
    NewNode
    OrExpressionNode
    PostIncDecNode
    PreIncDecNode
    StatementBlockNode
    SwitchStatementNode
    ThisNode
    ThrowStatementNode
    TryCatchStatementNode
    TypeOfNode
    WhileStatementNode

Examples:


    JavaScriptParser parseExpression:'3 != 4'  
JavaScriptParser parseExpression:'0b11 + 0b100'
    (JavaScriptParser parseExpression:'3 + 4 * 5') evaluate  
    JavaScriptParser parseExpression:'(3 != 4) && (5 == 5)' 
    (JavaScriptParser parseExpression:'(3 == 4) || (5 == 5)') evaluate 
    JavaScriptParser parseExpression:'!(3 != 4)'      
    (JavaScriptParser parseExpression:'(3 != 4)') evaluate
    (JavaScriptParser parseExpression:'!(3 != 4)') evaluate
    #(
        '1 + 2 * 3 + 4'
        '1 * 2 * 3 * 4'
        '1 + 2 / 3'
        '10 / 3'
        '11 & 3'
        '0x8000'
        '0377'
        '3 == 3'
        '3 != 3'
        '3 == 4'
        '3 != 4'
        '3 > 3'
        '3 >= 3'
        '3 < 3'
        '3 <= 3'
        '3 > 4'
        '3 >= 4'
        '3 < 4'
        '3 <= 4'
        '4 > 3'
        '4 >= 3'
        '4 < 3'
        '4 <= 3'
        '0x8>>2'
        '8 << 2'
        '8 >>> 2'
    ) do:[:s |
        Transcript
            show:'''';
            show:s;
            show:'''';
            show:' ->  ';
            showCR:(JavaScriptParser parseExpression:s) evaluate.
    ]
     JavaScriptParser
        parseFunction:'function foo(a, b, c) {}'
     JavaScriptParser
        parseFunction:'function foo(a, b, c) {
            if (a > 1) {
                return a;
            } else {
                return b;
            }
        }'
     JavaScriptParser
        parseFunction:'
function bar(a, b, c) {
    var sum;

    while (a > 1) {
        sum += a;
        a--;
    }
    return sum;
}'
     JavaScriptParser
        parseFunction:'
function bar(a, b, c) {
    var sum;
    var j;
    if ( foo(a,b) ) {
        for (j=0; j<=a.length; j++) {
            if (c[j] <= c[j+1])
                break;
        }
    }
    return sum;
}'
     JavaScriptParser
        parseFunction:'
function bar(a, b, c) {
    var sum;

    if ( foo(a,b) ) {
        for (var j=0; j<=a.length; j++) {
            if (c[j] <= c[j+1])
                break;
        }
    }
    return sum;
}'
     JavaScriptParser
        parseFunction:'
        function switch_time(value) {
          if (value < 0.5) sw = 0;
                else sw=-1;
        }
'
     JavaScriptParser
        parseFunction:'
        function f(a) {
          return ( function (b) { return (a + b); } );        
        }
'
    JavaScriptParser parseExpression:'{a:10 , b:20}'  
    JavaScriptParser parseFunction:'function foo() { var foo = {a:10 , b:20}; }'  
    JavaScriptParser parseExpression:'function foo() { var {a,b} = foo(); }'  


ST/X 7.7.0.0; WebServer 1.702 at 20f6060372b9.unknown:8081; Thu, 02 May 2024 15:17:22 GMT