EditFieldWithCompletion.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 27 Feb 2013 12:34:59 +0000
branchjv
changeset 12431 9f0c59c742d5
parent 12401 4714b9640528
child 12435 1f1faf35be04
permissions -rw-r--r--
Added LintRuleSettingsApplication and LintRuleEditDialog to define user-defined rule sets.

"
 COPYRIGHT (c) 2006 by eXept Software AG
	      All Rights Reserved

 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.
"
"{ Package: 'stx:libtool' }"

EditField subclass:#EditFieldWithCompletion
	instanceVariableNames:'showOptions optionsHolder optionsView optionsWindow
		focusEventsToIgnore hadFocus completionJob'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Text'
!

!EditFieldWithCompletion class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
	      All Rights Reserved

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

documentation
"
    documentation to be added.

    [author:]
        Jan Vrany (janfrog@bruxa)

    [instance variables:]

    [class variables:]

    [see also:]

"
!

example_1

    |top field label value|

    top := StandardSystemView new.
    top
        extent:300 @ 300;
        label:'Live class completion field'.
    value := '' asValue.
    field := (EditFieldWithCompletion new)
                origin:10 @ 135 corner:280 @ 165;
                entryCompletionBlock:[:content | Smalltalk classnameCompletion:content ];
                model:value.
    label := (Label new)
                origin:10 @ 95 corner:280 @ 115;
                labelChannel:value.
    top
        add:field;
        add:label.
    top open
!

examples
"
    Opens a LiveCompletionEditField on a class name
                                                        [exBegin]
    LiveCompletionEditField example_1
                                                        [exEnd]
"
! !

!EditFieldWithCompletion methodsFor:'accepting'!

accept

    self unselect.
    super accept.

    "Created: / 27-07-2009 / 09:38:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 12-02-2010 / 11:56:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditFieldWithCompletion methodsFor:'accessing-behavior'!

showOptions
    ^ showOptions
!

showOptions:aBoolean
    showOptions := aBoolean.
! !

!EditFieldWithCompletion methodsFor:'accessing-dimensions'!

absoluteLeft

    | absoluteLeft view |
    absoluteLeft := 1.
    view := self.
    [ view notNil ] whileTrue:
        [absoluteLeft := absoluteLeft + view left - 1.
        view := view superView].
    ^absoluteLeft

    "Created: / 08-08-2009 / 22:30:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

absoluteTop

    | absoluteTop view |
    absoluteTop := 1.
    view := self.
    [ view notNil ] whileTrue:
        [absoluteTop := absoluteTop + view top - 1.
        view := view superView].
    ^absoluteTop

    "Created: / 08-08-2009 / 22:30:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!EditFieldWithCompletion methodsFor:'accessing-mvc'!

optionsHolder

    ^ optionsHolder

    "Created: / 09-08-2009 / 08:14:02 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

optionsHolder:aValueHolder
    "set the 'options' value holder (automatically generated)"

    optionsHolder := aValueHolder.

    "Created: / 09-08-2009 / 08:14:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!EditFieldWithCompletion methodsFor:'event handling'!

completion:best options:options 
    |newContent oldContent|
    "
    oldContent := ((self contents ? '') asString).
    newContent := ((best isNil or:[ best = oldContent ]) 
                and:[ options isNilOrEmptyCollection not ]) 
                    ifTrue:[
                        options first
                        ""options inject:options anyOne
                            into:[:shortest :each | 
                                shortest asString size > each asString size ifTrue:[
                                    each
                                ] ifFalse:[ shortest ]
                            ]""
                    ]
                    ifFalse:[ best ].
    self contents:newContent asString.
    self cursorCol:oldContent size + 1.
    oldContent size < newContent size ifTrue:[
        self 
            selectFromLine:1
            col:oldContent size + 1
            toLine:1
            col:newContent size
    ].
    "
    options size > 1 ifTrue:[
        optionsHolder value:options.
        self showOptionsWindow
    ]

    "Created: / 08-08-2009 / 22:02:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 08:16:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 13-02-2010 / 09:51:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

handleNonCommandKey: char

    super handleNonCommandKey: char.
    self startCompletion

    "Modified: / 26-07-2009 / 17:41:22 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

handlesKeyPress:key inView:aView

    <resource: #keyboard (#CursorDown #CursorUp)>

    ^aView == optionsView and:
        [(#( #CursorDown #CursorUp ) includes: key) not].

    "Created: / 09-12-2010 / 21:31:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hasKeyboardFocus:aBoolean

    focusEventsToIgnore > 0 ifTrue:[
        focusEventsToIgnore := focusEventsToIgnore - 1.
        "
        xxx == 0 ifTrue:[
            Transcript showCR:'--> taking focus'.
            self takeFocus.
            self assert: self windowGroup focusView == self.
            hadFocus := true.
        ].
        "            
        ^self].

    hadFocus == aBoolean ifTrue:[
        ^self
    ].

    aBoolean 
        ifTrue:
            [self selectAll]
        ifFalse:
            [self unselect.
            self hideOptionsWindow].
    hadFocus := aBoolean.
    ^ super hasKeyboardFocus:aBoolean

    "Created: / 08-08-2009 / 23:28:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 10:14:25 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-12-2010 / 22:05:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress:key x:x y:y 
    "Forward certain events to optionsView if any"

    <resource: #keyboard (#CursorDown #CursorUp #Accept #Return #Escape #BackSpace)>
    
    (optionsView notNil and:
        [(#( #CursorDown #CursorUp ) includes:key)]) 
            ifTrue:[^ optionsView keyPress:key x:x y:y].

    key = #Accept ifTrue:[self hideOptionsWindow].
    key = #Return ifTrue:[self hideOptionsWindow].
    key = #Escape ifTrue:[self hideOptionsWindow].
    key = #BackSpace ifTrue:
        [super 
"/            keyPress:#Delete x:x y:y;
            keyPress:#BackSpace x:x y:y.
        ^ self startCompletion].

    

    ^ super 
        keyPress:key
        x:x
        y:y

    "Created: / 08-08-2009 / 22:02:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 14:06:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 30-03-2012 / 17:34:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress:key x:x y:y view:aView

    self keyPress: key x:x y:y

    "Created: / 09-12-2010 / 21:32:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditFieldWithCompletion methodsFor:'initialization & release'!

destroy

    self hideOptionsWindow.
    super destroy.

    "Created: / 08-08-2009 / 22:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 08:50:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

initialize

    super initialize.
    showOptions := true.
    optionsHolder := ValueHolder new.
    focusEventsToIgnore := 0.
    completionJob := BackgroundJob 
                        named: 'Edit Field Completion Job'
                        on:[self doCompletion].

    "Created: / 08-08-2009 / 20:24:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 08:17:09 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-08-2011 / 17:50:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditFieldWithCompletion methodsFor:'private'!

doCompletion
    |oldContents options best|

    oldContents := (self contents ? '') asString.
    options := self entryCompletionBlock 
                valueWithOptionalArgument:oldContents
                and:self.
    options isNil ifTrue:[
        ^ self
    ].
    best := options first.
    options := options second.
    (options includes:best) ifFalse:[
        best := options 
                    detect:[:e | e asString startsWith:best asString ]
                    ifNone:[ best ]
    ].
    options isSortedCollection ifFalse:[
        options := options asSortedCollection:[:a :b | a displayString < b displayString ]
    ].
    self sensor 
        pushUserEvent:#completion:options:
        for:self
        withArguments:(Array with:best with:options).

    "Created: / 26-07-2009 / 17:45:09 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 02:51:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 18-11-2011 / 14:33:56 / cg"
    "Modified (format): / 20-11-2011 / 09:42:25 / cg"
    "Modified: / 20-04-2012 / 18:20:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hideOptionsWindow
    optionsWindow notNil ifTrue:[
        optionsWindow destroy.
        optionsWindow := nil.
    ]

    "Created: / 08-08-2009 / 23:23:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 09:00:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 29-11-2011 / 11:27:03 / cg"
!

showOptionsWindow

    | x y w |

    showOptions ifFalse:[^ self].
    optionsWindow notNil ifTrue:[ ^ self ].

    optionsView := SelectionInListModelView new
                    textStartLeft: textStartLeft - 2;
                    listHolder: optionsHolder;
                    action:[:value | self contents:value asString ];
                    doubleClickAction:[:index | 
                            self contents:(optionsView at:index) asString.
                            self hideOptionsWindow.
                            self accept
                        ];
                    useIndex: false;
                    " JV: Looks good to me "
                    highlightMode: #line;
                    font:self font;
                    backgroundColor:self backgroundColor;
                    delegate: self;
                    yourself.

    x := self absoluteLeft + 5" - optionsView textStartLeft".
    y := self absoluteTop + self height + 1 + 5.
    w := (width * 2) + 0"((optionsView textStartLeft) * 2)".

    optionsWindow := StandardSystemView new
        bePopUpView;
        beSlave;        
        origin:x @ y
        extent:(w min: (Screen current width - x)) @ (fontHeight * 10);
        yourself.

    ScrollableView   
        forView:optionsView 
        hasHorizontalScrollBar:false 
        hasVerticalScrollBar:true 
        miniScrollerH:true 
        miniScrollerV:false 
        origin:0.0@0.0 
        corner:1.0@1.0 
        in:optionsWindow.

    focusEventsToIgnore := 4.
    optionsWindow open.

    "Created: / 09-08-2009 / 08:12:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 09-08-2009 / 09:28:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 29-11-2011 / 11:27:13 / cg"
    "Modified: / 04-04-2012 / 13:08:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

startCompletion

    completionJob restart.

    "Created: / 26-07-2009 / 17:41:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified (format): / 03-08-2011 / 17:50:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!EditFieldWithCompletion class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/EditFieldWithCompletion.st,v 1.6 2013-01-17 10:47:17 cg Exp $'
!

version_HG

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

version_SVN
    ^ '§Id: EditFieldWithCompletion.st 7662 2010-12-09 21:05:19Z vranyj1 §'
! !