parsers/java/PPJavaParser.st
changeset 435 3bc08fb90133
child 436 e1c44b571db9
equal deleted inserted replaced
434:840942b96eea 435:3bc08fb90133
       
     1 "{ Package: 'stx:goodies/petitparser/parsers/java' }"
       
     2 
       
     3 "{ NameSpace: Smalltalk }"
       
     4 
       
     5 PPJavaSyntax subclass:#PPJavaParser
       
     6 	instanceVariableNames:''
       
     7 	classVariableNames:''
       
     8 	poolDictionaries:''
       
     9 	category:'PetitJava-Core'
       
    10 !
       
    11 
       
    12 PPJavaParser comment:'A parser which creates an AST upor parsing the code'
       
    13 !
       
    14 
       
    15 !PPJavaParser methodsFor:'accessing'!
       
    16 
       
    17 annotation 
       
    18 
       
    19 	^ super annotation ==> [:nodes | PJAnnotationNode typeName: nodes second]
       
    20 !
       
    21 
       
    22 classModifierNotAnnotation 
       
    23 
       
    24 	^super classModifierNotAnnotation ==> [:tokenKeyword | PJModifierNode keyword: tokenKeyword inputValue]
       
    25 !
       
    26 
       
    27 formalParameters 
       
    28 
       
    29 	^ super formalParameters ==> [:nodes | nodes second]
       
    30 !
       
    31 
       
    32 methodModifierNotAnnotation 
       
    33 
       
    34 	^super methodModifierNotAnnotation ==> [:tokenKeyword | PJModifierNode keyword: tokenKeyword inputValue]
       
    35 !
       
    36 
       
    37 qualifiedName
       
    38 	^ super qualifiedName
       
    39 		==> [ :nodes | 
       
    40 			nodes second notEmpty
       
    41 				ifTrue: [ self nameFromQualified: (Array with: nodes first withAll: (nodes second collect: [ :e | e second value ])) ]
       
    42 				ifFalse: [ PJSimpleNameNode identifier: nodes first value ] ]
       
    43 ! !
       
    44 
       
    45 !PPJavaParser methodsFor:'as yet unclassified'!
       
    46 
       
    47 endOfLineComment 
       
    48 ^ super endOfLineComment ==> [ :nodes | PJEndOfLineCommentsNode comment:  nodes second .].
       
    49 !
       
    50 
       
    51 floatingPointLiteral
       
    52 
       
    53 	 ^super floatingPointLiteral trim ==> [ :token | PJFloatLiteralNode newFrom: token inputValue ]
       
    54 !
       
    55 
       
    56 separator	
       
    57 
       
    58  ^super separator trim ==> [:token | PJSeparatorNode separatorValue: (token inputValue)]
       
    59 !
       
    60 
       
    61 traditionalComment
       
    62 ^ super traditionalComment ==> [ :nodes | PJTraditionalCommentsNode comment:  (nodes second ).].
       
    63 ! !
       
    64 
       
    65 !PPJavaParser methodsFor:'grammar-classes'!
       
    66 
       
    67 normalClassDeclaration 
       
    68 
       
    69 	^ super normalClassDeclaration 
       
    70 ! !
       
    71 
       
    72 !PPJavaParser methodsFor:'grammar-classes-method'!
       
    73 
       
    74 block
       
    75 	^ super block ==> [ :nodes | 
       
    76 			| blockNode |
       
    77 			blockNode := PJBlockNode new.
       
    78 			blockNode statements: nodes second.
       
    79 			blockNode]
       
    80 !
       
    81 
       
    82 constructorDeclaration 
       
    83 
       
    84 	^ super constructorDeclaration ==> [:nodes |
       
    85 		|constructor|
       
    86 		
       
    87 		constructor := PJConstructorDeclarationNode named: nodes third name.
       
    88 		constructor
       
    89 			statements: nodes eighth;
       
    90 			modifiers: nodes first;
       
    91 			returnType: nodes second;
       
    92 			parameters: nodes fourth.
       
    93 		constructor]
       
    94 !
       
    95 
       
    96 expressionStatement 
       
    97 	^ super expressionStatement ==> [ :nodes | 
       
    98 			| expressionStatementNode |
       
    99 			expressionStatementNode := PJExpressionStatementNode new.
       
   100 			expressionStatementNode expression: nodes first.
       
   101 			expressionStatementNode]
       
   102 !
       
   103 
       
   104 localVariableDeclaration
       
   105 	^ super localVariableDeclaration ==> [ :nodes | 
       
   106 			| declarationNode |
       
   107 			declarationNode := PJLocalVariableDeclarationStatementNode new.
       
   108 			declarationNode
       
   109 				type: nodes second;
       
   110 				declarators: (nodes third second collect: [:each | each second]) asOrderedCollection.
       
   111 			declarationNode declarators addFirst: nodes third first.
       
   112 			declarationNode]
       
   113 !
       
   114 
       
   115 localVariableDeclarationStatement 
       
   116 	^ super localVariableDeclarationStatement ==> [ :nodes | nodes first]
       
   117 !
       
   118 
       
   119 methodNotConstructorDeclaration 
       
   120 
       
   121 	^ super methodNotConstructorDeclaration ==> [:nodes |
       
   122 			| methodDeclarationNode |
       
   123 			methodDeclarationNode := PJMethodDeclarationNode named: nodes fourth name.
       
   124 			methodDeclarationNode modifiers: nodes first.
       
   125 			methodDeclarationNode returnType: nodes third.
       
   126 			methodDeclarationNode body: nodes eighth.
       
   127 			methodDeclarationNode parameters: nodes fifth.
       
   128 			methodDeclarationNode	
       
   129 				
       
   130 				 ]
       
   131 !
       
   132 
       
   133 normalParameterDecl  
       
   134 
       
   135 	^ super normalParameterDecl ==> [:nodes |
       
   136 		| declarator |
       
   137 		
       
   138 		declarator := PJParameterDeclaratorNode new.
       
   139 		declarator
       
   140 			modifiers: nodes first;
       
   141 			type: nodes second;
       
   142 			identifier: nodes third;
       
   143 			arrayLevel: nodes fourth size.
       
   144 		declarator]
       
   145 !
       
   146 
       
   147 normalParametersDecls
       
   148 	^ super normalParametersDecls ==> [ :nodes | 
       
   149 			| declarationNode |
       
   150 			((nodes second collect: [ :element | element second ]) asOrderedCollection)
       
   151 				addFirst: nodes first; yourself]
       
   152 !
       
   153 
       
   154 nullLiteral
       
   155 	 ^super nullLiteral trim ==> [:token | PJNullLiteralNode literalValue: (token inputValue)]
       
   156 !
       
   157 
       
   158 returnStatement
       
   159 	^ super returnStatement ==> [ :nodes | 
       
   160 			| returnNode |
       
   161 			returnNode := PJReturnStatementNode new.
       
   162 			returnNode expression: nodes second.
       
   163 			returnNode]
       
   164 !
       
   165 
       
   166 variableDeclarator 
       
   167 
       
   168 	^ super variableDeclarator ==> [:nodes |
       
   169 		| declarator |
       
   170 		
       
   171 		declarator := PJVariableDeclaratorNode new.
       
   172 		declarator
       
   173 			variable: nodes first;
       
   174 			arrayLevel: nodes second size.
       
   175 		nodes third ifNotNilDo: [:node | declarator initializer: node second].	
       
   176 		declarator]
       
   177 ! !
       
   178 
       
   179 !PPJavaParser methodsFor:'grammar-literals-boolean'!
       
   180 
       
   181 booleanLiteral 
       
   182 
       
   183  ^ super booleanLiteral trim ==> [:token | 
       
   184 		| value |
       
   185 		(token inputValue = 'false') 
       
   186 			ifTrue:  [ value := false]
       
   187 			ifFalse: [(token inputValue = 'true') 
       
   188 				ifTrue: [value := true]
       
   189 				ifFalse: [self error: 'A Boolean Literal must be either false or true']].
       
   190 		PJBooleanLiteralNode booleanValue: value.]
       
   191 ! !
       
   192 
       
   193 !PPJavaParser methodsFor:'grammar-literals-string'!
       
   194 
       
   195 additiveExpression 
       
   196 
       
   197 	^ super additiveExpression ==> self infixOpProcessor  .
       
   198 !
       
   199 
       
   200 andExpression 
       
   201 
       
   202 	^ super andExpression ==> self infixOpProcessor
       
   203 !
       
   204 
       
   205 characterLiteral 
       
   206  ^super characterLiteral trim ==> [:token | PJCharacterLiteralNode literalValue: (token inputValue allButFirst allButLast)]
       
   207 !
       
   208 
       
   209 classOrInterfaceType 
       
   210 	self flag: 'NA: temporary hack, should interpret nodes instead of returning first'.
       
   211 	^ super classOrInterfaceType ==> [ :nodes | nodes first ]
       
   212 !
       
   213 
       
   214 conditionalAndExpression 
       
   215 
       
   216 	^ super conditionalAndExpression ==> self infixOpProcessor
       
   217 !
       
   218 
       
   219 conditionalExpression 
       
   220 
       
   221  ^super conditionalExpression ==> [:node | node second ifNil: [node first] ifNotNil: [node]]
       
   222 !
       
   223 
       
   224 conditionalOrExpression 
       
   225 
       
   226 	^ super conditionalOrExpression ==> self infixOpProcessor
       
   227 !
       
   228 
       
   229 equalityExpression 
       
   230 
       
   231 	^ super equalityExpression ==> self infixOpProcessor
       
   232 !
       
   233 
       
   234 exclusiveOrExpression 
       
   235 
       
   236 	^ super exclusiveOrExpression ==> self infixOpProcessor
       
   237 !
       
   238 
       
   239 expression 
       
   240 
       
   241  ^super expression ==> [:node | node second ifNil: [node first] ifNotNil: [
       
   242 		|operation| 
       
   243 		operation := PJInfixOperationNode new.
       
   244 		operation
       
   245 			left: node first;
       
   246 			operator: node second first inputValue asSymbol;
       
   247 			right: node second second.
       
   248 		operation]]
       
   249 !
       
   250 
       
   251 identifier 
       
   252 
       
   253  ^super identifier ==> [:token | PJIdentifierNode newWithName: token inputValue]
       
   254 !
       
   255 
       
   256 identifierWithAccessors 
       
   257 
       
   258 	^ super identifierWithAccessors ==> [:node | node second isEmpty & node third isNil ifTrue: [node first] ifFalse: [node]]
       
   259 !
       
   260 
       
   261 ifStatement  
       
   262 
       
   263  ^super ifStatement ==> [:node |
       
   264 	| statementNode |
       
   265 	statementNode := PJIfStatementNode new.
       
   266 	statementNode
       
   267 		condition: node second;
       
   268 		thenPart: node third.
       
   269 	node fourth ifNotNil: [
       
   270 		statementNode elsePart: node fourth second].
       
   271 	statementNode]
       
   272 !
       
   273 
       
   274 inclusiveOrExpression 
       
   275 
       
   276  ^super inclusiveOrExpression ==> self infixOpProcessor
       
   277 !
       
   278 
       
   279 infixOpProcessor 
       
   280 
       
   281 	^ [:node |
       
   282 		(node second asOrderedCollection addFirst: node first; yourself) fold: [:left :current |
       
   283 			|operation| 
       
   284 			operation := PJInfixOperationNode new.
       
   285 			operation
       
   286 			left: left;
       
   287 			operator: current first inputValue asSymbol;
       
   288 			right: current second.
       
   289 			operation]]
       
   290 !
       
   291 
       
   292 instanceofExpression 
       
   293 
       
   294  ^super instanceofExpression ==> [:node | node second ifNil: [node first] ifNotNil: [node]]
       
   295 !
       
   296 
       
   297 integerLiteral 
       
   298 
       
   299  ^super integerLiteral trim ==> [ :token | PJIntegerLiteralNode newFrom: token inputValue ]
       
   300 !
       
   301 
       
   302 multiplicativeExpression 
       
   303 	^ super multiplicativeExpression ==> self infixOpProcessor
       
   304 !
       
   305 
       
   306 parExpression 
       
   307 
       
   308  ^super parExpression ==> [ :nodes | nodes second ]
       
   309 !
       
   310 
       
   311 primaryWithselectors 
       
   312 	^ super primaryWithselectors ==> [:node |
       
   313 		"JK: I have no idea, what this fold is supposed to do, 
       
   314 		 but #object: causes DNU, so I commented it out
       
   315 		"
       
   316 		node first ]
       
   317 		"(node second asOrderedCollection addFirst: node first; yourself) fold: [:inner :outer | outer object: inner]]
       
   318 		"
       
   319 !
       
   320 
       
   321 primitiveType 
       
   322 
       
   323  ^super primitiveType ==> [:token | PJPrimitiveTypeNode type: token inputValue]
       
   324 !
       
   325 
       
   326 relationalExpression 
       
   327 
       
   328  ^super relationalExpression ==> self infixOpProcessor
       
   329 !
       
   330 
       
   331 shiftExpression 
       
   332 
       
   333  ^super shiftExpression ==> [:node | node second ifEmpty: [node first] ifNotEmpty: [node]]
       
   334 !
       
   335 
       
   336 stringLiteral 
       
   337 
       
   338  ^super stringLiteral trim ==> [:token | PJStringLiteralNode literalValue: (token inputValue allButFirst allButLast)]
       
   339 !
       
   340 
       
   341 type
       
   342 	^ super type
       
   343 		==> [ :nodes | 
       
   344 			| pjtype |
       
   345 			nodes second notEmpty
       
   346 				ifTrue: [ pjtype := PJArrayTypeNode elementType: nodes first dimensions: nodes second size ]
       
   347 				ifFalse: [ pjtype := nodes first ].
       
   348 			pjtype ]
       
   349 !
       
   350 
       
   351 unaryPostfixExpression 
       
   352 	^ super unaryPostfixExpression ==> [:node | node second ifNil: [node first] ifNotNil: [node]]
       
   353 !
       
   354 
       
   355 whileStatement  
       
   356 
       
   357  ^super whileStatement ==> [ :nodes |
       
   358 	| while | 
       
   359 	while := PJWhileStatementNode new.
       
   360 	while expression: nodes second.
       
   361 	while statement: nodes third.
       
   362 	while ]
       
   363 ! !
       
   364 
       
   365 !PPJavaParser methodsFor:'private'!
       
   366 
       
   367 nameFromQualified: aCollection
       
   368 
       
   369 	^(aCollection size = 1)
       
   370 		ifTrue: [PJSimpleNameNode identifier: aCollection first]
       
   371           ifFalse: [
       
   372 			PJQualifiedNameNode 
       
   373 				name: (PJSimpleNameNode identifier: aCollection last)
       
   374 				qualifier: (self nameFromQualified: aCollection allButLast ).]
       
   375 ! !
       
   376