EditField.st
author claus
Wed, 24 Aug 1994 01:36:34 +0200
changeset 47 1b6dcf811b87
parent 38 4b9b70b2cc87
child 59 450ce95a72a4
permissions -rw-r--r--
MVC support

"
 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:''
       poolDictionaries:''
       category:'Views-Text'
!

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

$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.7 1994-08-23 23:36:34 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.7 1994-08-23 23:36:34 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
! !

!EditField methodsFor:'initialization'!

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

initStyle
    |myBgColor myFont|

    super initStyle.

    myBgColor := resources name:'BACKGROUND' default:nil.
    myBgColor notNil ifTrue:[
        bgColor := myBgColor on:device.
        self viewBackground:bgColor.
        selectionFgColor := fgColor on:device.
        selectionBgColor := White on:device
    ].

    myFont := resources name:'FONT' default:nil.
    myFont notNil ifTrue:[
        font := myFont
    ]
!

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

startScrollUp:y
    "no scrolling in editfields"

    ^ self
!

startScrollDown:y
    "no scrolling in editfields"

    ^ self
! !

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

    string := self contents.
    (string isNil or:[string isBlank]) ifTrue:[
        ^ super preferredExtent
    ].
    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:self with:#preferredExtent
    ]
!

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

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 == #CursorDown) or:[key == #Next]) ifTrue:[leave := true].
    ((key == #CursorUp) or:[key == #Prior]) ifTrue:[leave := true].

    leave ifTrue:[
        leaveAction notNil ifTrue:[
            leaveAction value:key
        ].
        "model-view behavior"
        model notNil ifTrue:[
            model perform:aspectSymbol with:(self contents).
        ].
        ^ self
    ].

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

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

    "
     did someone react ?
     (if not, we scroll horizontally)
    "
    xCol := (self xOfCol:cursorCol inLine: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
    ]
! !