EditField.st
author claus
Wed, 13 Oct 1993 02:04:14 +0100
changeset 3 9d7eefb5e69f
parent 0 e6a541c1c0eb
child 5 7b4fb1b170e5
permissions -rw-r--r--
(none)

"
 COPYRIGHT (c) 1990-93 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-93 by Claus Gittinger
              All Rights Reserved

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

$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.2 1993-10-13 01:01:54 claus Exp $
written jan-90 by claus
'!

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

    self middleButtonMenu:(PopUpMenu 
                                labels:labels
                             selectors:#(
                                         copySelection
                                         cut
                                         paste
                                         replace)
                                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:'accessing'!

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.
    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
    ((line >= 1) and:[line <= nLinesShown]) ifTrue:[
        super cursorLine:line col:col
    ]
    "ignore"
!

cursorDown
    "catch cursor movement"

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

!EditField methodsFor:'event processing'!

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|

    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
        ].
        ^ self
    ].
    super keyPress:key x:x y:y.
    xCol := (self xOfCol:cursorCol inLine:cursorLine) - leftOffset.
    (xCol > (width * (5/6))) ifTrue:[
        leftOffset := leftOffset + (width // 2).
        self clear.
        self redraw
    ] ifFalse:[
        (xCol < (width * (1/6))) ifTrue:[
            leftOffset := 0 max: leftOffset - (width // 2).
            self clear.
            self redraw
        ]
    ]
! !