DialogBox.st
author claus
Wed, 03 May 1995 02:30:14 +0200
changeset 118 3ee5ea99d0e2
parent 112 81633ba1bf40
child 120 710d41f17b68
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1994 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 1:38:02 pm'!

ModalBox subclass:#DialogBox
	 instanceVariableNames:'buttonPanel okButton okAction abortButton abortAction
		acceptReturnAsOK yPosition leftIndent addedComponents'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-DialogBoxes'
!

!DialogBox class methodsFor:'documentation'!

version
"
$Header: /cvs/stx/stx/libwidg/DialogBox.st,v 1.8 1995-05-03 00:28:59 claus Exp $
"
!

documentation
"
    this class implements the common behavior of dialogboxes.

    DialogBox is an (abstract) superclass of many other boxes - see InfoBox,
    WarningBox, YesNoBox etc. for concrete examples.
    Most of them simply add buttons or other elements.

    instance variables:

	buttonPanel      <PanelView>    contains the button(s)

	okButton         <Button>       the ok-Button

	okAction         <Block>        the action to be performed when ok is pressed,
					or return is pressed.

	acceptReturnAsOK <Boolean>      if true, pressing the return-key counts
					as if ok was pressed. Default is true.

	abortButton      <Button>       the cancel-Button

	abortAction      <Block>        the action to be performed when cancel is
					pressed.

    For compatibility with ST-80, this class is also available under
    the global names DialogView and Dialog (see patches file).
"
!

examples
"
    mostly, DialogBox is used as an abstract class as a base for InfoBox, 
    YesNoBox etc.
    However, you can construct dialogs programmatically, as shown in
    the following examples:


    DialogBox new open

    DialogBox new addOkButton; open

    DialogBox new addAbortButton; addOkButton; open

    DialogBox new
	addTextLabel:'hello';
	addAbortButton; 
	addOkButton; 
	open

    DialogBox new
	label:'a simple dialog';
	addTextLabel:'hello';
	addAbortButton; 
	addOkButton; 
	extent:200@200;
	sizeFixed:true;
	open

    DialogBox new
	addTextLabel:(Image fromFile:'bitmaps/garfield.gif');
	addAbortButton; 
	addOkButton; 
	open

    DialogBox new
	addTextLabel:'hello';
	addTextLabel:(Image fromFile:'bitmaps/garfield.gif');
	addTextLabel:'world';
	addAbortButton; 
	addOkButton; 
	open

  constructing a dialog from elements:

   adding a fileSelectionList:

     |top panel l scr fileName ok|

     fileName := '' asValue.

     top := DialogBox new.
     top extent:200@300; sizeFixed:true.

     panel := VerticalPanelView new.

     l := FileSelectionList on:fileName.
     l useIndex:false.
     scr := ScrollableView forView:l.
     panel addSubView:scr.
     scr left:0.0; width:1.0.

     top addComponent:panel.
     top addAbortButton; addOkButton.
     top okAction:[ok := true].
     ok := false.
     top openModal.

     ok ifTrue:[
	 Transcript show:'fileName: '; showCr:fileName value storeString.
     ]


   adding a panel with checkBoxes:

     |top panel b model value1 value2 value3 value4 ok|

     value1 := true asValue.
     value2 := false asValue.
     value3 := false asValue.
     value4 := true asValue.

     top := DialogBox new.
     top extent:200@300.

     panel := VerticalPanelView new.

     b := CheckBox on:value1.
     b label:'check1'.
     panel addSubView:b.

     b := CheckBox on:value2.
     b label:'check2'.
     panel addSubView:b.

     b := CheckBox on:value3.
     b label:'check3'.
     panel addSubView:b.

     b := CheckBox on:value4.
     b label:'check4'.
     panel addSubView:b.

     top addComponent:panel.
     top addAbortButton; addOkButton.
     top okAction:[ok := true].
     ok := false.
     top openModal.

     ok ifTrue:[
	 Transcript show:'value1: '; showCr:value1 value.
	 Transcript show:'value2: '; showCr:value2 value.
	 Transcript show:'value3: '; showCr:value3 value.
	 Transcript show:'value4: '; showCr:value4 value.
     ]


"
!

copyright
"
 COPYRIGHT (c) 1994 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 class methodsFor:'startup'!

request:aString 
    "launch a Dialog, which allows user to enter something.
     Return the entered string (may be empty string) 
     or nil (if cancel was pressed)"

    ^ self 
	request:aString 
	displayAt:nil 
	centered:true 
	action:nil 
	initialAnswer:''

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

