JavaMirror.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 16 Dec 2012 21:04:02 +0100
branchdirectory_structure_refactoring
changeset 1899 800c0f76adce
parent 1818 2e5ed72e7dfd
child 1848 b508cc4d4bf0
permissions -rw-r--r--
Closing branch directory_structure_refactoring

"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010
"
"{ Package: 'stx:libjava' }"

Object subclass:#JavaMirror
	instanceVariableNames:'klass reflection'
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Java-Classes'
!

JavaMirror subclass:#AlienClassMirror
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaMirror
!

JavaMirror subclass:#JavaArrayMirror
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaMirror
!

JavaMirror subclass:#JavaClassMirror
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaMirror
!

JavaMirror subclass:#JavaPrimitiveMirror
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaMirror
!

!JavaMirror class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010

"
!

documentation
"
    Instances of a JavaCassMirror provide unified access to
    Java reflective data (expeccially to methods, constructors and
    fields) as required by Java reflection API.

    Different classes may use different mirrors - for example,
    Smalltalk classes use a special mirror so non-Smalltalk classes
    and instances could be introspected and manipulated by standard 
    Java code.

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

    [instance variables:]
        klass ........ the real class on which receiver reflects
        reflection ... now always a JavaVM reflection.

    [class variables:]

    [see also:]

"
! !

!JavaMirror class methodsFor:'instance creation'!

forClass: aClass
    ^self new setKlass: aClass.

    "Created: / 31-07-2012 / 17:54:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror class methodsFor:'accessing'!

mirrorClassForAlienClass
    ^ AlienClassMirror

    "Created: / 31-07-2012 / 17:36:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mirrorClassForJavaArray
    ^ JavaArrayMirror

    "Created: / 31-07-2012 / 18:26:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mirrorClassForJavaClass
    ^ JavaClassMirror

    "Created: / 31-07-2012 / 17:36:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mirrorClassForJavaPrimitive
    ^ JavaPrimitiveMirror

    "Created: / 31-07-2012 / 18:27:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror methodsFor:'accessing'!

getClassLoader
    "Returns a class loader that loaded this class"
    ^self subclassResponsibility

    "Created: / 31-07-2012 / 18:25:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredConstructors: publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class. "

    ^self subclassResponsibility

    "Created: / 31-07-2012 / 18:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredFields: publicOnly
    "Returns an java.lang.reflect.Field[] with all constructors 
     declared by this class."

    ^self subclassResponsibility

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

getDeclaredMethods:publicOnly 
    "Returns an java.lang.reflect.Method[] with all methods 
     declared by this class."
    
    ^ self subclassResponsibility

    "Created: / 01-08-2012 / 11:07:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getGenericSignature
    "Returns Java generic signature (if a generic class) or nil"

    ^nil

    "Created: / 22-08-2012 / 11:57:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getInterfaces
    "Return a list if interfaces"

    ^self subclassResponsibility

    "Created: / 22-08-2012 / 11:05:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getModifiers
    "Return class modifiers (public/abstract/final...)"

    ^self subclassResponsibility

    "Created: / 22-08-2012 / 10:49:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getName
    "Returns name of the class"
    ^klass javaName

    "Created: / 22-08-2012 / 10:46:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getProtectionDomain
    ^nil

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

!JavaMirror methodsFor:'initialization'!

setKlass: aClass
    klass := aClass.
    reflection := JavaVM reflection

    "Created: / 31-07-2012 / 17:40:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror methodsFor:'instance creation-java.lang.reflect.*'!

