DialogBox.st
author Claus Gittinger <cg@exept.de>
Fri, 17 Nov 1995 09:59:40 +0100
changeset 183 b40623839205
parent 174 d80a6cc3f9b2
child 197 00927189c882
permissions -rw-r--r--
requestPassword also here

"
 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.5 on 3-may-1995 at 2:41:07 am'!

ModalBox subclass:#DialogBox
	 instanceVariableNames:'buttonPanel okButton okAction abortButton abortAction
		acceptReturnAsOK yPosition leftIndent rightIndent bindings addedComponents
		inputFieldGroup acceptOnLeave acceptValue tabableElements'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-DialogBoxes'
!

!DialogBox class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/DialogBox.st,v 1.26 1995-11-17 08:59:40 cg 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.

    For programmatically created boxes, instances support adding of components
    in a top-to-bottom fashion, and also keep track of added text-fields and,
    since they are most common, automatically create an EnterFieldGroup for
    them.
    Caveat: more adding support is required - especially for row-wise
    construction.

    Historic note:
	originally, ST/X had separate classes for the various entry methods;
	there were YesNoBox, EnterBox, InfoBox and so on.
	ST-80 has all this defined in the common Dialog.
	Therefore, for compatibility, many ST/X methods defined here in Dialogs 
	class protocol simply dispatch to some other boxes class method.



    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.

	yPosisition      <Integer>      current y position when adding components

	leftIndent       <Integer>      left inset to use when adding components

	rightIndent      <Integer>      right inset to use when adding components

	addedComponents  <Collection>   programmatically added components

	inputFieldGroup  <EnterFieldGroup>   
					for added input fields

	acceptOnLeave    <Boolean>      if true (the default) and there are 
					tabable inputFields, accept and close when
					the last field is left. If false, the ok
					button must be pressed to close the box.

	acceptedValue    v(<Boolean>)   valueHolder on a boolean
					after close: holds true if box was accepted
					(i.e. ok-Button was pressed), false if box was
					closed via cancel or window manager.

        
    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.
    For most simple standard dialogs, there are ready to use
    methods in the class protocol.
    For example:

      info & warnings:

	Dialog information:'hi there'

	Dialog warn:'oops'


      yes/no questions:

	(Dialog confirm:'is this simple ?')
	ifTrue:[
	    Transcript showCr:'thats what I expected'
	] ifFalse:[
	    Transcript showCr:'read more examples and documentation'
	]


      yes/no question with cancel option:

	|answer|

	answer := Dialog confirmWithCancel:'is this simple ?'.
	answer isNil ifTrue:[
	    Transcript showCr:'no easy decision'
	] ifFalse:[
	    answer ifTrue:[
		Transcript showCr:'thats what I expected'
	    ] ifFalse:[
		Transcript showCr:'read more examples and documentation'
	    ]
	]


      asking for a string:

	|s|

	s := Dialog request:'enter your name, please:'.
	s notEmpty ifTrue:[
	    Transcript showCr:'you entered: ' , s.
	]


      asking for a string with given default:

	|s|

	s := Dialog 
		request:'enter your name, please:'
		initialAnswer:(OperatingSystem getLoginName).
	s notEmpty ifTrue:[
	    Transcript showCr:'you entered: ' , s.
	]


      asking for a filename:

	|s|

	s := Dialog 
		requestFileName:'select a file, please:'
		default:''.
	Transcript show:'you entered: '; showCr:s.


      with changed button label and pattern:

	|s|

	s := Dialog 
		requestFileName:'select a file, please:'
		default:''
		ok:'show'
		abort:'cancel'
		pattern:'*.rc'.
	Transcript show:'you entered: '; showCr:s.

    However, you can construct dialogs programmatically, as shown in
    the following examples:

    basic (unusable) example:

	DialogBox new open

    still unusable - only an ok-button:

	DialogBox new addOkButton; open

    both ok- and abortButtons:

	DialogBox new addAbortButton; addOkButton; open

    with different ok-label:

	DialogBox new addAbortButton; addOkButtonLabelled:'yeah'; open

    adding a textlabel gives an infoBox:

	DialogBox new
	    addTextLabel:'hello';
	    addOkButton; 
	    open

    a textlabel with abort- and okButton gives a yesNoBox:

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

    the same, adjusting the labels contents to the left:

	|box|

	box := DialogBox new.
	(box addTextLabel:'hello') adjust:#left.
	box addAbortButton; 
	    addOkButton; 
	    open

    with modified buttons:

	|box|

	box := DialogBox new.
	(box addTextLabel:'are you certain ?') adjust:#left.
	box addAbortButtonLabelled:'not really'. 
	(box addOkButtonLabelled:'yes, absolutely') 
		activeBackgroundColor:Color red. 
	box open


    mswindows style:

	|b box|

	box := DialogBox new.
	(box addTextLabel:'are you certain ?') adjust:#left.
	b := Button new.
	b activeLogo:(Image fromFile:'bitmaps/cancel_down.bmp').
	b passiveLogo:(Image fromFile:'bitmaps/cancel_up.bmp').
	b focusLogo:(Image fromFile:'bitmaps/cancel_focus.bmp').
	b beImageButton.
	box addAbortButton:b.

	b := Button new.
	b activeLogo:(Image fromFile:'bitmaps/ok_down.bmp').
	b passiveLogo:(Image fromFile:'bitmaps/ok_up.bmp').
	b focusLogo:(Image fromFile:'bitmaps/ok_focus.bmp').
	b beImageButton.
	box addOkButton:b.
	box open


    two textlabels:

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

    fixing the dialogs size (suppres it calculating its size from the
    preferredExtents of its components):

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

    asking the box if it was closed via ok:

	(DialogBox new
	    label:'a simple dialog';
	    addTextLabel:'hello';
	    addAbortButton; 
	    addOkButton; 
	    extent:200@200;
	    sizeFixed:true;
	    open
	) accepted ifTrue:[
	    Transcript showCr:'yes'
	] ifFalse:[
	    Transcript showCr:'no'
	]

    textLabels are not limited to strings (although, the name which is
    used for ST-80 compatibility, suggests it):

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

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

    adding an input field (on a string model):

	|stringModel|

	stringModel := '' asValue.
	(DialogBox new
	    addTextLabel:'Please enter a string:';
	    addInputFieldOn:stringModel; 
	    addAbortButton; 
	    addOkButton; 
	    open
	) accepted ifTrue:[
	    Transcript showCr:'entered: ', stringModel value
	]


    multiple input fields (notice, that the dialog connects the fields
    in a group, so stepping is allowed via Cursor and Return keys):

	|firstName lastName|

	firstName := '' asValue.
	lastName := '' asValue.
	(DialogBox new
	    addTextLabel:'Please enter your name:';
	    addInputFieldOn:firstName; 
	    addVerticalSpace;
	    addInputFieldOn:lastName; 
	    addAbortButton; 
	    addOkButton; 
	    open
	) accepted ifTrue:[
	    Transcript showCr:'entered: ', firstName value , ' ' , lastName value
	]


    of course, the model may contain a value initially:

	|firstName lastName p line i name|

	firstName := '' asValue.
	lastName := '' asValue.
	p := PipeStream readingFrom:'finger ' , OperatingSystem getLoginName.
	p notNil ifTrue:[
	    line := p nextLine.
	    (i := line findString:'Name:') ~~ 0 ifTrue:[
		name := line copyFrom:(i + 'Name:' size).
	    ] ifFalse:[
		(i := line findString:'real life:') == 0 ifTrue:[
		    line := p nextLine.
		].
		(i := line findString:'real life:') ~~ 0 ifTrue:[
		    name := line copyFrom:(i + 'real life:' size).
		]
	    ].
	    name notNil ifTrue:[
		firstName value: name asCollectionOfWords first.
		lastName  value: name asCollectionOfWords last.
		Transcript showCr:'initially ' , firstName value , ' ' , lastName value.
	    ].
	    p close.
	].

	(DialogBox new
	    addTextLabel:'Please enter your name:';
	    addInputFieldOn:firstName; 
	    addVerticalSpace;
	    addInputFieldOn:lastName; 
	    addAbortButton; 
	    addOkButton;
	    open
	) accepted ifTrue:[
	    Transcript showCr:'entered: ', firstName value , ' ' , lastName value
	]


   constructing a dialog from other elements:

     adding a fileSelectionList:
     (since the dialog adds the component with its preferred extent,
      ignoring the 300-height, this looks ugly ... 
      ... especially when resized vertically)

	|top l scr fileName|

	fileName := '' asValue.

	top := DialogBox new.

	l := FileSelectionList new.
	l useIndex:false.
	l doubleClickAction:[:name | top okPressed].
	l action:[:name | fileName value:name].
	scr := ScrollableView forView:l.
	scr extent:(1.0 @ 300).

	top addComponent:scr.
	top addAbortButton; addOkButton.
	top openModal.

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

    same, looks better, since the height is made larger (not using 
    fileLists preferredExtent):

	|top l scr fileName|

	fileName := '' asValue.

	top := DialogBox new.

	l := FileSelectionList new.
	l useIndex:false.
	l doubleClickAction:[:name | top okPressed].
	l action:[:name | fileName value:name].
	scr := ScrollableView forView:l.

	top addComponent:scr withExtent:300@300.
	top addAbortButton; addOkButton.
	top openModal.

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


    again, setting the boxes initial size and fixing it
    (let it ignore the components' preferredExtent):

	|top fixFrame l scr fileName|

	fileName := '' asValue.

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

	fixFrame := View new.
	fixFrame extent:(1.0 @ 300).

	l := FileSelectionList new.
	l useIndex:false.
	l doubleClickAction:[:name | top okPressed].
	l action:[:name | fileName value:name].
	scr := ScrollableView forView:l.
	scr origin:0.0@0.0 corner:1.0@1.0.
	fixFrame add:scr.

	top addComponent:fixFrame.
	top addAbortButton; addOkButton.
	top openModal.

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


   adding a panel with checkBoxes:

	|top panel b value1 value2 value3 value4|

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

	top accepted 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.
	]

   same, using a more convenient interface:

	|box value1 value2 value3 value4|

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

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

	box addCheckBox:'check1' on:value1.
	box addVerticalSpace.
	box addCheckBox:'check2' on:value2.
	box addVerticalSpace.
	box addCheckBox:'check3' on:value3.
	box addVerticalSpace.
	box addCheckBox:'check4' on:value4.

	box addAbortButton; addOkButton.
	box open.

	box accepted 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.
	]


    adding two panels in a frame:

	|box frame vPanel1 vPanel2 m1 m2 m3 m4 chk ef|

	box := Dialog new.
	box label:'example'.

	frame := FramedBox label:'frame'.

	vPanel1 := VerticalPanelView origin:0.0@0.0 corner:0.5@1.0 in:frame.
	vPanel1 horizontalLayout:#leftSpace.
	vPanel1 verticalLayout:#top.

	vPanel2 := VerticalPanelView origin:0.5@0.0 corner:1.0@1.0 in:frame.
	vPanel2 horizontalLayout:#leftSpace.
	vPanel2 verticalLayout:#top.

	m1 := true asValue.
	m2 := true asValue.
	m3 := true asValue.
	m4 := 'hello' asValue.

	vPanel1 add:(Label label:'check1').
	vPanel1 add:(Label label:'m2').
	vPanel1 add:(Label label:'m3').
	vPanel1 add:(Label label:'enter').
	vPanel1 add:(Label label:'lbl1').
	vPanel1 add:(Label label:'lbl2').

	vPanel2 add:(chk := CheckToggle on:m1). 
	box makeTabable:chk.

	vPanel2 add:(chk := CheckToggle on:m2). 
	box makeTabable:chk.

	vPanel2 add:(chk := CheckToggle on:m3). 
	box makeTabable:chk.

	vPanel2 add:(chk := CheckToggle on:m3). 
	box makeTabable:chk.

	vPanel2 add:(chk := CheckToggle on:m3). 
	box makeTabable:chk.

	vPanel2 add:(ef := EditField on:m4). 
	ef immediateAccept:true.
	box makeTabable:ef.

	box addComponent:frame.

	box addAbortButton; addOkButton.
	box openModal.
	box accepted ifTrue:[
	    Transcript showCr:'accepted with:'.
	    Transcript showCr:'   m1: ' , m1 value printString.
	    Transcript showCr:'   m2: ' , m2 value printString.
	    Transcript showCr:'   m3: ' , m3 value printString.
	    Transcript showCr:'   m4: ' , m4 value printString.
	]



    a full example:

	|box warnSTX allowUnderscore immutableArrays logDoits
	 listOfLanguages listOfStyles styleNames 
	 frame panel c resourceDir dir |

	warnSTX := Compiler warnSTXSpecials asValue.
	allowUnderscore := Compiler allowUnderscoreInIdentifier asValue.
	immutableArrays := Compiler arraysAreImmutable asValue.

	logDoits := Smalltalk logDoits asValue.

	listOfLanguages := SelectionInList with:#('english'
						  'french'
						  'german'
						  'italian'
						  'spanish'
						 ).
	listOfLanguages selection:(Language asString).


	resourceDir := Smalltalk getSystemFileName:'resources'.
	dir := FileDirectory directoryNamed:resourceDir.

	styleNames := dir select:[:aFileName | aFileName endsWith:'.style'].
	styleNames := styleNames collect:[:aFileName | aFileName copyWithoutLast:6].
	listOfStyles := SelectionInList with:styleNames sort.
	listOfStyles selection:(View defaultStyle asString).

	box := Dialog new.
	box label:'Settings'.

	frame := FramedBox label:'Compiler'.
	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame.
	panel horizontalLayout:#leftSpace.

	panel add:((CheckBox on:warnSTX) label:'warn about ST/X language extensions'; resize).
	panel add:((CheckBox on:allowUnderscore) label:'allow underscore in identifiers'; resize).
	panel add:((CheckBox on:immutableArrays) label:'literal arrays are immutable'; resize).
	box addComponent:frame.

	frame := FramedBox label:'Misc'.
	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame.
	panel horizontalLayout:#leftSpace.

	panel add:((CheckBox on:logDoits) label:'log doIts in changes file'; resize).
	box addComponent:frame.

	frame := FramedBox label:'Language'.
	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame.
	panel horizontalLayout:#leftSpace.

	panel add:((PopUpList on:listOfLanguages) width:0.5).
	box addComponent:frame.

	frame := FramedBox label:'Style'.
	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame.
	panel horizontalLayout:#leftSpace.

	panel add:((PopUpList on:listOfStyles) width:0.5).
	box addComponent:frame.

	box addAbortButton; addOkButton.
	box showAtPointer.

	box accepted ifTrue:[
	    Transcript topView withCursor:Cursor wait do:[
		Compiler warnSTXSpecials:warnSTX value.
		Compiler allowUnderscoreInIdentifier:allowUnderscore value.
		Compiler arraysAreImmutable:immutableArrays value.

		Smalltalk logDoits:logDoits value.

		Transcript showCr:'change language to ' , listOfLanguages selection , ' ...'.
		Smalltalk at:#Language put:listOfLanguages selection asSymbol.
		Smalltalk changed:#Language.
		ResourcePack flushCachedResourcePacks.

		Transcript showCr:'change style to ' , listOfStyles selection , ' ...'.
		View defaultStyle:listOfStyles selection asSymbol.
	    ]
	]
