compiler/TParser.st
changeset 14 fa42d3f1a578
parent 9 569bf5707c7e
child 16 17a2d1d9f205
equal deleted inserted replaced
13:97090c2baa33 14:fa42d3f1a578
     1 "{ Package: 'jv:tea/compiler' }"
     1 "{ Package: 'jv:tea/compiler' }"
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 RBParser subclass:#TParser
     5 RBParser subclass:#TParser
     6 	instanceVariableNames:'parsingInlineAssembly'
     6 	instanceVariableNames:'parsingPrimitive'
     7 	classVariableNames:''
     7 	classVariableNames:''
     8 	poolDictionaries:''
     8 	poolDictionaries:''
     9 	category:'Languages-Tea-Compiler-AST'
     9 	category:'Languages-Tea-Compiler-AST'
    10 !
    10 !
    11 
    11 
    26 
    26 
    27     "Created: / 13-09-2015 / 06:39:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    27     "Created: / 13-09-2015 / 06:39:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    28     "Modified: / 13-09-2015 / 07:55:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    28     "Modified: / 13-09-2015 / 07:55:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    29 ! !
    29 ! !
    30 
    30 
    31 !TParser methodsFor:'accessing'!
       
    32 
       
    33 initializeParserWith: aString type: aSymbol 
       
    34         |stream|
       
    35 
       
    36         stream := ReadStream on: aString.
       
    37         source := aString.
       
    38         self scanner: (TScanner 
       
    39                                 perform: aSymbol
       
    40                                 with: stream
       
    41                                 with: self errorBlock)
       
    42 
       
    43     "Created: / 02-09-2015 / 05:57:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    44 ! !
       
    45 
       
    46 !TParser methodsFor:'initialization & release'!
    31 !TParser methodsFor:'initialization & release'!
    47 
    32 
    48 scanner: aScanner 
    33 scanner: aScanner 
    49     parsingInlineAssembly := false.
    34     parsingPrimitive := false.
    50     super scanner: aScanner.
    35     super scanner: aScanner.
    51 
    36 
    52     "Created: / 02-09-2015 / 06:34:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    37     "Created: / 02-09-2015 / 06:34:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    53 ! !
    38 ! !
    54 
    39 
   121     ^node
   106     ^node
   122 
   107 
   123     "Created: / 14-09-2015 / 14:35:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   108     "Created: / 14-09-2015 / 14:35:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   124 !
   109 !
   125 
   110 
   126 parseInlineAssembly
       
   127         | position blockNode firstLine prevScope|
       
   128 
       
   129         position := currentToken start.
       
   130         firstLine := currentToken lineNumber.
       
   131         parsingInlineAssembly := true.
       
   132         self step. "/ To eat %[ token
       
   133         blockNode := self parseBlockArgsInto: TInlineAssemblyNode new.
       
   134 "/        node arguments do:[:eachArg | eachArg parent:self].
       
   135         blockNode left: position.
       
   136         blockNode firstLineNumber:firstLine.
       
   137         prevScope := currentScope.
       
   138         currentScope := blockNode.
       
   139         self rememberLastNode:blockNode.
       
   140         blockNode body: (self parseStatements: false).
       
   141         RBParser isSmalltalkX ifTrue:[
       
   142             self addComments:(scanner getCommentsBeforeToken) afterNode:blockNode body.
       
   143         ].
       
   144         "/ ensure that right is set, even if parse aborted due to an error
       
   145         blockNode right: currentToken start-1.
       
   146 
       
   147         (currentToken isTInlineAssemblyEnd ) 
       
   148                 ifFalse: [self parserError: '''$]'' expected'].
       
   149         "/ fix right
       
   150         blockNode right: currentToken start.
       
   151         blockNode lastLineNumber:currentToken lineNumber.
       
   152         parsingInlineAssembly := false.
       
   153 
       
   154         self step.
       
   155         self addComments:(scanner getCommentsBeforeToken) afterNode:blockNode.
       
   156         currentScope := prevScope.
       
   157         ^ blockNode
       
   158 
       
   159     "Created: / 02-09-2015 / 06:25:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   160 !
       
   161 
       
   162 parseKeywordMessageWith: node 
   111 parseKeywordMessageWith: node 
   163     | message |
   112     | message |
   164     message := super parseKeywordMessageWith: node.
   113     message := super parseKeywordMessageWith: node.
   165     message ~~ node ifTrue:[ 
   114     message ~~ node ifTrue:[ 
   166         "/ Check for special forms here...
   115         "/ Check for special forms here...
   184 
   133 
   185     "Created: / 20-08-2015 / 17:33:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   134     "Created: / 20-08-2015 / 17:33:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   186     "Modified: / 21-08-2015 / 22:50:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   135     "Modified: / 21-08-2015 / 22:50:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   187 !
   136 !
   188 
   137 
   189 parseStatementList: tagBoolean into: sequenceNode 
   138 parseKeywordPragma
   190         | statements return periods returnPosition returnLineNumber node valueNode|
   139     | selectorParts arguments |
   191         return := false.
   140 
   192         statements := OrderedCollection new.
   141     selectorParts := OrderedCollection new: 2.
   193         periods := OrderedCollection new.
   142     arguments := OrderedCollection new: 2.
   194         self addComments:(scanner getCommentsBeforeToken) beforeNode:sequenceNode.
   143     [ currentToken isKeyword ] whileTrue: [
   195         tagBoolean ifTrue: [self parseResourceTag].
   144         selectorParts add: currentToken.
   196         
   145         self step.        
   197         [
   146         "Hack to handle <primitive: [:asm | asm ret: 1 ]>
   198          "skip empty statements"
   147          style primitives"
   199          emptyStatements ifTrue: 
   148         (selectorParts size == 1 
   200                  [[currentToken isSpecial and: [currentToken value == $.]] whileTrue: 
   149             and:[selectorParts last value = 'primitive:'
   201                                  [periods add: currentToken start.
   150             and:[currentToken isSpecial 
   202                                  self step]].
   151             and:[currentToken value == $[]]]) ifTrue: [                        
   203 
   152             parsingPrimitive := true.
   204          self atEnd 
   153             arguments addLast: self parseBlock.
   205                 or: [(currentToken isSpecial and: ['])}' includes: currentToken value ])
   154             parsingPrimitive := false.
   206                 or: [(currentToken isTInlineAssemblyEnd)]]
   155         ] ifFalse:[
   207         ] whileFalse:[ 
   156             arguments addLast: self parsePragmaLiteral 
   208             self addComments:(scanner getCommentsBeforeToken) beforeNode:node "value".
   157         ]
   209 
   158     ].
   210             return ifTrue: [
   159     ^ RBPragmaNode
   211                 self class isSmalltalkX 
   160         selectorParts: selectorParts
   212                     ifTrue:
   161         arguments: arguments.
   213                         ["could output a warning"]
   162 
   214                     ifFalse:
   163     "Created: / 22-09-2015 / 16:49:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   215                         [self 
       
   216                             parserError: 'End of statement list encounted (statements after return)'
       
   217                             lastNode:node]].
       
   218             (currentToken isTInlineAssemblyBegin) ifTrue:[ 
       
   219                 node := self parseInlineAssembly.
       
   220                 statements add: node.
       
   221             ] ifFalse:[
       
   222             (currentToken isSTXPrimitiveCode) 
       
   223                 ifTrue:[
       
   224                     " primPosition := currentToken start. "
       
   225                     node := RBSTXPrimitiveCCodeNode new codeToken: currentToken.
       
   226                     self addComments:(scanner getCommentsBeforeToken) afterNode:node.
       
   227                     statements add: node.
       
   228                     self step.
       
   229                 ] ifFalse:[
       
   230                     (currentToken isSpecial and: [currentToken value == $^])
       
   231                         ifTrue: 
       
   232                                 [
       
   233                                 returnPosition := currentToken start.
       
   234                                 returnLineNumber := currentToken lineNumber.
       
   235                                 self step.
       
   236 
       
   237                                 valueNode := self parseAssignment.
       
   238                                 node := RBReturnNode return: returnPosition value: valueNode.
       
   239                                 node lineNumber:returnLineNumber.
       
   240                                 scanner atEnd ifFalse:[
       
   241                                     self addComments:(scanner getCommentsBeforeToken) afterNode:node value.
       
   242                                 ].
       
   243 
       
   244                                 statements add: node.
       
   245                                 return := true]
       
   246                         ifFalse: 
       
   247                                 [
       
   248                                 node := self parseAssignment.
       
   249                                 node notNil ifTrue:[
       
   250                                     self addComments:(scanner getCommentsAfterTokenIfInLine:node lastLineNumber) afterNode:node.
       
   251                                     scanner atEnd ifFalse:[
       
   252                                         self addComments:(scanner getCommentsAfterToken) afterNode:node.
       
   253                                         self addComments:(scanner getCommentsBeforeToken) afterNode:node.
       
   254                                     ].
       
   255 
       
   256                                     statements add: node
       
   257                                 ]].
       
   258                 ].
       
   259             ].
       
   260 
       
   261             (currentToken isSpecial and: [currentToken value == $.])
       
   262                 ifTrue: 
       
   263                     [periods add: currentToken start.
       
   264                     self step]
       
   265                 ifFalse: 
       
   266                     [return := true].
       
   267             emptyStatements 
       
   268                 ifTrue: 
       
   269                     [[currentToken isSpecial and: [currentToken value == $.]] whileTrue: 
       
   270                                     [periods add: currentToken start.
       
   271                                     self step]]].
       
   272 
       
   273         sequenceNode 
       
   274             statements: statements;
       
   275             periods: periods.
       
   276 
       
   277         self addComments:(scanner getCommentsBeforeToken) afterNode:node "value".
       
   278         ^sequenceNode
       
   279 
       
   280     "Created: / 02-09-2015 / 06:23:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   281 !
   164 !
   282 
   165 
   283 parseType
   166 parseType
   284     "
   167     "
   285     type ::= type_simple
   168     type ::= type_simple
   316     "Created: / 20-08-2015 / 17:20:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   199     "Created: / 20-08-2015 / 17:20:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   317     "Modified: / 21-08-2015 / 21:13:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   200     "Modified: / 21-08-2015 / 21:13:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   318 !
   201 !
   319 
   202 
   320 parseTypeSpec: forReturn
   203 parseTypeSpec: forReturn
   321     parsingInlineAssembly ifTrue:[ ^ nil ].
   204     parsingPrimitive ifTrue:[ ^ nil ].
   322     
   205     
   323     (currentToken isBinary and: [currentToken value == #<]) ifTrue: [
   206     (currentToken isBinary and: [currentToken value == #<]) ifTrue: [
   324         | start stop type |    
   207         | start stop type |    
   325         start := currentToken start.
   208         start := currentToken start.
   326         self step.
   209         self step.