initial checkin
authorClaus Gittinger <cg@exept.de>
Fri, 01 Jul 2011 16:22:38 +0200
changeset 10025 cdf041762f27
parent 10024 b273c6fd3606
child 10026 a2ae79b015b1
initial checkin
EditFieldWithCompletion.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/EditFieldWithCompletion.st	Fri Jul 01 16:22:38 2011 +0200
@@ -0,0 +1,394 @@
+"
+ 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'
+	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
+
+    ^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"
+
+
+    
+    (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: / 09-02-2010 / 20:47:59 / 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.
+
+    "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: / 09-12-2010 / 20:56:40 / 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 ifNil:[ ^ 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 asString < b asString]].
+    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: / 09-02-2010 / 20:46:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+hideOptionsWindow
+    optionsWindow
+        ifNotNil:[
+            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>"
+!
+
+showOptionsWindow
+
+    showOptions ifFalse:[^ self].
+    optionsWindow ifNotNil:[ ^ self ].
+
+    optionsView := SelectionInListModelView new
+                    textStartLeft: textStartLeft - 2;
+                    listHolder: optionsHolder;
+                    action:[:value | self contents:value asString ];
+                    useIndex: false;
+                    " JV: Looks good to me "
+                    highlightMode: #line;
+                    font:self font;
+                    backgroundColor:self backgroundColor;
+                    delegate: self.
+
+    optionsWindow := StandardSystemView new
+        bePopUpView;
+        beSlave;        
+        origin:(self absoluteLeft + 5" - optionsView textStartLeft") 
+                    @ (self absoluteTop + self height + 1 + 5)
+        extent:(width + 0"((optionsView textStartLeft) * 2)") @ (fontHeight * 10).
+
+    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: / 09-12-2010 / 22:05:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+startCompletion
+
+    entryCompletionBlock ifNil:[^self].
+
+    self doCompletion
+
+    "Created: / 26-07-2009 / 17:41:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!EditFieldWithCompletion class methodsFor:'documentation'!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/EditFieldWithCompletion.st,v 1.1 2011-07-01 14:22:38 cg Exp $'
+!
+
+version_SVN
+    ^ '§Id: EditFieldWithCompletion.st 7662 2010-12-09 21:05:19Z vranyj1 §'
+! !