"
!

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:'common dialogs'!

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

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

    ^ EnterBox requestPassword:aString 

    "
     Dialog 
	 requestPassword:'enter secret:'
    "

    "Created: 17.11.1995 / 09:45:21 / cg"
!

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

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

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
    ].
    ^ ''  "/ used to be nil - but that is incompatible to ST-80

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

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

confirm:aString initialAnswer:what
    "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].
    what == false ifTrue:[
	box okButton isReturnButton:false.
	box acceptReturnAsOK:false.
    ].
    box showAtPointer.
    box yesAction:nil noAction:nil.
    ^ answer

    " 
     Dialog confirm:'really ?' initialAnswer:false
    "
!

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

choose:aString labels:buttonLabels values:values default:default
    "launch a Dialog, which allows user to enter any of buttonLabels.
     Returning a corresponding value from the values-array."

    |box answer idx|

    box := OptionBox title:aString numberOfOptions:buttonLabels size. 
    box buttonTitles:(self classResources array:buttonLabels)
	     actions:(values collect:[:val | [answer := val]]).
    answer := default.
    box buttons last isReturnButton:false.
    idx := values indexOf:default.
    idx ~~ 0 ifTrue:[box defaultButtonIndex:idx].
    box showAtPointer.
    box actions:nil.
    ^ answer

    "
     Dialog 
	choose:'choose any' 
	labels:#('one' 'two' 'three' 'four') 
	values:#(1 2 3 4) 
	default:2 
    "
    "
     Dialog 
	choose:'choose any' 
	labels:#('one' 'two' 'three' 'four') 
	values:#(1 2 3 4) 
	default:nil 
    "
