SmallSense__MethodPO.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 20 May 2014 12:33:10 +0100
changeset 232 a95a378b4248
parent 230 2c12395f8108
child 233 fb33bd6466a4
permissions -rw-r--r--
PO refactoring: parametrized displayLabel:... method to ease customozation. PO class have to provide an #label, #icon (optional, default none) and #hint (optional, default none). #displayLabel: use results of those to display items properly. This avoid a need to override displayLabel:... this method is complex enough so it should not be duplicated.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

PO subclass:#MethodPO
	instanceVariableNames:'selector classes'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Core-Interface-PO'
!


!MethodPO methodsFor:'accessing'!

cursorColumnAfterComplete

    | idx |
    idx := self label indexOf: $:.
    ^idx == 0 ifTrue:[self label size + 1] ifFalse:[idx + 1].

    "Created: / 05-04-2011 / 17:08:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-05-2014 / 11:43:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

cursorColumnAfterCompleteForLanguage: language
    | stringToComplete idx |

    stringToComplete := self stringToCompleteForLanguage: language.
    language  isSmalltalk  ifTrue:[
        idx := stringToComplete indexOf: $:.
        ^idx == 0 ifTrue:[stringToComplete size] ifFalse:[idx].
    ].
    ((language askFor: #isJava) or:[language askFor: #isGroovy]) ifTrue:[
        ^ (stringToComplete at: stringToComplete size - 1) isSeparator
            ifTrue:[stringToComplete size- 2]
            ifFalse:[stringToComplete size]
    ].

    ^ stringToComplete size + 1.

    "Created: / 03-10-2013 / 16:50:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-10-2013 / 12:30:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hint
    ^ (classes collect:[:each | each nameWithoutPrefix ]) asArray asStringWith:' , '.

    "Created: / 20-05-2014 / 12:27:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

label

    label isNil ifTrue:[
        | someClass |

        someClass := classes anElement.
        label := selector.
        someClass programmingLanguage isSmalltalk ifFalse:[
            label := (someClass compiledMethodAt: selector) printStringForBrowserWithSelector: selector.
        ]
    ].
    ^ label

    "Created: / 07-04-2011 / 09:56:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-05-2014 / 10:28:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stringToCompleteForLanguage: language
    | someClass |

    someClass := classes anElement.
    someClass isJavaClass ifTrue:[
        | method |

        method := someClass compiledMethodAt: selector.
        language isSmalltalk  ifTrue:[          
            ^ selector upTo: $(
        ].
        ((language askFor: #isJava) or:[language askFor: #isGroovy]) ifTrue:[
            ^ (selector upTo: $() , (method numArgs == 0 ifTrue:['()'] ifFalse:['(  )']).
        ].
    ].
    ^ String 
        fromStringCollection: (selector tokensBasedOn: $:)
        separatedBy: ':  '.

    "Created: / 02-10-2013 / 02:33:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-05-2014 / 10:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MethodPO methodsFor:'initialization'!

initializeWithClass: aClass selector: aSymbol
    ^ self initializeWithClasses: (Array with: aClass) selector: aSymbol

    "Created: / 20-05-2014 / 10:32:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeWithClasses: anArray"Of Classes" selector: aSymbol 
    selector := aSymbol.
    classes := anArray

    "Created: / 20-05-2014 / 10:32:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-05-2014 / 11:34:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MethodPO methodsFor:'testing'!

isSmallSenseMethodPO
    ^ true
! !

!MethodPO class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '$Id: SmallSense__MethodPO.st,v 1.2 2014/02/12 14:49:29 sr Exp $'
! !