tools/JavaSourceDocument.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 10 Sep 2013 05:04:41 +0100
branchdevelopment
changeset 2721 ceb9ed115183
parent 2718 b3fe904a2fc7
child 2726 6971720de5a4
permissions -rw-r--r--
Added source line number to JavaSourceRef. Used for scrolling to the method header, skipping the Javadoc.

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

Object subclass:#JavaSourceDocument
	instanceVariableNames:'javaClass sourceText sourceTree sourceLineEnds sourceTreeLock'
	classVariableNames:'Cache CacheSize Job'
	poolDictionaries:''
	category:'Languages-Java-Tools-Source'
!

!JavaSourceDocument class methodsFor:'documentation'!

documentation
"
    JavaSourceDocument object keeps various useful information about one source 
    file. In particular, it keeps parse tree and pre-highlighted source.

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaSourceDocument class methodsFor:'initialization'!

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

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

    CacheSize := 25.
    Cache := OrderedCollection new: CacheSize * 2 "To avoid excessive shifting...".
    Job := BackgroundQueueProcessingJob named: 'java parsing job' on:[:block | block value ].

    "Modified: / 06-09-2013 / 17:45:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSourceDocument class methodsFor:'instance creation'!

for: aJavaClass
    ^self new javaClass: aJavaClass.

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

!JavaSourceDocument class methodsFor:'accessing'!

cachedDocumentFor: aJavaClass
    "Returns a cached document for given class or nil if no cached 
     document is found."

    Cache withIndexDo:[:document :index|
        document javaClass == aJavaClass ifTrue:[
            "/ Move that document towards the end so it'll be less likely
            "/ to be removed
            index < Cache size ifTrue:[
                Cache swap: index with: index + 1.                
            ].
            ^ document.
        ]
    ].
    ^ nil

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

cachedDocumentFor: aJavaClass put: aJavaSourceDocument
    "Stores given source document in the cache"

    self assert: aJavaSourceDocument javaClass == aJavaClass.
    Cache size = CacheSize ifTrue:[
        Cache removeFirst.
    ].
    Cache addLast: aJavaSourceDocument

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

!JavaSourceDocument methodsFor:'accessing'!

javaClass
    ^ javaClass
!

javaClass:aJavaClass
    aJavaClass == javaClass ifTrue:[
        ^ self
    ].
    javaClass notNil ifTrue:[
        self error: 'Class already set!!'
    ].
    javaClass := aJavaClass.
    self initializeSourceTree.

    "Modified: / 06-09-2013 / 17:51:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sourceLineToOffset: lineNr
    lineNr == 1 ifTrue:[ ^ 1 ].
    ^  (sourceLineEnds at: lineNr - 1) + 1.

    "Created: / 08-09-2013 / 10:52:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sourceOffsetToLine: offset

    |low    "{ Class: SmallInteger}"
     high   "{ Class: SmallInteger}"
     middle "{ Class: SmallInteger}"
     element|

    "
     we can of course use a binary search - since the elements are sorted
    "
    low := 1.
    high := sourceLineEnds size.
    [low > high] whileFalse:[
        middle := (low + high) // 2.
        element := sourceLineEnds at:middle.
        element < offset ifTrue:[
            "middleelement is smaller than object"
            low := middle + 1
        ] ifFalse:[
            high := middle - 1
        ]
    ].
    ^ low

    "Created: / 10-09-2013 / 03:40:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sourceText
    ^ sourceText
!

sourceText:aText
    sourceText := aText.
!

sourceTree
    sourceTree isNil ifTrue:[
        sourceTreeLock notNil ifTrue:[
            sourceTreeLock wait.
        ].
    ].
    ^ sourceTree

    "Modified: / 06-09-2013 / 22:58:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSourceDocument methodsFor:'debugging'!

inspector2TabParseTree

    SmallSense::ParseNodeInspector notNil ifTrue:[
        ^self newInspector2Tab
            label: 'Parse Tree';
            priority: 35;
            application: (SmallSense::ParseNodeInspector new node: sourceTree source: sourceText)
    ].
    ^nil

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

inspector2Tabs
    | tabs |

    tabs := super inspector2Tabs.
    (SmallSense::ParseNodeInspector notNil and:[sourceTree notNil and:[sourceText notNil]]) ifTrue:[
        tabs := tabs , #(inspector2TabParseTree)
    ].
    ^tabs

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

!JavaSourceDocument methodsFor:'initialization-private'!

initializeSourceRefsInMethods
    | typeName  typeNode |

    typeName := javaClass lastName.
    (typeName includes: $$) ifTrue: [
        | components |

        components := typeName tokensBasedOn: $$.
        typeNode := sourceTree types 
                detect: [:each | each name = components first ].
        2 to: components size do: [:i | 
            typeNode := typeNode memberTypes 
                    detect: [:each | each name = (components at: i) ].
        ].
    ] ifFalse: [
        typeNode := sourceTree types detect: [:each | each name = typeName ].
    ].
    javaClass methodDictionary 
        keysAndValuesDo: [:selector :method | 
            | descriptor  methodName  methodNodes  methodNode  source |

            method isJavaMethod ifTrue:[
                descriptor := method descriptor.
                methodName := descriptor name.
                methodName = '<init>' ifTrue: [
                    methodName := typeName.
                ].
                methodNodes := typeNode methods 
                        select: [:each | 
                            each selector = methodName 
                                and: [ each arguments size == descriptor parameters size ]
                        ].
                methodNodes notEmptyOrNil ifTrue: [
                    methodNodes size == 1 ifTrue: [
                        methodNode := methodNodes anElement.
                    ] ifFalse: [
                        method hasLineNumberInformation ifTrue: [
                            | line0  offset0 |

                            line0 := method lineNumberForPC: 1.
                            offset0 := self sourceLineToOffset: line0.
                            methodNodes := typeNode methods 
                                    select: [:each | 
                                        offset0 between: each declarationSourceStart
                                            and: each declarationSourceEnd + 1
                                    ].
                            methodNodes size == 1 ifTrue: [
                                methodNode := methodNodes anElement.
                            ]
                        ].
                        methodNode isNil ifTrue: [
                            | 
                            "/ OK, search by parameter types...
                             i |

                            i := 1.
                            [
                                (methodNodes size > 1) and: [ i <= descriptor parameters size ]
                            ] whileTrue: [
                                | descr  descrArgTypeName  descrArgDimensions |

                                descr := descriptor parameters at: i.
                                descrArgTypeName := descr javaClassName.
                                descrArgDimensions := descr dimensions.
                                descrArgTypeName first == $[ ifTrue: [
                                    descrArgTypeName := (JavaDescriptor baseTypes at: descrArgTypeName second) 
                                            javaName.
                                    descrArgDimensions := descrArgDimensions + 1.
                                ].
                                methodNodes := methodNodes 
                                        select: [:each | 
                                            | nodeArgType  nodeArgDimensions |

                                            nodeArgType := (each arguments at: i) type getTypeName asStringWith: $/.
                                            nodeArgDimensions := (each arguments at: i) type dimensions.
                                            descrArgDimensions == nodeArgDimensions 
                                                and: [ descrArgTypeName includesSubString: nodeArgType ]
                                        ].
                                i := i + 1.
                            ].
                            methodNodes isEmpty ifTrue: [
                                self error: 'No matching method node!!'.
                            ].
                            methodNodes size > 1 ifTrue: [
                                self error: 'Cannot determine method!!'.
                            ].
                            methodNode := methodNodes anElement.
                        ].
                    ].
                    methodNode notNil ifTrue: [
                        | line |

                        line := (self sourceOffsetToLine: methodNode sourceStart) -
                                (self sourceOffsetToLine: methodNode declarationSourceStart) + 1.

                        source := JavaSourceRef new.
                        source offset: methodNode declarationSourceStart.
                        source length: methodNode declarationSourceEnd - methodNode declarationSourceStart + 1.
                        source line: line.
                        method setSource: source.
                    ] ifFalse: [
                        self error: 'Cannot determine method!!'.
                    ]
                ].
            ].
        ]

    "Created: / 07-09-2013 / 01:43:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-09-2013 / 03:56:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeSourceTree
    sourceTreeLock := Semaphore new.
    Job 
        add: [
            [
                | source  unit  parser |

                source := javaClass theNonMetaclass source.
                source notNil ifTrue: [
                    unit := (Java classForName: 'stx.libjava.tools.source.JavaSource') new.
                    unit setContents: source.
                    parser := (Java classForName: 'stx.libjava.tools.source.JavaSourceParser') 
                            new.
                    sourceTree := parser parse: unit diet: true.
                    sourceLineEnds := parser scanner getLineEnds.
                    self initializeSourceRefsInMethods.
                ].
            ] ensure: [
                sourceTreeLock signal.
                sourceTreeLock := nil.
            ]
        ]

    "Created: / 06-09-2013 / 17:50:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-09-2013 / 01:59:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSourceDocument class methodsFor:'documentation'!

version_HG

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


JavaSourceDocument initialize!