! !

!DialogBox methodsFor:'user actions'!

doAccept
    "let all components accept (i.e. update their model from the values),
     then set my accept value to true.
     This is confusing: this method was originally called #accept,
     but renamed for compatibility with ST-80, where #accept returns the
     accept-valueHolder (which looks like a bad name to me ...)."

    addedComponents notNil ifTrue:[
	addedComponents do:[:aComponent |
	    (aComponent respondsTo:#accept) ifTrue:[
		 aComponent accept
	    ]
	].
    ].
    acceptValue value:true.
!

lastFieldLeft
    "if the dialog involves input fields, this is called
     when the last field is left by Return-key or NextField-key"

    acceptOnLeave ifTrue:[
	acceptValue value:true. 
	self okPressed
    ].
!

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

    okButton notNil ifTrue:[okButton turnOffWithoutRedraw].
    self doAccept.

    "/ actually, only hides if I have been opened modal
    self hideAndEvaluate:okAction.
!

abortPressed
    "sent by the cancel button; user pressed abort button
     - hide myself and evaluate okAction"

    abortButton turnOffWithoutRedraw.
    acceptValue value:false.

    "/ actually, only hides if I have been opened modal
    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:'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."

    |h|

    buttonPanel addSubView:aButton after:someOtherButtonOrNil.
    buttonPanel subViews size > 1 ifTrue:[
	buttonPanel horizontalLayout:#fitSpace.
    ].
    (h := (aButton heightIncludingBorder + (ViewSpacing * 2))) > buttonPanel topInset ifTrue:[
	 buttonPanel topInset:h negated
    ].
    ^ aButton
