EnterBox.st
author claus
Wed, 13 Oct 1993 03:49:56 +0100
changeset 5 7b4fb1b170e5
parent 3 9d7eefb5e69f
child 7 15a9291b9bd0
permissions -rw-r--r--
(none)

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

ModalBox subclass:#EnterBox
       instanceVariableNames:'labelField enterField buttonPanel
                              okButton abortButton
                              okAction abortAction'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Interactors'
!

EnterBox comment:'

COPYRIGHT (c) 1990 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.3 1993-10-13 02:47:34 claus Exp $

written Feb 90 by claus
'!

!EnterBox class methodsFor:'documentation'!

documentation
"
this class implements a pop-up box to enter some string
with 2 buttons; one to cancel, another to start some action.
The boxes title can be changed using: 

    aBox title:'some string'

The two button-labels default to 'abort' and 'ok'; they can be changed
using:

    aBox okText:'someString'
    aBox abortText:'someString'

The initial text in the enterfield can be set using:

    aBox initialText:'someString'

when the ok-button is pressed, an eaction is performed, which is
set using:

    aBox action:[ ... ]

the abort-action defaults to no-action, but can also be set.
"
! !

!EnterBox class methodsFor:'defaults'!

defaultExtent
    ^ (Display pixelPerMillimeter * (60 @ 30)) rounded
! !

!EnterBox class methodsFor:'instance creation'!

action:aBlock
    "create and return a new EnterBox 
     which will evaluate aBlock when 'ok' is pressed"

    ^ (self new) action:aBlock

    "(EnterBox action:[:string | Transcript showCr:string]) showAtPointer"
!

title:titleString action:aBlock
    "create and return a new EnterBox with title aString,
     which will evaluate aBlock when 'ok' is pressed"

    ^ ((self new) title:titleString) action:aBlock
!

title:titleString okText:okText abortText:abortText action:aBlock
    "create and return a new EnterBox with title aString, and buttons showing
     okText and abortText; it will evaluate aBlock when 'ok' is pressed"

    ^ ((self new) title:titleString 
                 okText:okText 
              abortText:abortText) action:aBlock
! !

!EnterBox methodsFor:'initialization'!

initialize
    |space2 innerWidth|

    super initialize.

    space2 := 2 * ViewSpacing.

    labelField := Label in:self.
    labelField label:''.
    labelField borderWidth:0.
    labelField adjust:#center.

    "kludge: preset extent to something useful since other subviews
     depend on it (extent blocks are not evaluated until view is realized)
     - avoid visible resizing when realized the first time"

    innerWidth := width - space2.

    labelField origin:(ViewSpacing @ ViewSpacing)
               extent:(innerWidth @ labelField height).

    enterField := EditField in:self.
    enterField origin:(ViewSpacing @ (space2 + labelField height))
               extent:((width - space2 - (enterField borderWidth * 2)) @ enterField height).
    enterField origin:[ViewSpacing @ (space2 + labelField height)]
               extent:[(width - space2 - (enterField borderWidth * 2)) @ enterField height].
    enterField leaveAction:[:key | self okPressed].

    buttonPanel := HorizontalPanelView in:self.
    buttonPanel origin:(ViewSpacing @ (height - (font height * 2) - ViewSpacing - (borderWidth * 2)))
                extent:((width - space2 - (buttonPanel borderWidth * 2)) 
                       @ ((font height * 2) + (borderWidth * 2))).
    buttonPanel origin:[ViewSpacing @ (height - (font height * 2) - ViewSpacing - (borderWidth * 2))]
                extent:[(width - space2 - (buttonPanel borderWidth * 2)) 
                       @ ((font height * 2) + (borderWidth * 2))].

    buttonPanel layout:"#spread2" #right.
    buttonPanel borderWidth:0.

    abortButton := Button label:(resources at:'abort')
                         action:[
                                    abortButton turnOffWithoutRedraw.
                                    self abortPressed
                                ]
                             in:buttonPanel.

    okButton := Button label:(resources at:'ok')
                      action:[
                                okButton turnOffWithoutRedraw.
                                self okPressed
                             ]
                          in:buttonPanel.
    okButton isReturnButton:true.

    self keyboardHandler:enterField

