EnterBox.st
author claus
Mon, 06 Mar 1995 20:29:54 +0100
changeset 97 cbf495fe3b64
parent 90 6e94d68102a4
child 101 88e7faeda854
permissions -rw-r--r--
*** empty log message ***

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

'From Smalltalk/X, Version:2.10.4 on 28-dec-1994 at 2:45:44 pm'!

DialogBox subclass:#EnterBox
	 instanceVariableNames:'labelField enterField'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-DialogBoxes'
!

!EnterBox 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/EnterBox.st,v 1.16 1995-03-06 19:28:30 claus Exp $
"
!

documentation
"
    this class implements a pop-up box to enter some string
    with 2 buttons; a cancel button, and a trigger-action button.
    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 action is performed, which is
    set using:

	aBox action:[ ... ]

    the abort-action defaults to no-action, but can also be set.
    The box can be opened modal (i.e. the currently active view will
    be suspended) or modeless. The default is modal (i.e. sending #open
    is equivalent to #openModal).
"
!

examples 
"
    examples:
	|box|

	box := EnterBox new.
	box title:'your name please:'.
	box action:[:arg | Transcript showCr:'entered: ' , arg printString].
	box open

	|box|

	box := EnterBox new.
	box title:'your name please:'.
	box action:[:arg | Transcript showCr:'entered: ' , arg printString].
	box openModeless

    for easier instance creation, there are also some combination
    methods for instance creation:

	|box|

	box := EnterBox 
		 title:'your name please:'
		 action:[:arg | Transcript showCr:'entered: ' , arg printString].
	box openModeless

    If the box is needed to ask for a simple string, you can also use the
    #request method, to bring up a box, let it ask for something and return
    the entered string. This method will return nil, if the box was
    closed with the 'abort' button.
    Example:

	|box string|

	box := EnterBox request:'input some string:'.
	string isNil ifTrue:[
	    Transcript showCr:'no input'
	] ifFalse:[
	    Transcript showCr:('the enetered string was: ' , string)
	]

    of course, this can be written shorter as:

	|string|

	string := EnterBox request:'input some string:'.
	string isNil ifTrue:[
	    Transcript showCr:'no input'
	] ifFalse:[
	    Transcript showCr:('the enetered string was: ' , string)
	]
"
! !

!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
    "create and return a new EnterBox with title aString"

    ^ self new title:titleString
!

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
!

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

!EnterBox class methodsFor:'defaults'!

minExtent
    ^ self defaultExtent
!

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

!EnterBox class methodsFor:'easy startup '!

request:aTitle
    "create and show an enterBox asking for aTitle.
     Return the enterred string or nil (if abort was pressed).
     The string may be empty, in case return was pressed immediately."

    ^ self new request:aTitle

    "
     EnterBox request:'enter a string'
    "
! !

!EnterBox methodsFor:'accessing'!

contents
    "return my contents"

    ^ enterField contents
!

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

    enterField initialText:aString
!

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

    |oldSize|

    aString ~= labelField label ifTrue:[
	oldSize := labelField extent.
	labelField label:aString.
	labelField resize.

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

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
!

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

    (titleString ~= labelField label or:[okString ~= okButton label]) ifTrue:[
	okButton label:okString.
	okButton resize.
	labelField label:titleString.
	labelField resize.
	shown ifTrue:[self resize].
    ]
!

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

    (titleString ~= labelField label 
     or:[okString ~= okButton label
     or:[abortString ~= abortButton label]]) ifTrue:[
	okButton label:okString.
	okButton resize.
	abortButton label:abortString.
	abortButton resize.
	labelField label:titleString.
	labelField resize.
	shown ifTrue:[self resize].
    ]
! !

!EnterBox methodsFor:'initialization'!

createEnterField
    "this has been extracted from the initialize method
     to allow redefinition in subclasses. (FilenameEnterBox for example)"

    enterField := EditField in:self.
!

initialize
    |space2 innerWidth|

    super initialize.

    self addAbortButton; addOkButton.

    label := 'Enter'.

    space2 := 2 * ViewSpacing.
    innerWidth := width - space2.

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

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

    self createEnterField.
    enterField origin:[ViewSpacing @ (space2 + labelField height)]
	       extent:[(width - space2 - (enterField borderWidth * 2) - margin) @ enterField height].
    enterField leaveAction:[:key | self okPressed].
    enterField addDependent:self. "to get preferedExtent-changes"

    "
     forward keyboard input to the enterfield
    "
    self keyboardHandler:enterField
!

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
!

focusSequence
    ^ Array with:enterField with:abortButton with:okButton 
! !

!EnterBox methodsFor:'dependencies'!

update:something with:someArgument from:changedObject
    "sent if my enterbox thinks it needs more real-estate ..."

    changedObject == enterField ifTrue:[
	something == #preferedExtent ifTrue:[
	    shown ifTrue:[self resize]
	]
    ]
! !

!EnterBox methodsFor:'queries'!

preferedExtent 
    |wWanted hWanted wPanel vs2 min panelPref|

    vs2 := ViewSpacing * 2.
    panelPref := buttonPanel preferedExtent.
    wWanted := (labelField widthIncludingBorder max:enterField preferedExtent x) + vs2.
    wPanel := panelPref x + vs2.
    wPanel > wWanted ifTrue:[
	wWanted := wPanel
    ].
    hWanted := vs2 + labelField height + enterField height +
	       (ViewSpacing * 6) + panelPref y + ViewSpacing.

    min := self class minExtent.
    wWanted <  min x ifTrue:[
	wWanted :=  min x
    ].
    hWanted <  min y ifTrue:[
	hWanted :=  min y
    ].
    ^ wWanted @ hWanted
! !

!EnterBox methodsFor:'user actions'!

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

!EnterBox methodsFor:'startup'!

request
    "open the box and return the entered string or nil, if
     abort was pressed"

    self action:[:string | ^ string].
    self open.
    ^ nil
!

request:title
    "set the title, open the box and return the entered string or nil, if
     abort was pressed"

    self title:title.
    ^ self request
! !