compiler/TParser.st
changeset 6 0c806a7f1888
parent 2 2a3e47c13905
child 7 7556e3d41d80
--- a/compiler/TParser.st	Mon Aug 31 18:37:31 2015 +0100
+++ b/compiler/TParser.st	Wed Sep 02 09:18:00 2015 +0100
@@ -3,7 +3,7 @@
 "{ NameSpace: Smalltalk }"
 
 RBParser subclass:#TParser
-	instanceVariableNames:''
+	instanceVariableNames:'parsingInlineAssembly'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Languages-Tea-Compiler-AST'
@@ -17,6 +17,30 @@
     "Created: / 20-08-2015 / 17:04:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!TParser methodsFor:'accessing'!
+
+initializeParserWith: aString type: aSymbol 
+        |stream|
+
+        stream := ReadStream on: aString.
+        source := aString.
+        self scanner: (TScanner 
+                                perform: aSymbol
+                                with: stream
+                                with: self errorBlock)
+
+    "Created: / 02-09-2015 / 05:57:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!TParser methodsFor:'initialization & release'!
+
+scanner: aScanner 
+    parsingInlineAssembly := false.
+    super scanner: aScanner.
+
+    "Created: / 02-09-2015 / 06:34:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !TParser methodsFor:'private-parsing'!
 
 parseArgOrLocal
@@ -42,6 +66,42 @@
     "Created: / 21-08-2015 / 22:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+parseInlineAssembly
+        | position blockNode firstLine prevScope|
+
+        position := currentToken start.
+        firstLine := currentToken lineNumber.
+        parsingInlineAssembly := true.
+        self step. "/ To eat %[ token
+        blockNode := self parseBlockArgsInto: TInlineAssemblyNode new.
+"/        node arguments do:[:eachArg | eachArg parent:self].
+        blockNode left: position.
+        blockNode firstLineNumber:firstLine.
+        prevScope := currentScope.
+        currentScope := blockNode.
+        self rememberLastNode:blockNode.
+        blockNode body: (self parseStatements: false).
+        RBParser isSmalltalkX ifTrue:[
+            self addComments:(scanner getCommentsBeforeToken) afterNode:blockNode body.
+        ].
+        "/ ensure that right is set, even if parse aborted due to an error
+        blockNode right: currentToken start-1.
+
+        (currentToken isTInlineAssemblyEnd ) 
+                ifFalse: [self parserError: '''$]'' expected'].
+        "/ fix right
+        blockNode right: currentToken start.
+        blockNode lastLineNumber:currentToken lineNumber.
+        parsingInlineAssembly := false.
+
+        self step.
+        self addComments:(scanner getCommentsBeforeToken) afterNode:blockNode.
+        currentScope := prevScope.
+        ^ blockNode
+
+    "Created: / 02-09-2015 / 06:25:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 parseKeywordPattern
     | method |
 
@@ -53,6 +113,100 @@
     "Modified: / 21-08-2015 / 22:50:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+parseStatementList: tagBoolean into: sequenceNode 
+        | statements return periods returnPosition returnLineNumber node valueNode|
+        return := false.
+        statements := OrderedCollection new.
+        periods := OrderedCollection new.
+        self addComments:(scanner getCommentsBeforeToken) beforeNode:sequenceNode.
+        tagBoolean ifTrue: [self parseResourceTag].
+        
+        [
+         "skip empty statements"
+         emptyStatements ifTrue: 
+                 [[currentToken isSpecial and: [currentToken value == $.]] whileTrue: 
+                                 [periods add: currentToken start.
+                                 self step]].
+
+         self atEnd 
+                or: [(currentToken isSpecial and: ['])}' includes: currentToken value ])
+                or: [(currentToken isTInlineAssemblyEnd)]]
+        ] whileFalse:[ 
+            self addComments:(scanner getCommentsBeforeToken) beforeNode:node "value".
+
+            return ifTrue: [
+                self class isSmalltalkX 
+                    ifTrue:
+                        ["could output a warning"]
+                    ifFalse:
+                        [self 
+                            parserError: 'End of statement list encounted (statements after return)'
+                            lastNode:node]].
+            (currentToken isTInlineAssemblyBegin) ifTrue:[ 
+                node := self parseInlineAssembly.
+                statements add: node.
+            ] ifFalse:[
+            (currentToken isSTXPrimitiveCode) 
+                ifTrue:[
+                    " primPosition := currentToken start. "
+                    node := RBSTXPrimitiveCCodeNode new codeToken: currentToken.
+                    self addComments:(scanner getCommentsBeforeToken) afterNode:node.
+                    statements add: node.
+                    self step.
+                ] ifFalse:[
+                    (currentToken isSpecial and: [currentToken value == $^])
+                        ifTrue: 
+                                [
+                                returnPosition := currentToken start.
+                                returnLineNumber := currentToken lineNumber.
+                                self step.
+
+                                valueNode := self parseAssignment.
+                                node := RBReturnNode return: returnPosition value: valueNode.
+                                node lineNumber:returnLineNumber.
+                                scanner atEnd ifFalse:[
+                                    self addComments:(scanner getCommentsBeforeToken) afterNode:node value.
+                                ].
+
+                                statements add: node.
+                                return := true]
+                        ifFalse: 
+                                [
+                                node := self parseAssignment.
+                                node notNil ifTrue:[
+                                    self addComments:(scanner getCommentsAfterTokenIfInLine:node lastLineNumber) afterNode:node.
+                                    scanner atEnd ifFalse:[
+                                        self addComments:(scanner getCommentsAfterToken) afterNode:node.
+                                        self addComments:(scanner getCommentsBeforeToken) afterNode:node.
+                                    ].
+
+                                    statements add: node
+                                ]].
+                ].
+            ].
+
+            (currentToken isSpecial and: [currentToken value == $.])
+                ifTrue: 
+                    [periods add: currentToken start.
+                    self step]
+                ifFalse: 
+                    [return := true].
+            emptyStatements 
+                ifTrue: 
+                    [[currentToken isSpecial and: [currentToken value == $.]] whileTrue: 
+                                    [periods add: currentToken start.
+                                    self step]]].
+
+        sequenceNode 
+            statements: statements;
+            periods: periods.
+
+        self addComments:(scanner getCommentsBeforeToken) afterNode:node "value".
+        ^sequenceNode
+
+    "Created: / 02-09-2015 / 06:23:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 parseType
     "
     type ::= type_simple ( '|' type )*
@@ -99,6 +253,8 @@
 !
 
 parseTypeSpec: forReturn
+    parsingInlineAssembly ifTrue:[ ^ nil ].
+    
     (currentToken isBinary and: [currentToken value == #<]) ifTrue: [
         | start stop type |    
         start := currentToken start.
@@ -121,11 +277,11 @@
             start: start;
             stop: stop.
     ] ifFalse:[ 
-        self parserError: 'type specification expected'
+        self parserError: 'type annotation expected'
     ].
 
     "Created: / 20-08-2015 / 17:13:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 21-08-2015 / 21:18:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-09-2015 / 07:01:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseUnaryPattern