experiments/JavaCompiler.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 24 Apr 2013 00:07:32 +0100
branchdevelopment
changeset 2549 6ef03f1baa82
parent 2515 bcfe9f4dca6b
child 2578 fc6186a4961f
permissions -rw-r--r--
Bugfix in natives (array reflection). Caused by semi-automatic refactoring of natives.

"
 Copyright (c) 2010-2011 Jan Vrany, Jan Kurs & Marcel Hlopko,
                         SWING Research Group, Czech Technical University 
                         in Prague

 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
 files (the 'Software'), to deal in the Software without
 restriction, including without limitation the rights to use,
 copy, modify, merge, publish, distribute, sublicense, and/or sell
 copies of the Software, and to permit persons to whom the
 Software is furnished to do so, subject to the following
 conditions:

 The above copyright notice and this permission notice shall be
 included in all copies or substantial portions of the Software.

 THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
 OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
 HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
 WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
 FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
 OTHER DEALINGS IN THE SOFTWARE.
"
"{ Package: 'stx:libjava/experiments' }"

Object subclass:#JavaCompiler
	instanceVariableNames:'analyzer className imports packageName sourceCode sourceDir
		requestor classloader'
	classVariableNames:'Problems'
	poolDictionaries:''
	category:'Languages-Java-Support-Compiling'
!

JavaParserII subclass:#ClassSourceAnalyzer
	instanceVariableNames:'source package imports name terminator'
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaCompiler
!

!JavaCompiler class methodsFor:'documentation'!

copyright
"
 Copyright (c) 2010-2011 Jan Vrany, Jan Kurs & Marcel Hlopko,
                         SWING Research Group, Czech Technical University 
                         in Prague

 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
 files (the 'Software'), to deal in the Software without
 restriction, including without limitation the rights to use,
 copy, modify, merge, publish, distribute, sublicense, and/or sell
 copies of the Software, and to permit persons to whom the
 Software is furnished to do so, subject to the following
 conditions:

 The above copyright notice and this permission notice shall be
 included in all copies or substantial portions of the Software.

 THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
 OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
 HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
 WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
 FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
 OTHER DEALINGS IN THE SOFTWARE.

"
!

documentation
"
    An facade to Java compiler to compile Java classed from
    source (given as string).

    Internally, it uses ECJ. See stx.libjava.compiler.ecj.CompilerAdapter.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>
        Marcel Hlopko <marcel.hlopko@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
!

history

    "Created: #dotJavaPathname / 13-12-2012 / 00:02:03 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    Problems := WeakIdentityDictionary new.

    "Modified: / 15-04-2013 / 21:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'instance creation'!

new
    ^self basicNew initialize

    "Created: / 15-12-2012 / 16:48:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-04-2013 / 20:43:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

newAnalyzer
    ^ClassSourceAnalyzer new

    "Created: / 15-12-2012 / 16:58:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'accessing'!

problems
    ^Problems

    "Created: / 15-04-2013 / 21:39:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

