SmallSense__MethodPO.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 31 Mar 2014 23:43:25 +0200
changeset 185 75738108cc3f
parent 174 3e08d765d86f
child 192 f27ce6dac101
permissions -rw-r--r--
Support for Tab in code completion. Pressing Tab when code completion window is open completes longes common prefix of items matching already typed text. If no text can be completed, flashes the completion popup.

"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

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


!MethodPO class methodsFor:'Instance creation'!

name:name class:class 
    ^ (self new)
        name:name;
        class:class.

    "Created: / 17-10-2013 / 01:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MethodPO methodsFor:'accessing'!

class:something
    class := something.

    "Created: / 06-04-2011 / 16:51:42 / Jakub <zelenja7@fel.cvut.cz>"
!

cursorColumnAfterComplete

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

    "Created: / 05-04-2011 / 17:08:14 / 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>"
!

label

    label isNil ifTrue:[
        | someClass |

        someClass := class isBehavior ifTrue:[class] ifFalse:[class anElement].
        label := name.
        someClass programmingLanguage isSmalltalk ifFalse:[
            label := (someClass compiledMethodAt: name) printStringForBrowserWithSelector: name.
        ]
    ].
    ^ label

    "Created: / 07-04-2011 / 09:56:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2013 / 02:28:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stringToCompleteForLanguage: language
    | someClass |

    someClass := class isBehavior ifTrue:[class] ifFalse:[class anElement].
    someClass isJavaClass ifTrue:[
        | method |

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

    "Created: / 02-10-2013 / 02:33:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-03-2014 / 23:08:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MethodPO methodsFor:'displaying'!

displayLabel:aLabel h:lH on:aGC x:x y:y h:h
    | lw cn cnw fg y0 |

    super displayLabel:aLabel h:lH on:aGC x:x y:y h:h.

    lw :=  x + IconWidth + (self label widthOn: aGC).
    class isCollection ifTrue:[
        cn := (class collect:[:each | each nameWithoutPrefix ]) asArray asStringWith:' , '.
    ] ifFalse:[
        cn := class nameWithoutPrefix.
    ].
    cnw := aGC widthOfString: cn.
    y0 := y - (lH + 1 - h // 2).
    y0 := y0 + (cn ascentOn:aGC).  

    (aGC width > (lw + cnw + 5)) ifTrue:
        [fg := aGC paint.
        aGC paint: Color gray .
        aGC displayString: cn x: aGC width - cnw - 5 y: y0.
        aGC paint: fg.
    ]

    "Created: / 18-09-2013 / 00:19:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2013 / 02:17:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayOn:aGC x:x y:y opaque:opaque

    | lw cn cnw fg |

    super displayOn:aGC x:x y:y opaque:opaque.
    lw :=  x + 16 + (self label widthOn: aGC).
    cn := class nameWithoutPrefix.
    cnw := aGC widthOfString: cn.

    (aGC width > (lw + cnw + 5)) ifTrue:
        [fg := aGC paint.
        aGC paint: Color gray .
        aGC displayString: cn x: aGC width - cnw - 5 y: y.
        aGC paint: fg.
        ]

    "Created: / 21-05-2011 / 11:02:45 / 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 $'
! !