!

addOkButton:aButton 
    "add an already created okButton - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     Returns the button."

    okButton := aButton.
    aButton model:self; change:#okPressed.
    ^ self addButton:aButton.

    "Modified: 17.9.1995 / 20:20:41 / claus"
!

addOkButtonLabelled:buttonLabel 
    "create an okButton with a label - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     A nil argument creates one with the default text.
     Returns the button."

    |aButton|

    aButton := Button okButton.
    buttonLabel notNil ifTrue:[aButton label:buttonLabel].
    aButton isReturnButton:acceptReturnAsOK.
    ^ self addOkButton:aButton.

    "Modified: 17.9.1995 / 20:19:49 / claus"
!

addOkButton
    "create an okButton - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     Returns the button."

    ^ self addOkButtonLabelled:nil
!

addButton:aButton
    "add a button into the buttonPanel.
     Returns the button."

    ^ self addButton:aButton after:nil
!

addAbortButton:aButton 
    "add an already created abortButton - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     Returns the button."

    abortButton := aButton.
    aButton model:self; change:#abortPressed.
    ^ self addButton:aButton.

    "Created: 17.9.1995 / 20:17:26 / claus"
!

addAbortButtonLabelled:buttonLabel
    "create an abortButton with a label - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     A nil argument creates one with the default label.
     Returns the button."

    |aButton|

    aButton := Button abortButton.
    buttonLabel notNil ifTrue:[aButton label:buttonLabel].
    ^ self addAbortButton:aButton

    "Modified: 17.9.1995 / 20:18:00 / claus"
