EnterBox.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 03:26:58 +0100
changeset 197 00927189c882
parent 181 dc72c27581b7
child 242 1fa14a974cc2
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.
"

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

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

    non-modal:
	|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 entered 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 entered string was: ' , string)
	]


    A box for passwords is created with:

	|box|

	box := EnterBox 
		 title:'your name please:'
		 action:[:arg | Transcript showCr:'entered: ' , arg printString].
	box enterField passwordCharacter:$*.
	box showAtPointer

    or simply:

	|string|

	string := EnterBox requestPassword:'enter your password:'.
	Transcript showCr:string.
"

    "Modified: 16.11.1995 / 21:28:11 / cg"
!

version
    ^ '$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.33 1995-11-23 02:24:52 cg Exp $'
! !

!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 action:aBlock
    "create and return a new EnterBox with title aString,
     which will evaluate aBlock when 'ok' is pressed"

    ^ (self 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 title:titleString okText:okText action:aBlock) abortText:abortText 
!

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

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

!EnterBox class methodsFor:'defaults'!

defaultExtent
    ^ (Screen current pixelPerMillimeter * (60 @ 30)) rounded
!

minExtent
    ^ self defaultExtent
! !

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

requestPassword:aTitle
    "create and show an enterBox asking for aTitle.
     The box is setup to NOT display entered characters (as with password entry).
     Return the entered string or nil (if abort was pressed).
     The string may be empty, in case return was pressed immediately."

    ^ self new requestPassword:aTitle

    "
     |s|

     s := EnterBox requestPassword:'enter a string'.
     Transcript showCr:'you entered: ' , s
    "

    "Created: 16.11.1995 / 21:25:08 / cg"
! !

!EnterBox methodsFor:'accessing'!

contents
    "return my contents"

    ^ enterField contents
!

contents:aString
    "set my contents"

    enterField contents:aString
!

enterField
    "provide access to the entryfield"

    ^ enterField

    "Created: 16.11.1995 / 21:23:48 / cg"
!

entryCompletionBlock:aBlock
    enterField entryCompletionBlock:aBlock
!

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
!

labelField
    "provide access to the labelfield"

    ^ labelField

    "Created: 16.11.1995 / 21:23:48 / cg"
!

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

    |oldSize|

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

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

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 forceResize.
	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 forceResize.
	shown ifTrue:[self resize].
    ]
! !

!EnterBox methodsFor:'change & update'!

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

    changedObject == enterField ifTrue:[
	something == #preferredExtent ifTrue:[
	    shown ifTrue:[self resizeUnderPointer].
	    ^ self
	]
    ].
    super update:something with:someArgument from:changedObject
! !

!EnterBox methodsFor:'initialization'!

createEnterField
    "this has been extracted from the initialize method
     to allow redefinition in subclasses. (FilenameEnterBox for example).
     It shall return a new instance of the desired editField class."

     ^ EditField new.
!

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

initialize
    |space2 innerWidth|

    super initialize.

    self addAbortButton; addOkButton.

    label := resources string:'Enter'.

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

    labelField := Label in:self.
    labelField 
	label:''; 
	borderWidth:0;
	adjust:#left;
	origin:(0.0 @ ViewSpacing) extent:[1.0 @ labelField height];
	leftInset:ViewSpacing; 
	rightInset:ViewSpacing.

    self addComponent:(enterField := self createEnterField).
    enterField 
	origin:[0.0 @ (space2 + labelField preferredExtent y "height")]
	extent:(1.0 @ enterField height).
    enterField 
	leftInset:ViewSpacing-enterField borderWidth; 
	rightInset:ViewSpacing;
	leaveAction:[:key | self okPressed].

    enterField addDependent:self. "to get preferredExtent-changes"

    "
     forward keyboard input to the enterfield
    "
    self delegate:(KeyboardForwarder toView:enterField condition:#noFocus).
    enterField hasKeyboardFocus:true.
!

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

preferredExtent 
    |wWanted hWanted wPanel vs2 min 
     labelPref enterPref panelPref|

    panelPref := buttonPanel preferredExtent.
    labelPref := labelField preferredExtent.
    enterPref := enterField preferredExtent.
    wWanted := (labelPref x max:enterPref x).
    wPanel := panelPref x.
    wPanel > wWanted ifTrue:[
	wWanted := wPanel
    ].

    hWanted := labelPref y + enterPref y +
	       (ViewSpacing * 6) + panelPref y + ViewSpacing.

    min := self class minExtent.
    wWanted <  min x ifTrue:[
	wWanted :=  min x
    ].
    hWanted <  min y ifTrue:[
	hWanted :=  min y
    ].
    vs2 := ViewSpacing * 2.
    ^ (wWanted + vs2) @ (hWanted + vs2) 
! !

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

requestPassword
    "open the box for a password (i.e. hide entered characters)
     and return the entered string or nil, if abort was pressed"

    enterField passwordCharacter:$*.
    ^ self request.

    "Created: 16.11.1995 / 21:25:33 / cg"
!

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

    enterField passwordCharacter:$*.
    ^ self request:title

    "Created: 16.11.1995 / 21:25:33 / cg"
! !

!EnterBox methodsFor:'user actions'!

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

    |string|

    (windowGroup notNil and:[windowGroup isModal]) ifTrue:[
	self hide.
    ].
    aBlock notNil ifTrue:[
	string := self contents.
	string isNil ifTrue:[
	    string := ''
	] ifFalse:[
	    string := string withoutSeparators
	].
	aBlock value:string
    ]
! !