EditField.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 03:26:58 +0100
changeset 197 00927189c882
parent 192 fc2fc4347d5d
child 209 7a6db7fac566
permissions -rw-r--r--
checkin from browser

"
 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 crAction tabAction converter
                leaveKeys immediateAccept acceptOnLeave acceptOnReturn
                lengthLimit entryCompletionBlock passwordCharacter
                cursorMovementWhenUpdating'
	 classVariableNames:'DefaultForegroundColor DefaultBackgroundColor
                DefaultSelectionForegroundColor DefaultSelectionBackgroundColor
                DefaultFont'
	 poolDictionaries:''
	 category:'Views-Text'
!

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

documentation
"
    an editable text-field. Realized by using an EditTextView,
    and forcing its size to 1 line - disabling cursor movement
    in the vertical direction.

    Instance variables:

      leaveAction    <Block | nil>              if non-nil, this is evaluated with
						the key (#Return, #CursorUp etc.) when
						the field is left via keyboard keys.
						(fieldGroups use this to decide which
						 field has to be enabled next)

      enabled        <Boolean>                  if false, input is ignored.

      enableAction   <Block | nil>              action performed if the field is
						enabled via an explicit click.
						(this is used by the group to
						 set the active field to the clicked upon field)

      crAction       <Block | nil>              if non-nil, keyboard input of a cr are not
						handled specially, instead this block is evaluated
						(however, this block can perform additional checks and send
						 a #accept then)

      tabAction      <Block | nil>              if non-nil, keyboard input of a tab character
						is not entered into the text, instead this block
						is evaluated.

      converter      <PrintConverter | nil>     if non-nil, this is supposed to convert between
						the object and its printed representation.
						Defaults to nil i.e. assume that strings are edited.

      leaveKeys      <Collection>               keys which are interpreted as 'leving the field'

      immediateAccept   <Boolean>               if true, every change of the text is immediately
						forwarded to the model/acceptBlock. If false,
						the changed value is only stored in the model
						if the field is left or accepted.
						Default is false.

      acceptOnLeave  <Boolean>                  if true, leaving the field (via cursor keys)
						automatically accepts the value into the model.
						Default is true.

      acceptOnReturn <Boolean>                  if true, leaving the field via return
						automatically accepts the value into the model.
						Default is true.
"
!

examples 
"
    see more examples in EnterFieldGroup>>examples.


    basic field in a view:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@0.0 in:top.
	field width:1.0.        'let its height as-is'.

	top open


    forward input in topView to the field:
    (currently, the field does not know this - therefore,
     its been told here ... this may change)

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@0.0 in:top.
	field width:1.0.        'let its height as-is'.

	top delegate:(KeyboardForwarder toView:field).
	field hasKeyboardFocus:true.
	top open


    to make it look better: set some inset:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.        'let its height as-is'.
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.

	top open


    give it an initial contents:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.       
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field editValue:'hello world'.

	top open


    have it preselected:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.     
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field editValue:'hello world' selected:true.

	top open


    have part of it preselected:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.     
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field editValue:'hello world';
	      selectFromCharacterPosition:1 to:5.

	top open


    set a size limit:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.     
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field editValue:'hello';
	      maxChars:8.

	top open


    use a converter:
      - numbers (default to 0):

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.

	field converter:(PrintConverter new initForNumber).
	field editValue:1234.
	field acceptAction:[:value | Transcript showCr:value].
	field crAction:[field accept. top destroy].
	top open.

      - dates:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.

	field converter:(PrintConverter new initForDate).
	field editValue:Date today.
	field acceptAction:[:value | Transcript showCr:value class name , ' ' , value printString].
	field crAction:[field accept. top destroy].
	top open.


    setting immediateAccept, makes the field update with every key:

      - immediate accept numbers, defaulting to nil:

	|top field|

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.

	field converter:(PrintConverter new initForNumberOrNil).
	field immediateAccept:true.
	field editValue:1234.
	field acceptAction:[:value | Transcript showCr:value].
	field crAction:[field accept. top destroy].
	top open.




    use a model:
    (see changing model value in inspector when return is pressed in the field)

	|top field model|

	model := 'hello world' asValue.

	top := StandardSystemView new.
	top extent:200@100.

	field := EditField origin:0.0@ViewSpacing in:top.
	field width:1.0.
	field leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field model:model.
	field acceptOnReturn:true.

	top open.
	model inspect.


    two views on the same model (each accepts on return):

	|top1 top2 field1 field2 model|

	model := 'hello world' asValue.

	top1 := StandardSystemView new.
	top1 extent:200@100.
	field1 := EditField origin:0.0@ViewSpacing in:top1.
	field1 width:1.0.
	field1 leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field1 model:model.
	field1 acceptOnReturn:true.
	top1 open.

	top2 := StandardSystemView new.
	top2 extent:200@100.
	field2 := EditField origin:0.0@ViewSpacing in:top2.
	field2 width:1.0.
	field2 leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field2 model:model.
	field2 acceptOnReturn:true.
	top2 open.

    two views on the same model (no accept on return):

	|top1 top2 field1 field2 model|

	model := 'hello world' asValue.

	top1 := StandardSystemView new.
	top1 extent:200@100.
	field1 := EditField origin:0.0@ViewSpacing in:top1.
	field1 width:1.0.
	field1 leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field1 model:model; acceptOnReturn:false.
	top1 open.

	top2 := StandardSystemView new.
	top2 extent:200@100.
	field2 := EditField origin:0.0@ViewSpacing in:top2.
	field2 width:1.0.
	field2 leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field2 model:model; acceptOnReturn:false.
	top2 open.

    with immediate accept:

	|top1 top2 field1 field2 model|

	model := 'hello world' asValue.

	top1 := StandardSystemView new.
	top1 extent:200@100.
	field1 := EditField origin:0.0@ViewSpacing in:top1.
	field1 width:1.0.
	field1 leftInset:ViewSpacing; rightInset:ViewSpacing.
	field1 model:model; immediateAccept:true.
	top1 open.

	top2 := StandardSystemView new.
	top2 extent:200@100.
	field2 := EditField origin:0.0@ViewSpacing in:top2.
	field2 width:1.0.
	field2 leftInset:ViewSpacing; rightInset:ViewSpacing.
	field2 model:model; immediateAccept:true.
	top2 open.

    just an example; a checkBox and an editField on the same model:

	|top1 top2 field1 box model|

	model := false asValue.

	top1 := StandardSystemView new.
	top1 extent:200@100.
	field1 := EditField origin:0.0@ViewSpacing in:top1.
	field1 width:1.0.
	field1 leftInset:ViewSpacing;
	      rightInset:ViewSpacing.
	field1 converter:(PrintConverter new initForYesNo).
	field1 model:model.
	top1 open.

	top2 := StandardSystemView new.
	top2 extent:200@100.
	box := CheckBox on:model.
	box label:'on/off'.
	top2 add:box.
	top2 open.

	model inspect.


    connecting fields:
    update field2 wehenever field1 is changed.
    (normally, the processing below (xChanged) is done in your application
     class, or in a complex model. For the demonstration below, we use
     a Plug to simulate the protocol.)

	|application top field1 field2 value1 value2|

	application := Plug new.
	application respondTo:#value1Changed
			 with:[value2 value:(value1 value isNil ifTrue:[nil]
								ifFalse:[value1 value squared])].

	value1 := 1 asValue.
	value2 := 1 asValue.

	top := Dialog new.
	top extent:200@200.

	(top addTextLabel:'some number:') layout:#left.
	top addVerticalSpace.

	(top addInputFieldOn:value1 tabable:false) 
	    converter:(PrintConverter new initForNumberOrNil);
	    immediateAccept:true.
	top addVerticalSpace.

	(top addTextLabel:'squared:') layout:#left.
	top addVerticalSpace.
	(top addInputFieldOn:value2 tabable:false) 
	    converter:(PrintConverter new initForNumberOrNil).

	value1 onChangeSend:#value1Changed to:application.

	top openModeless.


    two-way connect:
    each field updates the other (notice, that we have to turn off
    onChange: notification, to avoid an endless notification cycle)

	|application top field1 field2 value1 value2|

	application := Plug new.
	application respondTo:#value1Changed
			 with:[value2 retractInterrestFor:application.
			       value2 value:(value1 value isNil ifTrue:[nil]
								ifFalse:[value1 value squared]).
			       value2 onChangeSend:#value2Changed to:application.
			      ].
	application respondTo:#value2Changed
			 with:[value1 retractInterrestFor:application.
			       value1 value:(value2 value isNil ifTrue:[nil]
								ifFalse:[value2 value sqrt]).
			       value1 onChangeSend:#value1Changed to:application.
			      ].

	value1 := 1 asValue.
	value2 := 1 asValue.

	top := Dialog new.
	top extent:200@200.

	(top addTextLabel:'some number:') layout:#left.
	top addVerticalSpace.

	(top addInputFieldOn:value1 tabable:false) 
	    converter:(PrintConverter new initForNumberOrNil);
	    immediateAccept:true.
	top addVerticalSpace.

	(top addTextLabel:'squared:') layout:#left.
	top addVerticalSpace.
	(top addInputFieldOn:value2 tabable:false) 
	    converter:(PrintConverter new initForNumberOrNil);
	    immediateAccept:true.

	value1 onChangeSend:#value1Changed to:application.
	value2 onChangeSend:#value2Changed to:application.

	top openModeless.
"
!

version
    ^ '$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.32 1995-11-23 00:48:21 cg Exp $'
! !

!EditField class methodsFor:'defaults'!

defaultLeaveKeys
    "return the set of keys which are taken as leave-keys.
     If the field is in an enterFieldGroup, all leave keys will be
     forwarded to the group and possible step to the next/previous field.
     Also, if acceptOnLeave is true, leave keys will store the current
     value into their model (if any)"

    ^ #(Return CursorUp CursorDown Next Previous Accept)
!

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:'accessing-behavior'!

acceptOnLeave:aBoolean
    "set/clear the acceptOnLeave flag. The default is false."

     acceptOnLeave := aBoolean
!

acceptOnReturn:aBoolean
    "set/clear the acceptOnReturn flag. The default is false."

     acceptOnReturn := aBoolean
!

crAction:aBlock
    "define an action to be evaluated when the return key is pressed."

    crAction := aBlock
!

cursorMovementWhenUpdating:aSymbol
    "define what should be done with the cursor, when I update
     my contents from the model. Allowed argumetns are:
	#keep / nil     -> stay where it was
	#endOfLine      -> position cursor after the string
	#beginOfLine    -> position cursor to the beginning
     The default is #endOfLine"

    cursorMovementWhenUpdating := aSymbol
!

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

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

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

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

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

    enableAction := aBlock
!

entryCompletionBlock:aOneArgBlock
    "define an action to be evaluated when Tab (NameCompletion) is pressed.
     The block gets the current contents as argument."

    entryCompletionBlock := aOneArgBlock
!

immediateAccept:aBoolean
    "set/clear the immediateAccept flag. The default is false."

     immediateAccept := aBoolean
!

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

    leaveAction := aBlock
!

leaveKeys:aCollectionOfKeySymbols 
    "define the set of keys which are interpreted as leaveKeys.
     I.e. those that make the field inactive and accept (if acceptOnLeave is true).
     The default is a set of #CursorUp, #CursorDown, #Next, #Prior and #Return."

    leaveKeys := aCollectionOfKeySymbols
!

tabAction:aBlock
    "define an action to be evaluated when the tabulator key is pressed."

    tabAction := aBlock
! !

!EditField methodsFor:'accessing-contents'!

contents
    "return contents as a string
     - redefined since EditFields hold only one line of text.
    In your application, please use #editValue; 
    it uses a converter (if any) and is compatible to ST-80."

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

contents:someText
    "set the contents from a string
     - redefined to place the cursor to the end.
    In your application, please use #editValue:; 
    it uses a converter (if any) and is compatible to ST-80."

    |newCol|

    newCol := cursorCol.

    super contents:someText.

    cursorMovementWhenUpdating == #endOfLine ifTrue:[
	 newCol := (someText size + 1).
    ] ifFalse:[
	cursorMovementWhenUpdating == #beginOfLine ifTrue:[
	    newCol := 1
	] ifFalse:[
	    "/ default: stay where it was
	]
    ].

    self cursorCol:newCol.