!

addAbortButton
    "create an abortButton - to be sent from redefined initialize
     methods in subclasses or when creating a box programmatically.
     Returns the button."

    ^ self addAbortButtonLabelled:nil
!

addColumn:aRow fromX:leftX toX:rightX collect:aBlock
    "add some elements in a vertical column.
     Equally space elements as returned from aBlock."

    |helper component|

    helper := VerticalPanelView new.

    aRow do:[:el |
	component := aBlock value:el.
	helper add:component.
	component resize.
    ].    

    helper resize.
    self addComponent:helper.
    width < helper preferredExtent x ifTrue:[
	self width:helper preferredExtent x.
Transcript show:'w now: '; showCr:helper preferredExtent x
    ].
    helper horizontalLayout:#fit.
    helper left:leftX asFloat;
	   right:rightX asFloat.

    "
     |dialog|

     dialog := Dialog new.
     dialog 
	addColumn:#('a' 'b' 'c' 'd')
	fromX:0
	toX:1
	collect:[:label | Label label:label].

     dialog addOkButton.
     dialog open.
    "

    "
     |dialog y|

     dialog := Dialog new.
     y := dialog yPosition.
     dialog 
	addColumn:#('a1' 'b1' 'c1' 'd1')
	fromX:0
	toX:(1/3) 
	collect:[:label | Label label:label].

     dialog yPosition:y.
     dialog 
	addColumn:#('a2' 'b2' 'c2' 'd2')
	fromX:(1/3)
	toX:(2/3) 
	collect:[:label | Label label:label].

     dialog yPosition:y.
     dialog 
	addColumn:#('a3' 'b3' 'c3' 'd3')
	fromX:(2/3)
	toX:1 
	collect:[:label | Label label:label].

     dialog addOkButton.
     dialog open.
    "