!

initEvents
    super initEvents.
    self enableKeyEvents
!

reAdjustGeometry
    "sent late in snapin processing - gives me a chance
     to resize for new font dimensions"

    super reAdjustGeometry.
    labelField resize.
    okButton resize.
    abortButton resize.
    self resize
! !

!EnterBox methodsFor:'private'!

resize
    "resize myself to make everything visible"

    |wWanted hWanted wPanel|

    wWanted := labelField widthIncludingBorder + ViewSpacing + ViewSpacing.
"
    (wWanted > width) ifFalse:[
        wWanted := width
    ].
"
    wPanel := buttonPanel preferedExtent x + ViewSpacing + ViewSpacing.
    wPanel > wWanted ifTrue:[
        wWanted := wPanel
    ].
    hWanted := ViewSpacing + labelField height +
               ViewSpacing + enterField height +
               (ViewSpacing * 6) + buttonPanel height +
               ViewSpacing.
    ((wWanted ~= width) or:[hWanted ~= height]) ifTrue:[
        self extent:(wWanted @ hWanted)
    ]
! !

!EnterBox methodsFor:'accessing'!

title:aString
    "set the title to be displayed at top of enterBox"

    |oldSize|

    oldSize := labelField extent.
    labelField label:aString.
    labelField resize.

    labelField extent ~= oldSize ifTrue:[
        self resize
    ]
!

title:titleString okText:okString abortText:abortString
    "set title and texts in the buttons"

    self title:titleString.
    okButton label:okString.
    abortButton label:abortString
!

title:titleString okText:okString
    "set title and text in okbutton"

    self title:titleString.
    okButton label:okString
!

okText:aString
    "set the text to be displayed in the ok-button"

    |oldSize|

    oldSize := okButton extent.
    okButton label:aString.
    okButton resize.
    okButton extent ~= oldSize ifTrue:[
        self resize
    ]
!

abortText:aString
    "set the text to be displayed in the abort-button"

    |oldSize|

    oldSize := abortButton extent.
    abortButton label:aString.
    abortButton resize.
    abortButton extent ~= oldSize ifTrue:[
        self resize
    ]
!

okText:okString abortText:abortString
    "set both texts displayed in the buttons"

    okButton label:okString.
    abortButton label:abortString.
    okButton resize.
    abortButton resize.
    self resize
!

contents
    "return my contents"

    ^ enterField contents
!

initialText:aString
    "define the initial text in the enterfield. all will be selected initially"

    enterField initialText:aString
!

initialText:aString selectFrom:start to:stop
    "define the initial text in the enterfield, and the part to be selected"

    enterField initialText:aString.
    enterField selectFromLine:1 col:start toLine:1 col:stop
!

action:aBlock
    "set the action to be performed when user presses ok-button;
     aBlock must be nil or a block with one argument "

    okAction := aBlock
!

abortAction:aBlock
    "set the action to be performed when user presses abort-button;
     aBlock must be nil or a block with no arguments"

    abortAction := aBlock
! !

!EnterBox methodsFor:'user interaction'!

hideAndEvaluate:aBlock
    "common processing for all ok-actions (see subclasses);
     shut down box, fetch entered string and evaluate the action with it"

    |string|

    self hide.
    aBlock notNil ifTrue:[
        string := self contents.
        string isNil ifTrue:[
            string := ''
        ] ifFalse:[
            string := string withoutSeparators
        ].
        aBlock value:string
    ]
!

okPressed
    "user pressed ok button - hide myself and evaluate okAction"

    self hideAndEvaluate:okAction
!

abortPressed
    "user pressed abort button - hide myself and evaluate okAction"

    self hideAndEvaluate:abortAction
! !