request:aString initialAnswer:initial
    "launch a Dialog, which allows user to enter something.
     Return the entered string (may be empty string) or nil (if cancel was pressed)"

    ^ self 
	request:aString 
	displayAt:nil 
	centered:true 
	action:nil 
	initialAnswer:initial

    "
     Dialog 
	 request:'enter a string:' 
	 initialAnswer:'the default'  
    "
!

request:aString initialAnswer:initial onCancel:cancelAction
    "launch a Dialog, which allows user to enter something.
     Return the entered string (may be empty string) 
     or cancelValue (if cancel was pressed)"

    |val|

    val :=self 
	request:aString 
	displayAt:nil 
	centered:true 
	action:[:result | ^ result] 
	initialAnswer:initial.

    ^ cancelAction value

    "
     Dialog 
	 request:'enter a string:' 
	 initialAnswer:'the default'  
	 onCancel:['foooo']   
    "
!

request:aString displayAt:aPoint initialAnswer:initial
    "launch a Dialog, which allows user to enter something.
     Return the entered string (may be empty string) or nil (if cancel was pressed)"

    ^ self 
	request:aString 
	displayAt:aPoint 
	centered:true 
	action:nil 
	initialAnswer:initial

    "
     Dialog 
	 request:'enter a string:' 
	 displayAt:(50 @ 50) 
	 initialAnswer:'the default' 
    "
!

request:aString displayAt:aPoint centered:centered action:resultAction initialAnswer:initial
    "launch a Dialog, which allows user to enter a string.
     Return the string (may be empty string) or nil (if cancel was pressed)"

    |box|

    box := EnterBox title:aString.
    box initialText:initial.
    resultAction isNil ifTrue:[
	box action:[:val | ^ val]
    ] ifFalse:[
	box action:[:val | ^ resultAction value:val]
    ].
    aPoint notNil ifTrue:[
	box showAt:aPoint
    ] ifFalse:[
	box showAtPointer
    ].
    ^ nil

    "
     Dialog request:'enter a string:'
	      displayAt:0@0
	       centered:true
		 action:[:result | result printNewline]
	  initialAnswer:'the default'
    "
!

confirm:aString
    "launch a Dialog, which allows user to enter yes or no.
     return true for yes, false for no"

    |box answer|

    box := YesNoBox title:aString.
    box yesAction:[answer := true] noAction:[answer := false].
    box showAtPointer.
    box yesAction:nil noAction:nil.
    ^ answer

    " 
     Dialog confirm:'really ?'
    "
!

confirmWithCancel:aString
    "launch a Dialog, which allows user to enter yes, no and cancel.
     return true for 'yes', false for 'no', nil for 'cancel'"

    |box answer|

    box := OptionBox title:aString numberOfOptions:3. 
    box buttonTitles:(self classResources array:
			#('cancel' 
			  'no' 
			  'yes')
		     )
	     actions:(Array with:[answer := nil]
			    with:[answer := false] 
			    with:[answer := true]
		     ).
    box showAtPointer.
    box actions:nil.
    ^ answer

    "
     Dialog confirmWithCancel:'really ?' nil
    "
!

information:aString
    "launch a Dialog to tell user something"

    (InfoBox title:aString) showAtPointer

    "
     Dialog information:'help'
    "
!

warn:aString
    "launch a Dialog to warn user"

    (WarningBox title:aString) showAtPointer

    "
     Dialog warn:'help'
    "
!

requestFileName:titleString default:defaultName
    "launch a Dialog, which allows user to enter a filename.
     The box will not allow pressing 'ok' without an entered string.
     Return the pathname string consisting of the full pathname of the filename,
     or an empty string (if cancel was pressed)."

    ^ self requestFileName:titleString 
		   default:defaultName 
		   version:nil 
		    ifFail:''

    "
     Dialog requestFileName:'enter a fileName:' default:''  
     Dialog requestFileName:'enter a fileName:' default:'Makefile.bak'  
    "
!

requestFileName:titleString default:defaultName version:versionSymbol
    "launch a Dialog, which allows user to enter a filename.
     The box will not allow pressing 'ok' without an entered string.
     Return the pathname string or the empty string if cancel was pressed.
     The version argument is ignored on Unix, but may at some time in the
     future be used on systems like VMS (which support file versioning)."

    ^ self requestFileName:titleString 
		   default:defaultName 
		   version:versionSymbol 
		    ifFail:''

    "
     Dialog requestFileName:'enter a fileName:'
			default:''
			version:nil
    "
!