create: ctorOrMethodClass for: class method: method signature: signature modifiers: modifiers parameterTyoes: parameterClasses exceptionTypes: exceptionClasses annotations: annotations
    "Creates a new java.lang.Constructor. Arguments:

        ctorOrMethodClass <java.lang.reflect.Constructor|java.lang.reflect.Method>
        class <Class>
        method <Method>
        signature <String>
        modifiers <SmallInteger>
        parameterClasses <Collection of Class>
        exceptionClasses <Collection of Class>
        annotations <JavaAnnotationContainer>
    "

    | ctorOrMethod |

    ctorOrMethod := ctorOrMethodClass new.

    ctorOrMethod
        instVarNamed: #clazz put: (reflection javaClassObjectForClass: "method m"class);
        instVarNamed: #slot put: method;
        instVarNamed: #modifiers put: modifiers;
        instVarNamed: #parameterTypes
            put: (reflection javaClassObjectArrayForClasses: parameterClasses);
        instVarNamed: #exceptionTypes
            put: (reflection javaClassObjectArrayForClasses: exceptionClasses);
        instVarNamed: #annotations put: annotations runtimeVisible bytes;
        breakPoint: #mh info: 'Please, replace ??? by code that accesses parameterAnnotations byte array'.
        "/ Look at java.lang.reflect.Method/Constructor to figure out what value is needed here."
        "/ Also, make sure there is a test in libjava tests (stx.libjava.tests.lang.XXXX, if not,
        "/ add some!!!!!!
        "/instVarNamed: #parameterAnnotations put: annotations ???;


    (method isJavaMethod and:[method signature notNil]) ifTrue:[
        ctorOrMethod                 
            instVarNamed: #signature
            put: (reflection javaStringObjectForString: method signature interned: true)
    ].

    ^ ctorOrMethod

    "Created: / 01-08-2012 / 10:24:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

createConstructorFor: class method: method signature: signature modifiers: modifiers parameterTyoes: parameterClasses exceptionTypes: exceptionClasses annotations: annotations
    "Creates a new java.lang.Constructor. Arguments:

        class <Class>
        method <Method>
        signature <String>
        modifiers <SmallInteger>
        parameterClasses <Collection of Class>
        exceptionClasses <Collection of Class>
        annotations <JavaAnnotationContainer>
    "

    | ctor |
    ctor := self create: (JavaVM classForName:'java.lang.reflect.Constructor')
                    for: class
                 method: method
              signature: signature 
              modifiers: modifiers 
         parameterTyoes: parameterClasses 
         exceptionTypes: exceptionClasses 
            annotations: annotations.
    ^ctor

    "Created: / 01-08-2012 / 10:20:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

createFieldFor: javaField 
    "given a java field, return the corresponding java.lang.Field
     instance for it."
    "
        See OpenJDK7 source:
        jdk7/hotspot/src/share/vm/runtime/reflection.cpp,
        oop Reflection::new_field"

    | field  clazz  name  slot  type  modifiers |

    clazz := reflection javaClassObjectForClass: klass.
    name := JavaVM reflection javaStringObjectForString: javaField name
                interned: true.
    slot := javaField index.
    type := JavaVM javaClassObjectForClass: javaField typeClass.
    modifiers := javaField accessFlags.
    field := (JavaVM classForName: 'java.lang.reflect.Field') new.
    field
        instVarNamed: #clazz put: clazz;
        instVarNamed: #name put: name;
        instVarNamed: #slot put: slot;
        instVarNamed: #type put: type;
        instVarNamed: #modifiers put: modifiers;
        yourself.
    javaField annotations 
        ifNotNil: [
            field instVarNamed: #annotations
                put: javaField annotations runtimeVisible rawAnnotations
        ].
    ^ field.

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

createMethodFor: class method: method name: name signature: signature modifiers: modifiers parameterTyoes: parameterClasses returnType: returnClass exceptionTypes: exceptionClasses annotations: annotations
    "Creates a new java.lang.Constructor. Arguments:

        class <Class>
        method <Method>
        name <String>
        signature <String>
        modifiers <SmallInteger>
        parameterClasses <Collection of Class>
        returnClass <Class>
        exceptionClasses <Collection of Class>
        annotations <JavaAnnotationContainer>
    "

    | mthd |
    mthd := self create: (JavaVM classForName:'java.lang.reflect.Method')
                    for: class
                 method: method
              signature: signature 
              modifiers: modifiers 
         parameterTyoes: parameterClasses 
         exceptionTypes: exceptionClasses 
            annotations: annotations.

    mthd
        instVarNamed: #name       put: (reflection javaStringObjectForString: name interned: true);
        instVarNamed: #returnType put: (reflection javaClassObjectForClass: returnClass);
        instVarNamed: #annotationDefault put: (annotations default bytes).

    ^mthd

    "Created: / 01-08-2012 / 10:46:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror::AlienClassMirror class methodsFor:'documentation'!

