EditField.st
author claus
Fri, 28 Oct 1994 04:25:37 +0100
changeset 60 f3c738c24ce6
parent 59 450ce95a72a4
child 62 7cc1e330da47
permissions -rw-r--r--
mostly style

"
 COPYRIGHT (c) 1990 by Claus Gittinger
	      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.
"

EditTextView subclass:#EditField
       instanceVariableNames:'leaveAction enabled enableAction'
       classVariableNames:'DefaultForegroundColor DefaultBackgroundColor
			   DefaultSelectionForegroundColor DefaultSelectionBackgroundColor
			   DefaultFont'
       poolDictionaries:''
       category:'Views-Text'
!

EditField comment:'
COPYRIGHT (c) 1990 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.9 1994-10-28 03:24:56 claus Exp $
'!

!EditField class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1990 by Claus Gittinger
	      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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.9 1994-10-28 03:24:56 claus Exp $
"
!

documentation
"
    an editable text-field. Realized by using an EditTextView,
    and forcing its size to 1 line - disabling cursor movement
    in the vertical direction.
    An action (leaveAction) is performed when the field is left
    by either Return or a cursor movement, or if 'accept' is
    performed from the menu.
"
! !

!EditField class methodsFor:'defaults'!

defaultNumberOfLines
    "the number of lines in the field"

    ^ 1
!

updateStyleCache
    DefaultForegroundColor := StyleSheet colorAt:'editFieldForegroundColor' default:Black.
    DefaultBackgroundColor := StyleSheet colorAt:'editFieldBackgroundColor' default:White.
    DefaultSelectionForegroundColor := StyleSheet colorAt:'editFieldSelectionForegroundColor' default:DefaultBackgroundColor.
    DefaultSelectionBackgroundColor := StyleSheet colorAt:'editFieldSelectionBackgroundColor' default:DefaultForegroundColor.
    DefaultFont := StyleSheet fontAt:'editFieldFont' default:nil.

    "
     self updateStyleCache
    "
! !

!EditField methodsFor:'initialization'!

initialize
    super initialize.
    self height:(font height + font descent + (topMargin * 2)).
    enabled := true.
    fixedSize := true.
    nFullLinesShown := 1.
    nLinesShown := 1.
!

initStyle
    super initStyle.

    DefaultBackgroundColor notNil ifTrue:[
	bgColor := DefaultBackgroundColor on:device.
	self viewBackground:bgColor.
    ].
    fgColor := DefaultForegroundColor.
    selectionFgColor := DefaultSelectionForegroundColor.
    selectionBgColor := DefaultSelectionBackgroundColor.

    DefaultFont notNil ifTrue:[
	font := DefaultFont on:device
    ]
!

initializeMiddleButtonMenu
    |labels|

    labels := resources array:#(
			       'copy'
			       'cut'
			       'paste'
"
			       'replace'
"
			       '-'
			       'accept'
			       ).

    self middleButtonMenu:(PopUpMenu 
				labels:labels
			     selectors:#(
					 copySelection
					 cut
					 paste
"
					 replace
"
					 nil
					 accept
					)
				receiver:self
				     for:self)
! !

!EditField methodsFor:'realization'!

realize
    "scroll back to beginning when realized"
    leftOffset := 0.
    super realize
! !

!EditField methodsFor:'private'!

startAutoScrollUp:y
    "no vertical scrolling in editfields"

    ^ self
!

startAutoScrollDown:y
    "no vertical scrolling in editfields"

    ^ self
! !

!EditField methodsFor:'queries'!

preferedExtent
    "return the prefered extent of this view.
     That is the width of the string plus some extra, 
     but not wider than half of the screen"

    |string w|

    string := self contents.
    (string isNil or:[string isBlank]) ifTrue:[
	string := '          ' "/ just any string is ok ^ super preferedExtent
    ].
    w := (((font on:device) widthOf:string) * 1.5) rounded.
    w := w min:(device width // 2).
    ^ w @ self height
! !

!EditField methodsFor:'editing'!

paste:someText
    "redefined to force text to 1 line"

    super paste:someText.
    list size > 1 ifTrue:[
	self deleteFromLine:2 toLine:(list size)
    ]
! !

!EditField methodsFor:'accessing'!

list:someText
    "redefined to force text to 1 line, and notify dependents
     of any changed extent-wishes."

    |l oldWidth|

    l := someText.
    l size > 1 ifTrue:[
	l := OrderedCollection with:(l at:1)
    ].
    oldWidth := self widthOfContents.
    super list:l.
    self widthOfContents ~~ oldWidth ifTrue:[
	self changed:#preferedExtent
    ]
!

contents
    "return contents as a string
     - redefined since EditFields hold only one line of text"

    list isNil ifTrue:[^ ''].
    (list size == 0) ifTrue:[^ ''].
    ^ list at:1
!

enable
    "enable the field; show cursor and allow input"

    enabled ifFalse:[
	enableAction notNil ifTrue:[
	    enableAction value
	].
	enabled := true.
	super showCursor
    ]
!

disable
    "disable the field; hide cursor and ignore input"

    enabled ifTrue:[
	enabled := false.
	self hideCursor
    ]
!

enableAction:aBlock
    "define an action to be evaluated when enabled by clicking upon"

    enableAction := aBlock
!

leaveAction:aBlock
    "define an action to be evaluated when field is left by return key"

    leaveAction := aBlock
!

initialText:aString
    "set the initialText"

    leftOffset := 0.
    self contents:aString.
    aString size ~~ 0 ifTrue:[
	self selectFromLine:1 col:1 toLine:1 col:(aString size)
    ]
! !

!EditField methodsFor:'cursor drawing'!

showCursor
    "make cursor visible if currently invisible - but only if this
     EditField is enabled"

    enabled ifTrue:[super showCursor]
! !

!EditField methodsFor:'cursor movement'!

cursorLine:line col:col
    "catch cursor movement"

    super cursorLine:1 col:col
!

cursorDown
    "catch cursor movement"

    (cursorVisibleLine == nLinesShown) ifFalse:[
	super cursorDown
    ]
! !

!EditField methodsFor:'events'!

accept
    "accept the fields contents - perform the leave action as if
     return was pressed."

    enabled ifTrue:[
	leaveAction notNil ifTrue:[
	    leaveAction value:#Return
	].
	"model-view behavior"
	(model notNil and:[aspectSymbol notNil]) ifTrue:[
	    model perform:aspectSymbol with:(self contents).
	].
    ].
!

buttonPress:button x:x y:y
    "enable myself on mouse click"

    enabled ifFalse:[
	enabled := true.
	super buttonPress:button x:x y:y.
	enableAction notNil ifTrue:[
	    enableAction value
	]
    ] ifTrue:[
	super buttonPress:button x:x y:y
    ]
!

canHandle:aKey
    "return true, if the receiver would like to handle aKey
     (usually from another view, when the receiver is part of
      a more complex dialog box).
     We do return true here, since the editfield will handle
     all keys."

    ^ true
!

keyPress:key x:x y:y
    "if keyHandler is defined, pass input; otherwise check for leave
     keys"

    |leave xCol newOffset oldWidth newWidth|

    enabled ifFalse:[
	(keyboardHandler notNil
	and:[keyboardHandler canHandle:key]) ifTrue:[
	    (keyboardHandler == self) ifTrue:[
		self error:'invalid keyhandler'.
		^ self
	    ].
	    keyboardHandler keyPress:key x:x y:y
	].
	^ self
    ].

    (key == #DeleteLine) ifTrue:[
	Smalltalk at:#CopyBuffer put:(self contents).
	self contents:''. ^ self
    ].

    leave := false.
    (key == #Return) ifTrue:[leave := true].
    (key == #Accept) ifTrue:[leave := true].
    ((key == #CursorDown) or:[key == #Next]) ifTrue:[leave := true].
    ((key == #CursorUp) or:[key == #Prior]) ifTrue:[leave := true].

    leave ifTrue:[
	self accept.
	^ self
    ].

    oldWidth := self widthOfContents.
    super keyPress:key x:x y:y.
    newWidth := self widthOfContents.

    "
     should (& can) we resize ?
    "
    xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - leftOffset.
    (xCol > (width * (5/6))) ifTrue:[
	self changed:#preferedExtent
    ] ifFalse:[
	self widthOfContents < (width * (1/6)) ifTrue:[
	    self changed:#preferedExtent
	]
    ].

    "
     did someone react ?
     (if not, we scroll horizontally)
    "
    xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - leftOffset.
    (xCol > (width * (5/6))) ifTrue:[
	newOffset := leftOffset + (width // 2).
    ] ifFalse:[
	(xCol < (width * (1/6))) ifTrue:[
	    newOffset := 0 max: leftOffset - (width // 2).
	] ifFalse:[
	    newOffset := leftOffset
	]
    ].
    newOffset ~~ leftOffset ifTrue:[
	leftOffset := newOffset.
	self clear.
	self redraw
    ]
! !