requestFileName:titleString default:defaultName version:versionSymbol ifFail:failBlock
    "launch a Dialog, which allows user to enter a filename.
     The box will not allow pressing 'ok' without an entered string.
     Return the string or the value of failBlock if cancel was pressed.
     The version argument is ignored on Unix, but may at some time in the
     future be used on systems like VMS (which support file versioning)."

    |box|

    box := FileSelectionBox title:titleString.
    box initialText:defaultName.
    box action:[:name | ^ name].
    box showAtPointer.
    box action:nil.
    ^ failBlock value

    "
     Dialog requestFileName:'enter a fileName:'
			default:''
			version:nil
			 ifFail:['none']   
    "
!

requestFileName:titleString default:defaultName ok:okText abort:abortText pattern:pattern
    "launch a Dialog, which allows user to enter a filename.
     The box will show okText in its okButton, abortText in the abortButton.
     The matchPattern is set to pattern initially.
     Return the string or nil if cancel was pressed."

    |box|

    box := FileSelectionBox 
	       title:titleString
	       okText:okText 
	       abortText:abortText
	       action:[:fileName | ^ fileName].
    box pattern:pattern.
    box initialText:defaultName.
    box showAtPointer.
    box action:nil.
    ^ nil

    "
     Dialog requestFileName:'enter a fileName:'
			default:''
			     ok:'yeah' 
			  abort:'oh, no' 
			pattern:'*.st'   
    "
! !

!DialogBox methodsFor:'user actions'!

okPressed
    "user pressed ok-button; make myself invisible and if an action was
     specified do it"

    okButton turnOffWithoutRedraw.
    self hideAndEvaluate:okAction
!

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

    abortButton turnOffWithoutRedraw.
    self hideAndEvaluate:abortAction
!