documentation
"
    Specialized mirror for Smalltalk (and all other 
    non-Java classes)

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaMirror::AlienClassMirror methodsFor:'accessing'!

getClassLoader
    "Returns a class loader that loaded this class"

    ^ (Java classForName:'stx.libjava.ClassLoader') instVarNamed: #scl.

    "Modified: / 31-07-2012 / 18:34:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredConstructors:publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class"

    "Here, return onlu default constructor. Later, all methods annotated
     with <jsignature: #'<init>(...)V'> wil be returned as well"

    | ctors |

    ctors := OrderedCollection new.
    klass selectorsAndMethodsDo:[:sel :mthd|
        (self isJavaConstructor: mthd selector: sel) ifTrue:[
            ctors add: (self getDeclaredConstructorFor: mthd).
        ].
    ].

    ctors isEmpty ifTrue:[
        "/If no constructor is found, fake default one...    
        ctors add: (self getDeclaredConstructorFor: (klass lookupMethodFor: #initialize)).
    ].

    ^(JavaVM classForName:'java.lang.reflect.Constructor') javaArrayClass withAll: ctors

    "Modified: / 22-08-2012 / 11:37:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredFields:publicOnly
    "Returns an java.lang.reflect.Field[] with all constructors 
     declared by this class."

    | fields |    

    fields := OrderedCollection new.

    klass instVarNames withIndexDo:[:nm :index|
        | field |

        field := JavaField new.
        field 
            setAccessFlags: JavaConstants ACC_PROTECTED;
            setClass: klass;
            setIndex: klass superclass instSize + index;
            setDescriptor: #'Ljava/lang/Object;';
            setName: nm.

        fields add: (self createFieldFor: field)
    ].

    ^ (JavaVM classForName:'java.lang.reflect.Field') javaArrayClass 
        withAll:fields

    "Modified: / 22-08-2012 / 12:19:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredMethods:publicOnly 
    "Returns an java.lang.reflect.Method[] with all methods 
     declared by this class"

    | methods |

    methods := OrderedCollection new.
    klass selectorsAndMethodsDo:[:sel :mthd|
        (self isJavaMethod: mthd selector: sel) ifTrue:[
            methods add: (self getDeclaredMethodFor: mthd).
        ].
    ].
    ^(JavaVM classForName:'java.lang.reflect.Method') javaArrayClass withAll: methods

    "Modified: / 22-08-2012 / 11:36:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getInterfaces
    "Return a list if interfaces"

    ^ Array with: (JavaVM classForName: 'java.lang.Cloneable')

    "Modified: / 22-08-2012 / 11:06:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getModifiers
    "Return class modifiers (public/abstract/final...)"

    ^ JavaConstants ACC_PUBLIC

    "Modified: / 22-08-2012 / 11:01:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getName
    "Returns name of the class"
    ^'SMALLTALK.' , klass name

    "Created: / 22-08-2012 / 10:47:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror::AlienClassMirror methodsFor:'accessing-private'!

getDeclaredConstructorFor: method
    ^ self 
        createConstructorFor: klass 
                      method: method 
                   signature: (self getSignatureForConstructor: method)
                   modifiers: JavaConstants ACC_PUBLIC 
              parameterTyoes: #() 
              exceptionTypes: #() 
                 annotations: JavaMethodAnnotationContainer new

    "Created: / 22-08-2012 / 11:36:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredMethodFor:method
    | signature name java_lang_Object |

    signature := self getSignatureForMethod: method short: false.
    name := signature upTo: $(.
    java_lang_Object := JavaVM classNamed: 'java.lang.Object'.
    ^ self 
        createMethodFor: klass 
                      method: method 
                        name: name
                   signature: signature
                   modifiers: JavaConstants ACC_PUBLIC 
              parameterTyoes: ((1 to: method selector numArgs) collect:[:i|java_lang_Object])
                  returnType: java_lang_Object
              exceptionTypes: #() 
                 annotations: JavaMethodAnnotationContainer new

    "Created: / 22-08-2012 / 11:36:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getSignatureForConstructor: method
    | signature |

    signature :=
        (String streamContents:[:s|
            s nextPutAll: '<init>('.
            method selector numArgs timesRepeat:[
                s nextPutAll:'Ljava/lang/Object;'.
            ].
            s nextPutAll: ')V'.
        ]) asSymbol.
    ^signature

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

getSignatureForMethod: method short: short
    | selector signature |

    selector := method selector.
    signature :=
        (String streamContents:[:s|
            short ifTrue:[
                s nextPutAll: (selector upTo: $:)
            ] ifFalse:[
                selector numArgs == 1 ifTrue:[
                    s nextPutAll: (selector copyTo: selector size - 1)
                ] ifFalse:[
                    s nextPutAll: (selector copyReplaceAll: $: with: $_)
                ]
            ].
            s nextPut: $(.
            method selector numArgs timesRepeat:[
                s nextPutAll:'Ljava/lang/Object;'.
            ].
            s nextPutAll: ')'.
            s nextPutAll:'Ljava/lang/Object;'.
        ]) asSymbol.
    ^signature

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

!JavaMirror::AlienClassMirror methodsFor:'testing-private'!

isJavaConstructor: mthd selector: sel

    ^sel startsWith: #initialize

    "Created: / 22-08-2012 / 11:47:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isJavaMethod: mthd selector: sel

    ^sel isBinarySelector not 
        and:[(self isJavaConstructor: mthd selector: sel) not]

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

!JavaMirror::JavaArrayMirror methodsFor:'accessing'!

getClassLoader
    "Returns a class loader that loaded this class"

    ^ klass javaComponentClass javaMirror getClassLoader

    "Modified: / 31-07-2012 / 18:35:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredConstructors:publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class"

    ^ (JavaVM classForName:'java.lang.reflect.Constructor') javaArrayClass new:0.

    "Modified: / 31-07-2012 / 18:41:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredFields:publicOnly
    "Returns an java.lang.reflect.Field[] with all constructors 
     declared by this class."

    ^(JavaVM classForName:'java.lang.reflect.Field') javaArrayClass new:0.

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

getDeclaredMethods:publicOnly 
    "Returns an java.lang.reflect.Method[] with all methods 
     declared by this class"
    
    ^ (JavaVM classForName:'java.lang.reflect.Method') javaArrayClass new:0.

    "Modified: / 01-08-2012 / 11:08:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getInterfaces
    "Return a list if interfaces"

    ^ Array 
        with: (JavaVM classForName: 'java.lang.Cloneable')
        with: (JavaVM classForName: 'java.io.Serializable')

    "Modified: / 22-08-2012 / 11:06:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getModifiers
    "Return class modifiers (public/abstract/final...)"

    ^ JavaConstants ACC_ABSTRACT | JavaConstants ACC_FINAL | JavaConstants ACC_PUBLIC

    "Modified: / 22-08-2012 / 11:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror::JavaClassMirror class methodsFor:'documentation'!

documentation
"
    A specialized mirror for all Java classes

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaMirror::JavaClassMirror methodsFor:'accessing'!

getClassLoader
    "Returns a class loader that loaded this class"

    ^ klass classLoader

    "Modified: / 31-07-2012 / 18:26:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredConstructors:publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class"

    | ctors |

    ctors := OrderedCollection new.
    klass selectorsAndMethodsDo:[:sel :mthd|
        (mthd isJavaConstructor and:[publicOnly not or:[mthd isPublic]]) ifTrue:[
            ctors add: (self getDeclaredConstructorFor: mthd).
        ].
    ].
    ^(JavaVM classForName:'java.lang.reflect.Constructor') javaArrayClass withAll: ctors

    "Modified: / 01-08-2012 / 11:04:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredFields:publicOnly
    "Returns an java.lang.reflect.Field[] with all constructors 
     declared by this class."

    | fields |    

    fields := klass fields , klass staticFields.
    publicOnly ifTrue:[ fields := fields select:[:f | f isPublic ] ].
    JavaClassReader classLoaderQuerySignal answer: klass classLoader do:[
        fields := fields collect:[:f | self createFieldFor:f ].
    ].
    ^ (JavaVM classForName:'java.lang.reflect.Field') javaArrayClass 
        withAll:fields

    "Modified: / 22-08-2012 / 12:10:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredMethods:publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class"

    | methods |

    methods := OrderedCollection new.
    klass selectorsAndMethodsDo:[:sel :mthd|
        mthd isJavaMethod and:[
            (mthd isJavaConstructor not 
                and:[mthd isJavaStaticInitializer not
                and:[publicOnly not or:[mthd isPublic]]]) ifTrue:[
                methods add: (self getDeclaredMethodFor: mthd).
            ]
        ].
    ].
    ^(JavaVM classForName:'java.lang.reflect.Method') javaArrayClass withAll: methods

    "Modified: / 19-09-2012 / 16:26:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getGenericSignature
    "Returns Java generic signature (if a generic class) or nil"

    ^klass signatureJ

    "Created: / 22-08-2012 / 11:58:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getInterfaces
    "Return a list if interfaces"

    ^ klass interfaces

    "Modified: / 22-08-2012 / 11:08:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getModifiers
    "Return class modifiers (public/abstract/final...)"

    | modifiers |    

    "According to OpenJDK JVM, strip ACC_SUPER"
    modifiers := (klass accessFlags & JavaConstants ACC_SUPER bitInvert) & 16r7FFF.
    "JV@2011-10-30: It seems that private inner classes has no
     private bit set, sigh"
    (modifiers & 16r0007) == 0 ifTrue:[
        modifiers := modifiers | JavaConstants ACC_PRIVATE.
    ].
    ^modifiers

    "Modified: / 22-08-2012 / 11:03:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getProtectionDomain
    ^klass protectionDomain

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

!JavaMirror::JavaClassMirror methodsFor:'accessing-private'!

getDeclaredConstructorFor: method

    ^self createConstructorFor: method javaClass
                        method: method
                     signature: method signature
                     modifiers: method accessFlags
                parameterTyoes: (method descriptor parameterClassesUsingClassLoader: method javaClass classLoader)
                exceptionTypes: method exceptionClasses
                   annotations: method method annotations.

    "Created: / 01-08-2012 / 00:46:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredMethodFor: method

    ^self      createMethodFor: method javaClass
                        method: method
                          name: (method selector upTo: $()
                     signature: method signature
                     modifiers: method accessFlags
                parameterTyoes: (method descriptor parameterClassesUsingClassLoader: method javaClass classLoader)
                    returnType: (method descriptor returnClassUsingClassLoader: method javaClass classLoader)
                exceptionTypes: method exceptionClasses
                   annotations: method method annotations.

    "Created: / 01-08-2012 / 11:11:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror::JavaPrimitiveMirror methodsFor:'accessing'!

getClassLoader
    "Returns a class loader that loaded this class"

    ^ nil

    "Modified: / 31-07-2012 / 18:35:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredConstructors:publicOnly
    "Returns an java.lang.reflect.Constructor[] with all constructors 
     declared by this class"

    ^ (JavaVM classForName:'java.lang.reflect.Constructor') javaArrayClass new:0.

    "Modified: / 31-07-2012 / 18:41:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredFields:publicOnly
    "Returns an java.lang.reflect.Field[] with all constructors 
     declared by this class."

    ^(JavaVM classForName:'java.lang.reflect.Field') javaArrayClass new:0.

    "Modified: / 22-08-2012 / 12:03:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getDeclaredMethods:publicOnly 
    "Returns an java.lang.reflect.Method[] with all methods 
     declared by this class"
    
    ^ (JavaVM classForName:'java.lang.reflect.Method') javaArrayClass new:0.

    "Modified: / 01-08-2012 / 11:08:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getInterfaces
    "Return a list if interfaces"

    ^ #()

    "Modified: / 22-08-2012 / 11:07:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getModifiers
    "Return class modifiers (public/abstract/final...)"

    ^ JavaConstants ACC_ABSTRACT | JavaConstants ACC_FINAL | JavaConstants ACC_PUBLIC

    "Modified: / 22-08-2012 / 11:02:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaMirror class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !