experiments/JavaCompiler.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 19 Jan 2013 19:23:53 +0000
branchrefactoring-vmdata
changeset 1983 03dcc3899eea
parent 1921 a395d5c696b9
child 2069 75d40b7b986f
permissions -rw-r--r--
Make all native methods source ending with ': nativeContext'. This will ease automatic refactoring. Also, rename method categories with prefix 'OLD -'.

"
 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'
	classVariableNames:'CurrentCompilerClass JavaFileOutDirectory'
	poolDictionaries:''
	category:'Languages-Java-Support-Compiling'
!

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

JavaCompiler subclass:#Javac
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaCompiler
!

JavaCompiler subclass:#JavacExternal
	instanceVariableNames:''
	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 inteface to Java compiler to compile Java classed from
    source (given as string).

    Real compilation is implemented in one of my subclasses.

    [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)

    CurrentCompilerClass := Javac.
    JavaFileOutDirectory := Filename newTemporaryDirectory.

    "Modified: / 15-12-2012 / 23:02:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'instance creation'!

new
    ^(CurrentCompilerClass ? self) basicNew initialize

    "Created: / 15-12-2012 / 16:48:31 / 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'!

fileOutDirectory
    ^JavaFileOutDirectory

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

!JavaCompiler class methodsFor:'compiling'!

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

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

     Upon error, throws an exception"

    ^ self new compile: source.

    "Created: / 06-12-2012 / 22:14:12 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
    "Modified (comment): / 15-12-2012 / 16:52:27 / 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"


    ^ self subclassResponsibility

    "Modified (comment): / 02-01-2013 / 16:32:16 / 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>"
! !

!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>"
!

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'!

normalClassDeclaration
    "
        ^ classModifiers , (self  classKW) , self typeNameIdentifier ,
                typeParameters optional,
                jsuper optional,
                interfaces optional ,
                classBody"
    
    ^ super normalClassDeclaration 
        ==> [:nodes | 
            name := (nodes at:3) value.
            terminator value
        ]

    "Created: / 15-12-2012 / 17:08:20 / 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::Javac class methodsFor:'documentation'!

documentation
"
    A Java compiler that uses Java 6 Tool API (i.e., loads javac into
    running libjava)

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

    [instance variables:]

    [class variables:]

    [see also:]
        http://today.java.net/pub/a/today/2008/04/10/source-code-analysis-using-java-6-compiler-apis.html

"
! !

!JavaCompiler::Javac 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 |

    analyzer := self class newAnalyzer.
    analyzer analyze: source.
    javac := (Java classForName:'stx.libjava.tools.compiler.JavaCompilerAdapter') new.
    (javac compile: analyzer name source: source) ifFalse:[
        self error:'Compilation failed for whatever reason!!'.
    ].

    classfiles := javac getClassFiles toArray.
    ^classfiles collect:[:each|JavaClassReader readStream: each getBytes readStream].

    "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: / 02-01-2013 / 16:33:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompiler::JavacExternal class methodsFor:'documentation'!

documentation
"                                        
    A Java compiler that calls external javac command. 
    Unfinished.

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaCompiler::JavacExternal 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"


    | classDir  wasSuccessful  package  packageAsPath  compiledClass  result |
    sourceCode := source.
    sourceDir := Java cacheDirectory.
    analyzer := self analyzerFor: sourceCode.
        self fileOutSourceCode.
    result := self runCompiler.
    ^ result.

    "Created: / 06-12-2012 / 23:13:47 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
    "Modified: / 07-12-2012 / 10:05:03 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
    "Modified: / 12-12-2012 / 23:58:04 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified (comment): / 02-01-2013 / 16:32:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

runCompiler
    | result  compiledClass |
    result := OperatingSystem 
            executeCommand: 'javac -cp "' , Java classPathAsString , ':' , sourceDir pathName
                    , '" ' , self dotJavaPathname
            inDirectory: sourceDir.
    result ifFalse: [ self error: 'Compilation of Java class failed' ].
    compiledClass := JavaClassReader 
            readFile: sourceDir / self dotClassPathname
            ignoring: #().
    compiledClass classInit.
    compiledClass setSource: sourceCode.
    ^ compiledClass.

    "Created: / 08-12-2012 / 22:02:47 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 13-12-2012 / 00:11:43 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
! !

!JavaCompiler::JavacExternal methodsFor:'private'!

analyzerFor: sourceCode
   ^ self newAnalyzer analyze: sourceCode.

    "Created: / 08-12-2012 / 21:57:00 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 15-12-2012 / 16:58:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

className
    className ifNil: [ className := analyzer className. ].
    ^ className.

    "Created: / 12-12-2012 / 23:59:08 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

classPackageAsPath
    | name |
    name := self packageName.
    name isNil ifTrue: [ ^ '' ].
    ^ (name copyReplaceAll: $. with: Filename separator) , Filename separator.

    "Created: / 08-12-2012 / 22:50:40 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 13-12-2012 / 00:02:18 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

dotClassPathname
    ^ self classPackageAsPath , (self className , '.class').

    "Created: / 13-12-2012 / 00:01:49 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

dotJavaPathname
    ^ self classPackageAsPath , (self className , '.java').

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

fileOut: source
    "Files out given source into a file under JavaFileOutDirectory.
     into proper directory (as javac requires). The directory is created
     if it does not exists.

     Returns a full filename of the filed-out source"

    | analyzer filename |
    analyzer := self class newAnalyzer.
    analyzer analyze: source.
    filename := JavaFileOutDirectory / 
                    ((analyzer package ? '') copyReplaceAll:$. with: Filename separator) /
                    (analyzer name , '.java').
    filename directory exists ifFalse:[
        filename directory recursiveMakeDirectory
    ].
    filename writingFileDo:[:f|f nextPutAll: source].
    ^filename.

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

fileOutSourceCode
    | path |
    path := sourceDir / self dotJavaPathname.
    path directory recursiveMakeDirectory.                     
    path exists ifTrue: [ path delete ].
    path createAsEmptyFile.
    path writingFileDo: [:out | out nextPutAll: sourceCode ].

    "Created: / 08-12-2012 / 22:43:30 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 13-12-2012 / 00:09:03 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

fullClassName
    | package |
    package := self packageName.
    package ifNil: [ ^ self className ].
    ^ package , '.' , self className.

    "Created: / 09-12-2012 / 20:30:13 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
    "Modified: / 13-12-2012 / 00:03:07 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
!

packageName
    packageName ifNil: [ packageName := analyzer packageName ].
    ^ packageName.

    "Created: / 12-12-2012 / 23:59:00 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
! !

!JavaCompiler class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '§Id::                                                                                                                        §'
! !

JavaCompiler initialize!