keyPress:aKey x:x y:y
    "return-key dublicates ok-function if acceptReturnAsOK is true"

    acceptReturnAsOK ifTrue:[
	(aKey == #Return) ifTrue:[^ self okPressed]
    ].
    super keyPress:aKey x:x y:y
! !

!DialogBox methodsFor:'queries'!

positionOffset
    "return the delta, by which the box should be displayed
     from the mouse pointer. Value returned here makes center of
     okButton appear under the cursor"

    okButton isNil ifTrue:[
	^ super positionOffset
    ].
    buttonPanel setChildPositionsIfChanged.
    ^ (okButton originRelativeTo:self) + (okButton extent // 2)
!

preferedExtent 
    "return my prefered extent"

    |w h p|

    addedComponents notNil ifTrue:[
	w := addedComponents 
		inject:0 
		into:[:max :element | 
			max max:(element preferedExtent x + element leftInset)].
    ] ifFalse:[
	w := super preferedExtent x.
    ].
    h := ViewSpacing
	 + yPosition
	 + ViewSpacing.

    okButton notNil ifTrue:[
	p := buttonPanel preferedExtent.
	w := w max:p x.
	h := h
	     + p y
	     + ViewSpacing.
    ].

"/    okButton isNil ifTrue:[
"/        ^ super preferedExtent
"/    ].
"/    p := buttonPanel preferedExtent.
"/    w := p x.
"/    h := ViewSpacing
"/         + p y
"/         + ViewSpacing.
"/
    ^ w @ h
! !

!DialogBox methodsFor:'initialization'!

initialize
    |mm|

    super initialize.

    label := 'Dialog'.

    mm := ViewSpacing.

    acceptReturnAsOK := true.

    buttonPanel := HorizontalPanelView in:self.
    buttonPanel 
	origin:(0.0 @ 1.0) corner:(1.0 @ 1.0);
	bottomInset:mm; 
	topInset:(font height + mm * 2) negated;
	borderWidth:0;
	layout:#spread.

    yPosition := 0.
    leftIndent := 0.

    "
     |b|
     b := DialogBox new.
     b addAbortButton; 
       addOkButton; 
       showAtPointer
    "
    "
     |b|
     b := DialogBox new.
     b addOkButton; 
       showAtPointer
    "
    "
     |b|
     b := DialogBox new.
     b addTextLabel:'hello world';
       addOkButton; 
       showAtPointer
    "
    "
     |b|
     b := DialogBox new.
     b addTextLabel:'hello world';
       addVerticalSpace:50; 
       addOkButton; 
       showAtPointer
    "
!

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

    super reAdjustGeometry.
    okButton notNil ifTrue:[okButton resize].
    abortButton notNil ifTrue:[abortButton resize].
    self resize
!

focusSequence
    ^ buttonPanel subViews
! !

!DialogBox methodsFor:'construction-adding'!

addButton:aButton after:someOtherButtonOrNil
    "add a button in the buttonPanel.
     If the argument someOtherButtonOrNil is nil, the button is
     added at the end."

    buttonPanel addSubView:aButton after:someOtherButtonOrNil.
    buttonPanel subViews size > 1 ifTrue:[
	buttonPanel layout:#fitSpace.
    ].
!

addButton:aButton
    "add a button in the buttonPanel"

    self addButton:aButton after:nil
!

addOkButton:action
    "create an okButton - to be sent from redefined initialize
     methods in subclasses."

    okButton := Button okButton.
    action notNil ifTrue:[okButton action:action].
    okButton model:self; change:#okPressed.
    okButton isReturnButton:acceptReturnAsOK.
    self addButton:okButton.
!

addOkButton
    "create an okButton - to be sent from redefined initialize
     methods in subclasses."

    self addOkButton:nil
!

addAbortButton
    "create an abortButton - to be sent from redefined initialize
     methods in subclasses."

    abortButton := Button abortButton.
    abortButton model:self; change:#abortPressed.
    self addButton:abortButton.
!

addVerticalSpace:nPixel
    yPosition := yPosition + nPixel.
!

addComponent:aComponent
    "add a component with its prefered height and full width"

    addedComponents isNil ifTrue:[
	addedComponents := OrderedCollection new.
    ].
    addedComponents add:aComponent.
    self addSubView:aComponent.
    aComponent height:(aComponent preferedExtent y).
    aComponent origin:0.0@yPosition; width:1.0; leftInset:leftIndent.
    yPosition := yPosition + aComponent height.
!

addTextLabel:aString
    "create a text label - the name has been choosen for ST-80 compatibility;
     however, ST/X labels allow image labels too."

    |l|

    l := Label new label:aString.
    l 
	origin:(0.0 @ 0.0);
	topInset:yPosition; 
	bottomInset:yPosition negated;
	leftInset:leftIndent;
	rightInset:leftIndent negated.

    self addComponent:l.

    "
     |b|

     b := DialogBox new.
     b addTextLabel:'hello'.
     b showAtPointer
    "
    "
     |b|

     b := DialogBox new.
     b leftIndent:100.
     b addTextLabel:'hello'.
     b leftIndent:0.
     b addTextLabel:'world'.
     b showAtPointer
    "
    "
     |b|

     b := DialogBox new.
     b addTextLabel:'hello'.
     b addTextLabel:'world'.
     b addOkButton.
     b showAtPointer
    "
    "
     |b|

     b := DialogBox new.
     b addTextLabel:'hello world\\How about this ?' withCRs.
     b addOkButton.
     b showAtPointer
    "
    "
     |b|

     b := DialogBox new.
     b addTextLabel:'hello world\\How about this ?' withCRs.
     b addTextLabel:'not bad'.
     b addAbortButton.
     b addOkButton.
     b showAtPointer
    "
!

addCheckBox:label on:aModel
    |b|

    b := CheckBox on:aModel.
    b label:label.
    self addComponent:b.
    ^ b
!

yPosition 
    ^ yPosition 
!

yPosition:aNumber 
    yPosition := aNumber.
!

leftIndent:aNumber 
    leftIndent := aNumber.
! !

!DialogBox methodsFor:'private'!

hideAndEvaluate:aBlock
    "make myself invisible and evaluate aBlock"

    self hide.
    aBlock notNil ifTrue:[aBlock value]
! !

!DialogBox methodsFor:'accessing'!

acceptReturnAsOK:aBoolean
    "turn on/off interpretation of return-key as ok.
     Default is on"

    acceptReturnAsOK := aBoolean.
    okButton notNil ifTrue:[
	okButton isReturnButton:aBoolean.
    ]
!

okAction:aBlock
    "define the action to be performed when ok is pressed"

    okAction := aBlock
!

action:aBlock
    "set the action to be performed when user presses ok-button;
     aBlock must be nil or a block. This method simply
     reuses okAction: and has been added for a consistent action-setting
     protocol."

    self okAction:aBlock
!

okButton
    "return the okButton"

    ^ okButton
!

okText:aString
    "define the text in the ok-button"

    |oldSize|

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

abortAction:aBlock
    "define the action to be performed when abort is pressed"

    abortAction := aBlock
!

abortButton
    "return the abortButton"

    ^ abortButton
!

abortText:aString
    "define the label in the abort-button"

    |oldSize|

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

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

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