!

converter
    "return the converter (if any)."

    ^ converter
!

converter:aConverter
    "set the converter. If non-nil,
     the converter is applied to the text to convert from the string
     representation to the actual object value and vice versa.
     The default converter is nil, meaning no-conversion
     (i.e. the edited object is the string itself."

    converter := aConverter
!

editValue
    "if the field edits a string, this is a name alias for #contents.
     Otherwise, if there is a converter, return the edited string
     converted to an appropriate object."

    |string|

    string := self contents.
    converter isNil ifTrue:[^ string].
    string isNil ifTrue:[string := ''].
    ^ converter readValueFrom:string 
!

editValue:aStringOrObject
    "set the contents. If there is a converter, use it to convert
     the object into a printed representation.
     Otherwise, the argument is supposed to be a string like object,
     and used directly (i.e. this is equivalent to sending #contents:)."

    self editValue:aStringOrObject selected:false
!

editValue:aStringOrObject selected:aBoolean
    "set the contents. If there is a converter, use it to convert
     the object into a printed representation.
     Otherwise, the argument is supposed to be a string like object,
     and used directly (i.e. this is equivalent to sending #initialText:selected:)."

    |string|

    converter notNil ifTrue:[
	string := converter printStringFor:aStringOrObject
    ] ifFalse:[
	string :=  aStringOrObject.
    ].
    self contents:string.
    aBoolean ifTrue:[
	self selectFromLine:1 col:1 toLine:1 col:string size
    ]
!

initialText:aString
    "set the initialText and select it"

    self initialText:aString selected:true
!

initialText:aString selected:aBoolean
    "set the initialText and select it if aBoolean is true"

    |len s|

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

list:someText
    "low level access to the underlying contents' list.
     Redefined to force text to 1 line, and notify dependents
     of any changed extent-wishes (for automatic box resizing)."

    |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:#preferredExtent
    ]
!

stringValue
    "alias for #contents - for compatibility with ST-80's InputField"

    ^ self contents
! !

!EditField methodsFor:'accessing-look'!

maxChars
    "return the maximum number of characters that are allowed in
     the field. 
     A limit of nil means: unlimited. This is the default."

    ^ lengthLimit

    "Modified: 6.9.1995 / 13:43:33 / claus"
!

maxChars:aNumberOrNil
    "set the maximum number of characters that are allowed in
     the field. Additional input will be ignored by the field.
     A limit of nil means: unlimited. This is the default.
     This method has been renamed from #lengthLimit: for ST-80
     compatibility."

    lengthLimit := aNumberOrNil
!

passwordCharacter
    ^ passwordCharacter

    "Modified: 6.9.1995 / 12:25:39 / claus"
!

passwordCharacter:aCharacter
    passwordCharacter := aCharacter

    "Modified: 6.9.1995 / 12:25:33 / claus"
! !

!EditField methodsFor:'cursor drawing'!

drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg
    startVisLineNr to:endVisLineNr do:[:visLine |
	self drawVisibleLine:visLine with:fg and:bg
    ]

    "Modified: 6.9.1995 / 12:24:29 / claus"
!

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

    enabled ifTrue:[super showCursor]
! !

!EditField methodsFor:'cursor movement'!

cursorCol:col
    "redefined to lock the cursor at the end, if I have a lngthLimit"

    |c sz|

    c := col.
    lengthLimit notNil ifTrue:[
	sz := lengthLimit.
	c > sz ifTrue:[
	    c := sz+1.
	]
    ].
    super cursorCol:c
!

cursorDown
    "catch cursor movement"

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

cursorLine:line col:col
    "catch cursor movement"

    super cursorLine:1 col:col
! !

!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:'event handling'!

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.
     OBSOLETE: dont use this anymore - its a leftover for the tableWidget"

    ^ true
!

focusIn
    "got the explicit focus"

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

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

    <resource: #keyboard (#DeleteLine #EndOfText)>

    |leave xCol newOffset oldWidth newWidth s|

    enabled ifFalse:[
	^ self
    ].

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

    (key == #Tab) ifTrue:[
	tabAction notNil ifTrue:[tabAction value. ^ self].
	entryCompletionBlock notNil ifTrue:[
	    s := self contents.
	    s isNil ifTrue:[
		s := ''
	    ] ifFalse:[
		s := s asString
	    ].
	    entryCompletionBlock value:s. ^ self
	]
    ].
    (key == #Return) ifTrue:[
	crAction notNil ifTrue:[crAction value. ^ self].
    ].
    leave := leaveKeys includes:key.
    leave ifTrue:[
	leaveAction notNil ifTrue:[
	    leaveAction value:key
	].

	((key == #Return and:[acceptOnReturn])
	or:[key ~~ #Return and:[acceptOnLeave]]) ifTrue:[
	    self accept.
	].

	x >= 0 ifTrue:[
	    "
	     let superview know about the leave ...
	     This is a temporary kludge for the tableWidget -
	     it is no clean coding style. Should make the tableWidget
	     a proper model and handle it via the changed mechanism ....
	    "
	    (superView notNil and:[superView canHandle:key from:self]) ifTrue:[
		superView keyPress:key x:x y:y.
	    ].
	].
	^ self
    ].

    "
     ignore some keys (if not a leaveKey) ...
    "
    (key == #Find) ifTrue:[^self].
    (key == #FindNext) ifTrue:[^self].
    (key == #FindPrev) ifTrue:[^self].
    (key == #GotoLine) ifTrue:[^self].

    "
     a normal key - let superclass's method insert it
    "
    oldWidth := self widthOfContents.
    super keyPress:key x:x y:y.

    "
     for end-of-text, also move to end-of-line
    "
    key == #EndOfText ifTrue:[
	super keyPress:#EndOfLine 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:#preferredExtent
    ] ifFalse:[
	newWidth < (width * (1/6)) ifTrue:[
	    self changed:#preferredExtent
	]
    ].

    "
     did someone react (i.e. has my extent changed) ?
     (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:[
	self scrollHorizontalTo:newOffset.
"/        leftOffset := newOffset.
"/        self clear.
"/        self redraw
    ]
! !

!EditField methodsFor:'initialization'!

editMenu
    |labels selectors m|

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

     selectors := #(
		 copySelection
		 cut
		 paste
"
		 replace
"
		 nil
		 accept
		).

    m := PopUpMenu 
	  labels:(resources array:labels)
	  selectors:selectors.

    self hasSelection ifFalse:[
	m disableAll:#(copySelection cut)
    ].

    ^ m
!

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
    ]
!

initialize
    super initialize.
    self height:(font height + font descent + (topMargin * 2)).
    enabled := true.
    fixedSize := true.
    nFullLinesShown := 1.
    nLinesShown := 1.
    immediateAccept := false.
"/    acceptOnLeave := false.
"/    acceptOnReturn := false.
    acceptOnLeave := acceptOnReturn := true.
    cursorShown := true.
    leaveKeys := self class defaultLeaveKeys.
    cursorMovementWhenUpdating := #endOfLine
! !

!EditField methodsFor:'private'!

argForChangeMessage
    "redefined to send use converted value (if I have one)"

    ^ self editValue
!

getListFromModel
    "redefined to aquire the text via the aspectMsg - not the listMsg,
     and to ignore updates resulting from my own change."

    "
     ignore updates from my own change
    "
    lockUpdates ifTrue:[
	lockUpdates := false.
	^ self
    ].

    (model notNil and:[aspectMsg notNil]) ifTrue:[
	self editValue:(model perform:aspectMsg).
    ]
!

startAutoScrollDown:y
    "no vertical scrolling in editfields"

    ^ self
!

startAutoScrollUp:y
    "no vertical scrolling in editfields"

    ^ self
!

textChanged
    "this is sent by mySelf (somewhere in a superclass) whenever
     my contents has changed. 
     A good place to add immediateAccept functionality and check for the
     lengthLimit."

    |string c|

    super textChanged.
    string := self contents.
    lengthLimit notNil ifTrue:[
	string size > lengthLimit ifTrue:[
	    c := cursorCol.
	    self contents:(string copyTo:lengthLimit).
	    self flash.
	    self cursorCol:c.
	]
    ].
    immediateAccept ifTrue:[
	self accept
    ]
!

visibleAt:visLineNr
    "return the string at lineNr for display.
     If there is a password character, return a string consisting of those only."

    |s|

    s := super visibleAt:visLineNr.
    passwordCharacter notNil ifTrue:[
	^ String new:(s size) withAll:passwordCharacter
    ].
    ^ s

    "Modified: 6.9.1995 / 12:25:06 / claus"
! !

!EditField methodsFor:'queries'!

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

    |string w f|

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

    "Modified: 6.9.1995 / 19:24:06 / claus"
!

specClass
    self class == EditField ifTrue:[^ InputFieldSpec].
    ^ nil

    "Modified: 5.9.1995 / 17:28:27 / claus"
! !

!EditField methodsFor:'realization'!

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

!EditField methodsFor:'scrolling'!

makeColVisible:col inLine:line
    "dont scroll for the cursor, if its behond the text and a lengthLimit
     is present."

    lengthLimit notNil ifTrue:[
	(col == cursorCol and:[col > lengthLimit]) ifTrue:[
	    ^ super makeColVisible:lengthLimit inLine:line
	]
    ].
    ^ super makeColVisible:col inLine:line

    "Modified: 6.9.1995 / 13:57:53 / claus"
! !