problemsForClass: aClass
    ^Problems at: aClass ifAbsent:[#()].

    "Created: / 15-04-2013 / 22:07:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'compiler interface'!

compile: source
    "Compiles a new Groovy class given the source code"

    ^self new compile: source.

    "Created: / 27-02-2012 / 23:27:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

compile: source forClass: class inCategory: category notifying: requestor install: doInstall
    "We allways compile whole class"
    ^self compile: source register: true notifying: requestor

    "Created: / 21-02-2012 / 11:10:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-04-2013 / 00:11:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

compile:aString forClass:aClass inCategory:cat notifying:requestor
                 install:install skipIfSame:skipIfSame silent:silent

    "HACK.
     Problem:
     SmalltalkChunkFileReader always uses class's compiler to compile source. 
     However, when filing in Smalltalk extensions to Java classes, a Smalltalk 
     code is passed to me.

     See ClassCategoryReader>>fileInFrom:notifying:passChunk:single:silent:

     Workaround:
     Detect such a situation and compile using Smalltalk compiler...bad, I know.
     Better to move logic from Stream>>fileIn into SmalltalkChunkSourceFileReader.
     "

    (requestor isKindOf: SourceFileLoader) ifTrue:[
        ^Compiler compile:aString forClass:aClass inCategory:cat notifying:requestor
                 install:install skipIfSame:skipIfSame silent:silent
    ].

    self breakPoint:#jv.
    self error: 'Not (yet) supported'

    "Created: / 07-09-2012 / 10:35:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

compile: source register: register notifying: requestor
    "Called when a class is accepted"
    | classes |

    classes := self new
                requestor: requestor;
                compile: source.
    register ifTrue:[
        JavaVM registry registerClasses: classes.
    ].
    ^classes first.

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

evaluate: source notifying: requestor compile: doCompile
    "Called when a class is accepted"
    ^self compile: source register: true notifying: requestor

    "Created: / 04-04-2012 / 10:07:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-04-2013 / 00:11:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler methodsFor:'accessing'!

requestor
    ^ requestor
!

requestor:anObject
    requestor := anObject.
! !

!JavaCompiler methodsFor:'compiler interface'!

compile:source in: class notifying: requestor ifFail: block

    requestor class == SourceFileLoader ifTrue:[
        ^Compiler compile:source in: class notifying: requestor ifFail: block
    ].

    self error:'Not yet supported'.

    "Created: / 04-09-2012 / 23:56:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler methodsFor:'compiling'!

compile:source
    "Compiles a java class in given source code (passed as String).
     Return an array of JavaClass which are not yet registered in Java 
     class registry nor initialiized.

     To make it accessible for Java code, caller must register returned
     classes himself.

     Upon error, throws an exception"


    | javac classfiles classes problems |

    analyzer := self class newAnalyzer.
    analyzer analyze: source.
    analyzer fullName isNil ifTrue:[
        self error:'Syntax error - cannot determine class name'.
        ^self.
    ].

    classloader isNil ifTrue:[
        classloader := JavaClassReader classLoaderQuerySignal query.
        classloader isNil ifTrue:[
            classloader := JavaVM systemClassLoader.
        ]
    ].

    javac := (Java classForName:'stx.libjava.tools.compiler.ecj.CompilerAdapter') new: 
               classloader.

    javac compile: analyzer fullName source: source.

    "javac getResult hasErrors"
    javac getClassFiles size == 0 ifTrue:[
        ^self error:'Compilation failed - nothing compiled'
    ].

    classfiles := javac getClassFiles.
    classes := classfiles collect:[:each|
        (JavaClassReader readStream: each getBytes readStream)
            classLoader: classloader;
            setSource: source;
            setClassfileBytes: each getBytes;
            yourself].

    problems := javac getResult getProblems.
    problems notEmptyOrNil ifTrue:[
        classes do:[:each|
            Problems at: each put: problems
        ]
    ].

    ^classes.

    "Created: / 15-12-2012 / 23:04:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 15:36:16 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-04-2013 / 21:50:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer class methodsFor:'accessing'!

ignoredNames
    ^super ignoredNames , self instVarNames

    "Created: / 15-12-2012 / 17:17:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 29-03-2013 / 23:08:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer class methodsFor:'documentation'!

copyright
"
 Copyright (c) 2010-2011 Jan Vrany, Jan Kurs & Marcel Hlopko,
                         SWING Research Group, Czech Technical University 
                         in Prague

 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
 files (the 'Software'), to deal in the Software without
 restriction, including without limitation the rights to use,
 copy, modify, merge, publish, distribute, sublicense, and/or sell
 copies of the Software, and to permit persons to whom the
 Software is furnished to do so, subject to the following
 conditions:

 The above copyright notice and this permission notice shall be
 included in all copies or substantial portions of the Software.

 THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
 OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
 HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
 WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
 FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
 OTHER DEALINGS IN THE SOFTWARE.

"
!

history

    "Created: #imports / 08-12-2012 / 20:01:41 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: #imports / 09-12-2012 / 09:21:09 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

version_SVN
    ^ '§Id::                                                                                                                        §'
! !

!JavaCompiler::ClassSourceAnalyzer class methodsFor:'instance creation'!

analyze: javaSourceCode

    ^ self new analyze: javaSourceCode.

    "Created: / 08-12-2012 / 18:47:26 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified (format): / 15-12-2012 / 16:59:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

new
    ^self newStartingAt: #compilationUnit

    "Created: / 15-12-2012 / 17:15:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer methodsFor:'accessing'!

className
    <resource: #obsolete>
    ^ name

    "Created: / 08-12-2012 / 18:53:53 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-12-2012 / 17:04:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fullName
    ^package isNil 
        ifTrue:[name]
        ifFalse:[package , '.' , name]

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

imports
    ^imports ? #()

    "Created: / 08-12-2012 / 20:01:41 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 09-12-2012 / 09:21:09 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-12-2012 / 17:20:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

name
    ^ name
!

package
    ^ package
!

packageName
    <resource: #obsolete>
    ^package

    "Created: / 08-12-2012 / 18:50:26 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-12-2012 / 17:56:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer methodsFor:'grammar'!

importDeclaration 
"
    ^ ((self importKW) , (self staticKW) optional , qualifiedNameForImport 
        , (self tokenFor:';')).
        "
    ^ super importDeclaration ==> [:nodes | 
            imports isNil ifTrue:[imports := OrderedCollection new].
            imports add: (nodes at:3) value.
    ].

    "Created: / 15-12-2012 / 17:28:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

packageDeclaration 

"/        ^ (self  packageKW) , qualifiedName , (self tokenFor:';')
    ^super packageDeclaration ==> [:nodes| package := nodes second ].

    "Created: / 15-12-2012 / 22:44:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer methodsFor:'grammar-classes'!

typeNameIdentifier
    "    
    ^identifier
    "
    ^super typeNameIdentifier  ==> [:ident | 
            name := ident.
            terminator value
    ]

    "Created: / 15-04-2013 / 21:24:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::ClassSourceAnalyzer methodsFor:'parsing'!

analyze: aString 
    source := aString.
    terminator := [ ^ self ].
    self parse: source.

    "Created: / 08-12-2012 / 18:48:56 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-12-2012 / 17:04:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libjava/experiments/JavaCompiler.st,v 1.2 2013-02-25 11:15:34 vrany Exp $'
!

version_HG

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

version_SVN
    ^ '§Id::                                                                                                                        §'
! !


JavaCompiler initialize!