!

addRow:aCol fromX:leftX toX:rightX collect:aBlock
    "add some elements in a horizontal row.
     Equally space elements as returned from aBlock.
     Advance y."

    |helper component|

    helper := HorizontalPanelView new.

    aCol do:[:el |
	component := aBlock value:el.
	component resize.
	helper add:component.
    ].    

    helper resize.
    self addComponent:helper.
    width < helper preferredExtent x ifTrue:[
	self width:helper preferredExtent x.
Transcript show:'w now: '; showCr:helper preferredExtent x
    ].
    helper verticalLayout:#fit.
    helper left:leftX asFloat;
	   right:rightX asFloat.

    "
     |dialog|

     dialog := Dialog new.
     dialog 
	addRow:#('a' 'b' 'c' 'd')
	fromX:0
	toX:1
	collect:[:label | Label label:label].

     dialog addOkButton.
     dialog open.
    "

    "
     |dialog|

     dialog := Dialog new.
     dialog 
	addRow:#('a1' 'b1' 'c1' 'd1')
	fromX:0
	toX:1 
	collect:[:label | Label label:label].

     dialog 
	addRow:#('a2' 'b2' 'c2' 'd2')
	fromX:0
	toX:0.5 
	collect:[:label | Label label:label].

     dialog 
	addRow:#('a3' 'b3' 'c3' 'd3')
	fromX:0.5
	toX:1 
	collect:[:label | Label label:label].

     dialog addOkButton.
     dialog open.
    "
!

makeTabable:aComponentOrSubcomponent
    "add a component (usually a subcomponent, of which the dialog
     does not know) to the list of tabable ones (i.e. those, that can be
     stepped through via FocusNext/FocusPrevious)"

    tabableElements isNil ifTrue:[
	tabableElements := OrderedCollection new
    ].
    tabableElements add:aComponentOrSubcomponent
!

addComponent:aComponent withHeight:height 
    "add a component with some given height and full width.
     Returns the component."

    self basicAddComponent:aComponent.
    aComponent height:height.
    aComponent origin:0.0@yPosition; 
	       width:1.0; 
	       leftInset:leftIndent;
	       rightInset:rightIndent.
    yPosition := yPosition + "aComponent" height + ViewSpacing.
    ^ aComponent
!

addComponent:aComponent withExtent:ext 
    "add a component with some given extent.
     Returns the component."

    |fullSize|

    self basicAddComponent:aComponent.
    fullSize := ext + (leftIndent + rightIndent @ 0).
    aComponent extent:fullSize.
    aComponent origin:0.0@yPosition; 
	       leftInset:leftIndent; 
	       rightInset:rightIndent.
    yPosition := yPosition + aComponent height + ViewSpacing.
    width := fullSize x max:width.
    ^ aComponent
!

addComponent:aComponent tabable:tabable tabbedComponent:subComponent
    "add a component with its preferred height and full width.
     Returns the component."

    tabable ifTrue:[
	tabableElements isNil ifTrue:[
	    tabableElements := OrderedCollection new
	].
	tabableElements add:subComponent
    ].
    ^ self addComponent:aComponent 
	   withHeight:(aComponent preferredExtent y).
!

addComponent:aComponent tabable:tabable
    "add a component with its preferred height and full width.
     Returns the component."

    ^ self addComponent:aComponent tabable:tabable tabbedComponent:aComponent 
!

addComponent:aComponent
    "add a component with its preferred height and full width.
     Returns the component."

    ^ self addComponent:aComponent tabable:false
!

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

    |l|

    l := Label new label:aString.
    self addComponent:l.
    ^ 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'.
     (b addTextLabel:'world') foregroundColor:Color red.
     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 tabable:tabable
    "create a checkBox with label on aModel and add it.
     Returns the box."

    |b|

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

addCheckBox:label on:aModel
    "create a checkBox with label on aModel and add it.
     Returns the box."

    ^ self addCheckBox:label on:aModel tabable:true
!

addPopUpListOn:aModel tabable:tabable
    "create a popUpList on aModel and add it.
     Returns the popUpList."

    ^ self addPopUpList:nil on:aModel tabable:tabable
!

addPopUpList:labelString on:aModel
    "create a popUpList with a label on aModel and add it.
     Returns the box."

    ^ self addPopUpList:labelString on:aModel tabable:true
!

addPopUpListOn:aModel
    "create a popUpList on aModel and add it.
     Returns the box."

    ^ self addPopUpList:nil on:aModel tabable:true
!

addPopUpList:labelString on:aModel tabable:tabable
    "create a popUpList on aModel and add it.
     Returns the popUpList."

    |p box l|

    p := PopUpList on:aModel.
    p resize; sizeFixed:true.
    labelString notNil ifTrue:[
	box := HorizontalPanelView new.
	box borderWidth:0; horizontalLayout:#rightSpace.
	box add:(l := Label label:labelString).
	l borderWidth:0.
	box add:p.
    ] ifFalse:[
	box := p.
    ].        
    self addComponent:box tabable:tabable tabbedComponent:p.
    ^ p
!

addInputField:aField tabable:tabable
    "add an already created input field; return the field.
     If tabable is true, the field is put into a group, to allow
     stepping through the fields with #NextField/#PreviousField keys.
     Returns the field."

    self addComponent:aField tabable:tabable.
    tabable ifTrue:[
	inputFieldGroup isNil ifTrue:[
	    inputFieldGroup := EnterFieldGroup new.
	    inputFieldGroup leaveAction:[self lastFieldLeft].
	    aField hasKeyboardFocus:true.
	].
	inputFieldGroup add:aField.
	self delegate:(KeyboardForwarder to:inputFieldGroup condition:#noFocus).
    ].
    ^ aField
!

addInputField:aField
    "add an already created input field; return the field.
     Returns the field."

    ^ self addInputField:aField tabable:true
!

addInputFieldOn:aModel tabable:tabable
    "create an input field on aModel and add it.
     Returns the field."

    |f|

    f := EditField new.
    f model:aModel.
    self addInputField:f tabable:tabable.
    ^ f
!

addInputFieldOn:aModel
    "create an input field on aModel and add it.
     Returns the field."

    ^ self addInputFieldOn:aModel tabable:true

    "
     |dialog model field|

     model := '' asValue.

     dialog := DialogBox new.
     dialog addTextLabel:'enter a string'.
     field := dialog addInputFieldOn:model.
     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "
!

addHorizontalLine
    "add a horizontal line as separator"

    self addComponent:(Separator new extent:1.0 @ 5).
!

addVerticalSpace
    "add a default vertical space (1 mm)"

    self addVerticalSpace:(ViewSpacing).
!

addVerticalSpace:nPixel
    "add some pixels of space to the next component"

    yPosition := yPosition + nPixel.
!

yPosition 
    "return the current y position (thats where the next component
     will be located)."

    ^ yPosition 
!

