tools/JavaParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 03 Oct 2013 10:34:10 +0200
changeset 2764 dfac4cae11e9
parent 2678 c865275e48a7
child 2731 13f5be2bf83b
permissions -rw-r--r--
Added GroovySourceHighlighter

"{ Package: 'stx:libjava/tools' }"

JavaParserII subclass:#JavaParser
	instanceVariableNames:'builder'
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Java-Parser'
!

!JavaParser class methodsFor:'documentation'!

documentation
"
    PetitParser based parser for Java. One may pass in a builder, that
    is called whenever a rule is parsed. Builder can build AST or do
    some analysis. 

    Unfinished.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaParser class methodsFor:'accessing'!

namesToIgnore

        ^super namesToIgnore ,
        #(builder)

    "Created: / 03-04-2013 / 23:51:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParser methodsFor:'accessing'!

builder
    ^ builder
!

builder:aJavaParseNodeBuilder
    builder := aJavaParseNodeBuilder.
! !

!JavaParser methodsFor:'grammar'!

compilationUnit 
        "
        ^ 
        (annotations optional, packageDeclaration) optional , 
        importDeclaration star , 
        typeDeclaration star ,
        (self tokenParserFor:#EOF) end
        "

        ^super compilationUnit ==> [:nodes |
            | pkg |

            pkg := (nodes at:1) notNil ifTrue:[(nodes at:1) second] ifFalse:[nil].
            builder newSourceFile_package: pkg imports: (nodes at:2) types: (nodes at:3)            
        ]

    "Created: / 03-04-2013 / 23:18:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-04-2013 / 20:24:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

importDeclaration
    "
    ^ ((self importKW) , (self staticKW) optional , qualifiedNameForImport 
        , (self tokenFor:';')).
    "
    ^ super importDeclaration ==> [:nodes|
        builder newImportDeclaration: (nodes at: 3)
    ]

    "Created: / 25-08-2013 / 11:45:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

packageDeclaration 
    "
        ^ (self  packageKW) , qualifiedName , (self tokenFor:';')
    "
    ^super packageDeclaration ==> [:nodes |
        builder newPackageDeclaration: (nodes at:2)
    ]

    "Created: / 03-04-2013 / 23:48:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

typeDeclaration

        ^ ((self tokenFor: ';') ==> nil) / classOrInterfaceDeclaration

    "Created: / 03-04-2013 / 23:58:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParser methodsFor:'grammar-classes'!

classBody 

    ^ super classBody ==> [:nodes | nodes second reject:[:e|e isNil] ]

    "Created: / 24-08-2013 / 01:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formalParameters 

"/        ^ (self tokenFor: '(') ,
"/        formalParameterDecls optional ,
"/        (self tokenFor: ')')
    ^ super formalParameters ==> [:nodes | nodes second ]

    "Created: / 31-08-2013 / 23:09:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

normalClassDeclaration 
    "
        ^ classModifiers , (self  classKW) , self typeNameIdentifier ,
                typeParameters optional,
                jsuper optional,
                interfaces optional ,
                classBody
    "
    ^ super normalClassDeclaration ==> [:nodes|
        builder newClassDeclaration_modifiers: (nodes at:1)
                    name: (nodes at:3)
                    typeParameters: (nodes at:4)
                    superclass: (nodes at:5)
                    interfaces: (nodes at:6)
                    members: (nodes at:7)
    ]

    "Created: / 04-04-2013 / 00:04:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

normalParameterDecls
"/    ^ normalParameterDecl , ((self tokenFor: ',') , normalParameterDecl) star
    ^ super normalParameterDecls ==> [:nodes|
"/        | params |
"/
"/        params := OrderedCollection new.
"/        params add: nodes first.
"/        nodes second do:[:pair|
"/            params add: pair second
"/        ].
"/        params.
        nodes.
    ].

    "Created: / 01-09-2013 / 09:30:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

normalParameterDeclsAndEllipsisParameterDecl
"/    ^ normalParameterDecls , (self tokenFor: ',') , ellipsisParameterDecl
    ^ super normalParameterDeclsAndEllipsisParameterDecl ==> [:nodes |
        nodes first copyWith: nodes third.
    ]

    "Created: / 01-09-2013 / 09:29:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParser methodsFor:'grammar-classes-method'!

constructorDeclaration

"/        ^ constructorModifiers optional , 
"/           typeParameters optional , 
"/           self constructorNameIdentifier,
"/           formalParameters ,
"/           throws optional , 
"/           block

    ^ super constructorDeclaration ==> [:nodes |
        builder newConstructorDeclaration_modifiers: (nodes at:1)
                    typeParameters: (nodes at: 2)
                        parameters: (nodes at: 4)
                        exceptions: (nodes at: 5)
                              body: (nodes at: 6)
    ]

    "Created: / 24-08-2013 / 01:57:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

methodNotConstructorDeclaration

"/        ^ methodModifiers,
"/           typeParameters optional,
"/           ((self  voidKW) / type),
"/           self methodNameIdentifier,
"/           formalParameters ,
"/           emptySquaredParenthesis star ,
"/           throws optional,
"/           (block / (self tokenFor: ';'))

    ^ super methodNotConstructorDeclaration ==> [:nodes |
        builder newMethodDeclaration_modifiers: (nodes at:1)
                    typeParameters: (nodes at: 2)
                        returnType: (nodes at: 3)
                              name: (nodes at: 4)
                        parameters: (nodes at: 5)
                        exceptions: (nodes at: 7)
                              body: (nodes at: 8)      
    ]

    "Created: / 24-08-2013 / 02:00:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParser methodsFor:'initialization'!

initialize
    super initialize.
    builder := JavaParseNodeBuilder new.

    "Created: / 03-04-2013 / 23:52:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeProduction: name
    "Given a production name, return it a PPParser for it"

    | production |

    production := super initializeProduction: name.
    "Ugly!!"
    (production class == PPActionParser) ifTrue:[
        | oldBlock |
        oldBlock := production block.
        production setBlock:[:nodes|
            | first last start stop node |

            first := nodes.
            [ first isSequenceable and:[first notEmpty] ] whileTrue:[
                first := first first
            ].
            last := nodes.
            [ last isSequenceable and:[last notEmpty] ] whileTrue:[
                last := last last
            ].

            start := first perform: #startPosition ifNotUnderstood:[nil].
            stop := last perform: #endPosition ifNotUnderstood:[nil].
            builder start: start stop: stop.
            node := oldBlock value: nodes.
"/            (node isKindOf: JavaDeclarationNode) ifTrue:[
"/                | comments javadoc streamPos |
"/
"/                comments := scanner comments.
"/                javadoc := comments detectLast:[:comment|comment last < start] ifNone:nil.
"/                javadoc notNil ifTrue:[
"/                    streamPos := scanner sourceStream position.
"/                    scanner sourceStream position: javadoc first.
"/                    (scanner sourceStream next: 3) = '/**' ifTrue:[
"/                        node javadoc: javadoc.
"/                    ].
"/                    scanner sourceStream position: streamPos
"/                ].
"/            ].
            node
        ].

    ].
    ^ production

    "Created: / 25-08-2013 / 11:00:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-08-2013 / 03:00:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaParser class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libjava/tools/JavaParser.st,v 1.3 2013-09-06 00:45:27 vrany Exp $'
!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '§Id§'
! !