yPosition:aNumber 
    "set the current y position (thats where the next component
     will be located)."

    yPosition := aNumber.
!

leftIndent:aNumber 
    "set the left indent (current x position - thats where the next component
     will be located)."

    leftIndent := aNumber.
!

rightIndent:aNumber 
    "set the right indent"

    rightIndent := aNumber.
! !

!DialogBox methodsFor:'initialization'!

initialize
    |mm|

    super initialize.

    label := 'Dialog'.
    acceptValue := false asValue.

    mm := ViewSpacing.

    acceptReturnAsOK := true.
    acceptOnLeave := 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;
	horizontalLayout:#spread.

    yPosition := ViewSpacing.
    leftIndent := rightIndent := ViewSpacing.

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

focusSequence
    "return the elements through which we can step via 
     NextField/PreviousField keys.
     Here we return all tabable fields followed by all buttons in
     the panel."

    |fields buttons|

    tabableElements isNil ifTrue:[
	fields := #()
    ] ifFalse:[
	fields := tabableElements
    ].
    buttonPanel notNil ifTrue:[
	buttons := buttonPanel subViews.
	buttons notNil ifTrue:[
	    fields := fields , buttonPanel subViews
	]
    ].
    ^ fields
!

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

!DialogBox methodsFor:'queries'!

accepted
    "after the box has closed:
	 return true if accepted, false if canceled"

    ^ acceptValue value
!

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

preferredExtent 
    "return my preferred extent.
     That is the max component width, or my current width (default);
     whichever is larger, by the sum of the components heights."

    |w h p|

    addedComponents notNil ifTrue:[
	w := addedComponents 
		inject:0 
		into:[:max :element |
			|eExt|

			eExt := element preferredExtent x. "/ max:element extent x.
			max max:(eExt + element leftInset)].
    ] ifFalse:[
	w := super preferredExtent x.
    ].
    w := w max:width.
    h := yPosition
	 + ViewSpacing.

    buttonPanel subViews size ~~ 0 ifTrue:[
	p := buttonPanel preferredExtent.
	w := w max:p x.
	h := h
	     + p y
	     + ViewSpacing.
    ].

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

!DialogBox methodsFor:'private'!

realize
    "if any inputFields where added, activate the first one"

    inputFieldGroup notNil ifTrue:[
	inputFieldGroup activateFirst
    ].
    super realize
!

basicAddComponent:aComponent 
    "add a component, dont change its size"

    addedComponents isNil ifTrue:[
	addedComponents := OrderedCollection new.
    ].
    addedComponents add:aComponent.
    self addSubView:aComponent.
!

hideAndEvaluate:aBlock
    "if I am modal, make myself invisible and evaluate aBlock.
     If nonModal, stay up, but also evaluate the block."

    (windowGroup notNil and:[windowGroup isModal]) ifTrue:[
	self hide.
    ].
    aBlock notNil ifTrue:[aBlock value]

    "Modified: 5.9.1995 / 19:06:33 / claus"
! !

!DialogBox methodsFor:'accessing-elements'!

name:element as:name
    bindings isNil ifTrue:[
	bindings := IdentityDictionary new.
    ].
    bindings at:name put:element
!

componentAt:name
    bindings isNil ifTrue:[^ nil].
    ^ bindings at:name ifAbsent:nil
! !

!DialogBox methodsFor:'accessing-models'!

accept
    "return the valueHolder holding true when the box
     is accepted, false if closed via the windowManager or
     the cancel button.
     This is confusing: this method was originally called #acceptValue,
     but renamed for compatibility with ST-80.
     This looks like a bad name to me, since in most other situations, #accept
     is used to force an accept, not to return some valueHolder ...)."

    ^ acceptValue
! !

!DialogBox methodsFor:'accessing-behavior'!

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

    okAction := aBlock
!

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

    abortAction := 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
!

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

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

!DialogBox methodsFor:'accessing-components'!

okButton
    "return the okButton - this access is provided to allow
     setting the buttons look (for example: colors or font)"

    ^ okButton
!

abortButton
    "return the abortButton - this access is provided to allow
     setting the buttons look (for example: colors or font)"

    ^ abortButton
! !

!DialogBox methodsFor:'accessing'!

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

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