DialogBox.st
author Claus Gittinger <cg@exept.de>
Tue, 23 Apr 1996 17:17:11 +0200
changeset 573 3335fee474b5
parent 560 71479d7f20be
child 585 8f395aba0173
permissions -rw-r--r--
checkin from browser

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

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

!DialogBox class methodsFor:'documentation'!

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

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.
        In the future, those existing subclasses' functionality is going to
        be moved full into Dialog, and the subclasses will be replaced by dummy
        delegators. (They will be kept for backward compatibility, though).


    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.

        autoAccept       Boolean        if true, pressing ok (or return)
                                        sends #accept to all subcomponents.
                                        I.e. all subfields update their models
                                        first. The default is true.

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

examples
"
    historically, DialogBox was used as an abstract class as a base for InfoBox, 
    YesNoBox etc. However, the programmatic construction protocol (addComponent)
    now allows those classes to be easily replaced and future versions may
    do this and make those subclasses obsolete.

    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.


      asking for a password:

        |s|

        s := Dialog 
                requestPassword:'enter your secret, please:'.
        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
        ]


    validated password entry:

        |box firstEntry secondEntry|

        firstEntry := '' asValue.
        secondEntry := '' asValue.

        box := DialogBox new.
        (box addTextLabel:'Please enter your secret:') adjust:#left.
        (box addInputFieldOn:firstEntry) passwordCharacter:$*. 
        box addVerticalSpace.
        (box addInputFieldOn:secondEntry) passwordCharacter:$*. 
        box addAbortButton. 
        box addOkButton. 
        box open.
        box accepted ifTrue:[
            firstEntry value ~= secondEntry value ifTrue:[
                Transcript showCr:'wrong input - try again'
            ] ifFalse:[
                Transcript showCr:'entered: ', firstEntry 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.
        ]


    same, using an even better interface:

        |box values labels|

        values := #(true false false true) collect:[:val | val asValue].
        labels := #('check1' 'check2' 'check3' 'check4').

        box := Dialog new.

        box
           addColumn:(1 to:labels size)
           fromX:0.0
           toX:1.0 
           collect:[:index | CheckBox label:(labels at:index) model:(values at:index)]
           tabable:true.
        
        box addAbortButton; addOkButton.
        box open.

        box accepted ifTrue:[
           values with:labels do:[:val :lbl |
              Transcript show:(lbl , ': '); showCr:val 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.
            ]
        ]
"
!

inputFocus
"
    a DialogBox with multiple input fields can be configured on how it
    shall behave if the RETURN key is pressed. 

    The default is to shift the focus to the ok-button.
    This can be changed to automatic OK with:
        aBox focusToOKOnLeave:false

    Then, leaving the last field automatically accepts as if ok was pressed.
    (useful for simple - single entry dialogs).



    With: 
        aBox acceptReturnAsOK:false

    this any focusSHift or automatic OK is turned off, and the input group 
    switches its focus back to the topMost field. 
    The default for this is true.
    (useful, if you want an explicit ok from the user, or need all fields
     to be handled somehow).


    Simply leaving the group with a cursor movement may also be either
    interpreted as a return (the default),
    or again wrap back to the top of the group.
    with:
        aBox acceptOnLeave:false

    this is turned off and again, the focus is moved back to the topMost
    entry field. The default is true.
"
! !

!DialogBox class methodsFor:'class initialization'!

initialize
    self == DialogBox ifTrue:[
        Dialog := self
    ]

    "Created: 8.3.1996 / 21:18:54 / cg"
    "Modified: 10.4.1996 / 08:16:18 / cg"
! !

!DialogBox class methodsFor:'common dialogs'!

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

!DialogBox class methodsFor:'confirmation dialogs'!

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

    ^ self 
        confirm:aString
        title:nil
        yesLabel:nil
        noLabel:nil

"/    |box answer|
"/
"/    box := YesNoBox title:aString.
"/    box label:(self classResources string:'Confirm').
"/    box yesAction:[answer := true] noAction:[answer := false].
"/    box showAtPointer.
"/    box yesAction:nil noAction:nil.
"/    ^ answer

    " 
     Dialog confirm:'really ?' 

     Transcript showCr:(
        Dialog confirm:'are you certain ?'
     )
    "

    "Modified: 8.3.1996 / 21:16:54 / cg"
!

confirm:aString initialAnswer:what
    "launch a Dialog, which allows user to enter yes or no.
     return true for yes, false for no.
     InitialAnswer must be true or false and defines which button is to be
     the default (i.e. return-) button"

    |box answer|

    box := YesNoBox title:aString.
    box yesAction:[answer := true] noAction:[answer := false].
    what == false ifTrue:[
	box okButton isReturnButton:false.
	box acceptReturnAsOK:false.
	box noButton beReturnButton.
    ].
    box showAtPointer.
    box yesAction:nil noAction:nil.
    ^ answer

    " 
     Dialog confirm:'really ?' initialAnswer:false

     Transcript showCr:(
	Dialog confirm:'are you certain ?' initialAnswer:false
     )

     Transcript showCr:(
	Dialog confirm:'are you certain ?' initialAnswer:true 
     )
    "

    "Modified: 27.1.1996 / 14:24:39 / cg"
!

confirm:aString title:title yesLabel:yesText noLabel:noText
    "launch a Dialog, which allows user to enter yes or no.
     return true for yes, false for no.
     The yes/no buttons labels are defined by yesText/noText."

    |box answer|

    box := YesNoBox title:aString.
    yesText notNil ifTrue:[
        box yesLabel:yesText.
    ].
    noText notNil ifTrue:[
        box noLabel:noText.
    ].
    box yesAction:[answer := true] noAction:[answer := false].
    title notNil ifTrue:[
        box label:title
    ].
    box showAtPointer.
    box yesAction:nil noAction:nil.
    ^ answer

    " 
     Dialog 
        confirm:'really ?' 
        title:'fooBar'
        yesLabel:'oh well' 
        noLabel:'nope'
    "

    "Created: 21.2.1996 / 01:10:14 / cg"
    "Modified: 8.3.1996 / 21:15:56 / cg"
!

confirm:aString yesLabel:yesText noLabel:noText
    "launch a Dialog, which allows user to enter yes or no.
     return true for yes, false for no.
     The yes/no buttons labels are defined by yesText/noText."

    ^ self confirm:aString title:nil yesLabel:yesText noLabel:noText

    " 
     Dialog confirm:'really ?' yesLabel:'oh well' noLabel:'nope'
    "

    "Created: 21.2.1996 / 01:10:14 / cg"
    "Modified: 8.3.1996 / 21:15:06 / cg"
!

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

     Transcript showCr:(
	Dialog confirmWithCancel:'really ?'
     )
    "

    "Modified: 27.1.1996 / 14:25:49 / cg"
! !

!DialogBox class methodsFor:'defaults'!

defaultLabel
    "return the boxes default window title."

    ^ 'Dialog'

    "Created: 23.4.1996 / 17:13:10 / cg"
! !

!DialogBox class methodsFor:'file name dialogs'!

requestDirectoryName
    "same as requestFileName, but only show directories."

    ^ self
        requestDirectoryName:'directory ?' 

    "
     Dialog requestDirectoryName
    "

    "Created: 19.4.1996 / 14:29:48 / cg"
    "Modified: 19.4.1996 / 14:32:42 / cg"
!

requestDirectoryName:title
    "same as requestFileName, but only show directories."

    ^ self
        requestDirectoryName:title 
        default:nil
        ifFail:''

    "
     Dialog
        requestDirectoryName:'which directory ?' 
    "

    "Created: 19.4.1996 / 14:29:48 / cg"
    "Modified: 19.4.1996 / 14:32:02 / cg"
!

requestDirectoryName:title default:aFileName
    "same as requestFileName, but only show directories"

    ^ self
        requestDirectoryName:title 
        default:nil
        ifFail:''

    "
     Dialog
        requestDirectoryName:'which directory ?' 
        default:'/etc'
    "

    "Created: 19.4.1996 / 14:29:10 / cg"
    "Modified: 19.4.1996 / 14:31:52 / cg"
!

requestDirectoryName:title default:aFileName ifFail:failBlock
    "same as requestFileName, but only show directories"

    |fileBox|

    fileBox := FileSelectionBox
                    title:title
                    okText:'ok'
                    abortText:'cancel'
                    action:[:fileName | ^ fileName].

    fileBox initialText:aFileName.
    fileBox selectingDirectory:true.
    fileBox showAtPointer.
    ^ failBlock value

    "
     Dialog
        requestDirectoryName:'which directory ?' 
        default:'/etc'
        ifFail:'none'
    "

    "Created: 19.4.1996 / 14:31:04 / cg"
    "Modified: 19.4.1996 / 14:31:26 / cg"
!

requestFileName
    "launch a Dialog, which allows the user to enter a filename.
     Return the pathname string consisting of the full pathname of the filename,
     or an empty string (if cancel was pressed)."

    ^ self 
        requestFileName:'filename:' 

    "
     Dialog requestFileName
    "

    "Created: 27.1.1996 / 13:24:35 / cg"
    "Modified: 19.4.1996 / 13:49:28 / cg"
!

requestFileName:titleString
    "launch a Dialog, which allows user to enter a filename.
     Return the pathname string consisting of the full pathname of the filename,
     or an empty string (if cancel was pressed)."

    ^ self 
        requestFileName:titleString 
        default:'file.ext' 

    "
     Dialog requestFileName:'enter a fileName:' 
     Dialog requestFileName:'enter a fileName:' 
    "

    "Created: 27.1.1996 / 13:24:35 / cg"
    "Modified: 19.4.1996 / 13:53:17 / cg"
!

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

    "Modified: 19.4.1996 / 13:47:44 / cg"
!

requestFileName:titleString default:defaultName fromDirectory:aDirectoryPath
    "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:''
        fromDirectory:aDirectoryPath

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

    "Modified: 19.4.1996 / 14:27:31 / cg"
!

requestFileName:titleString default:defaultName ok:okText abort:abortText pattern:pattern
    "launch a Dialog, which allows user to enter a filename.
     The files presented initially are those from the current directory.
     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."

    ^ self 
        requestFileName:titleString 
        default:defaultName
        ok:okText 
        abort:abortText 
        pattern:pattern
        fromDirectory:nil

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

    "Modified: 19.4.1996 / 14:06:22 / cg"
!

requestFileName:titleString default:defaultName ok:okText abort:abortText pattern:pattern fromDirectory:aDirectoryPath
    "launch a Dialog, which allows user to enter a filename.
     The files presented initially are those in aDirectoryPath, or the
     current directory (if a nil path is given).
     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].

    aDirectoryPath notNil ifTrue:[box directory:aDirectoryPath].
    box pattern:pattern.
    box initialText:defaultName.
    box showAtPointer.
    box action:nil.
    ^ nil

    "
     Dialog 
        requestFileName:'enter a fileName:'
        default:''
        ok:'yeah' 
        abort:'oh, no' 
        pattern:'rc*'
        fromDirectory:'/etc'
    "

    "Modified: 19.4.1996 / 14:07:32 / cg"
!

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 allows validation of the files existance;
     it may be any of:
        #mustBeNew      - fail (return empty string) if the file exists
        #new            - confirm if the file exists
        #mustBeOld      - fail if the file does not exist
        #old            - confirm if the file does not exist
        #any (other)    - no validation
    "

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

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

     Dialog requestFileName:'enter a fileName:'
                        default:''
                        version:#mustBeNew 

     Dialog requestFileName:'enter a fileName:'
                        default:''
                        version:#new   
    "

    "Modified: 19.4.1996 / 13:53:58 / cg"
!

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 allows validation of the files existance;
     it may be any of:
        #mustBeNew      - fail (return empty string) if the file exists
        #new            - confirm if the file exists
        #mustBeOld      - fail if the file does not exist
        #old            - confirm if the file does not exist
        #any (other)    - no validation
    "

    ^ self
        requestFileName:titleString 
        default:defaultName 
        version:versionSymbol 
        ifFail:failBlock
        fromDirectory:nil

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

    "Modified: 19.4.1996 / 14:26:36 / cg"
!

requestFileName:titleString default:defaultName version:versionSymbol ifFail:failBlock fromDirectory:aDirectoryPath
    "launch a Dialog, which allows user to enter a filename.
     Return the string or the value of failBlock if cancel was pressed.
     The version argument allows validation of the files existance;
     it may be any of:
        #mustBeNew      - fail (return empty string) if the file exists
        #new            - confirm if the file exists
        #mustBeOld      - fail if the file does not exist
        #old            - confirm if the file does not exist
        #any (other)    - no validation
    "

    |box|

    box := FileSelectionBox title:titleString.
    aDirectoryPath notNil ifTrue:[box directory:aDirectoryPath].
    box initialText:defaultName.
    box action:[:name | 
        versionSymbol == #mustBeNew ifTrue:[
            "/ file may not exist
            name asFilename exists ifTrue:[^ ''].
        ].
        versionSymbol == #new ifTrue:[
            "/ file may not exist
            name asFilename exists ifTrue:[
                (self confirm:(ClassResources string:'''%1'' exists.\\Continue anyway ?' with:box fileName) withCRs)
                ifFalse:[^ ''].
            ].
        ].
        versionSymbol == #mustBeOld ifTrue:[
            name asFilename exists ifFalse:[^ ''].
        ].
        versionSymbol == #old ifTrue:[
            "/ file may not exist
            name asFilename exists ifFalse:[
                (self confirm:(ClassResources string:'''%1'' does not exist yet.\\Continue anyway ?' with:box fileName) withCRs)
                ifFalse:[^ ''].
            ].
        ].
        
        ^ name
    ].
    box showAtPointer.
    box action:nil.
    ^ failBlock value

    "
     Dialog 
        requestFileName:'enter a fileName:'
        default:''
        version:nil
        ifFail:['none']
        fromDirectory:'/etc'
    "
    "
     Dialog 
        requestFileName:'enter a fileName:'
        default:''
        version:#old 
        ifFail:['none']   
        fromDirectory:'/etc'
    "
    "
     Dialog 
        requestFileName:'enter a fileName:'
        default:''
        version:#mustBeNew 
        ifFail:['none']   
        fromDirectory:'/etc'
    "

    "Modified: 19.4.1996 / 14:25:15 / cg"
!

requestFileName:titleString ifFail:cancelBlock
    "launch a Dialog, which allows user to enter a filename.
     Return the pathname string consisting of the full pathname of the filename,
     or the value from evaluating cancelBlock (if cancel was pressed)."

    ^ self 
        requestFileName:titleString 
        default:'file.ext'
        version:nil
        ifFail:cancelBlock

    "
     Dialog requestFileName:'enter a fileName:' ifFail:['foo']
     Dialog requestFileName:'enter a fileName:' ifFail:[nil] 
    "

    "Modified: 19.4.1996 / 13:53:17 / cg"
    "Created: 19.4.1996 / 13:56:28 / cg"
!

requestNewFileName:titleString default:defaultName
    "launch a Dialog, which allows user to enter a filename.
     We expect a new files (i.e. nonexisting) name to be enterred,
     and confirm if it already exists.
     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:#new 
		    ifFail:''

    "
     Dialog requestNewFileName:'enter a fileName:' default:''  
    "

    "Modified: 27.1.1996 / 13:44:13 / cg"
! !

!DialogBox class methodsFor:'fill in the blank dialogs'!

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

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

    "
     Dialog 
	 request:'enter a string:' 
    "

    "Modified: 27.1.1996 / 14:44:30 / cg"
!

request:aString displayAt:aPoint centered:centered action:resultAction initialAnswer:initial
    "launch a Dialog, which allows user to enter a string.
     If aPoint is nonNil, the box is shown there, optionally centered.
     If it is nil, it is shown at the current pointer position or at the screen center.
     Return the string or an empty string (if cancel was pressed)"

    ^ self
	request:aString 
	displayAt:aPoint 
	centered:centered 
	action:resultAction 
	initialAnswer:initial
	onCancel:''

    "
     centered around 200@200:

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


     origin at 200@200:

	 Dialog 
	    request:'enter a string:'
	    displayAt:200@200
	    centered:false 
	    action:[:result | result printNewline]
	    initialAnswer:'the default'

     under mouse pointer:

	 Dialog 
	    request:'enter a string:'
	    displayAt:nil
	    centered:false 
	    action:[:result | result printNewline]
	    initialAnswer:'the default'

     centered on the screen:

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

    "Created: 7.12.1995 / 23:14:10 / cg"
    "Modified: 27.1.1996 / 14:44:08 / cg"
!

request:aString displayAt:aPoint centered:centered action:resultAction initialAnswer:initial onCancel:cancelValue
    "launch a Dialog, which allows user to enter a string.
     If aPoint is nonNil, the box is shown there, optionally centered.
     If it is nil, it is shown at the current pointer position or at the screen center.
     Return the string or the value of cancelValue (if cancel was pressed)"

    |box|

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

    "
     at topLeft (centering is suppressed, to make the box fully visible)    
	 Dialog 
	    request:'enter a string:'
	    displayAt:0@0
	    centered:true
	    action:[:result | result printNewline]
	    initialAnswer:'the default'
	    onCancel:#foo

     centered around 200@200:

	 Dialog 
	    request:'enter a string:'
	    displayAt:200@200
	    centered:true
	    action:[:result | result printNewline]
	    initialAnswer:'the default'
	    onCancel:#foo

     topLeft of box at 200@200:

	 Dialog 
	    request:'enter a string:'
	    displayAt:200@200
	    centered:false 
	    action:[:result | result printNewline]
	    initialAnswer:'the default'
	    onCancel:#foo

     under mouse pointer:

	 Dialog 
	    request:'enter a string:'
	    displayAt:nil
	    centered:false 
	    action:[:result | result printNewline]
	    initialAnswer:'the default'
	    onCancel:#foo

     centered on the screen:

	 Dialog 
	    request:'enter a string:'
	    displayAt:nil
	    centered:true 
	    action:[:result | result printNewline]
	    initialAnswer:'the default'
	    onCancel:#foo
    "

    "Created: 7.12.1995 / 23:14:10 / cg"
    "Modified: 27.1.1996 / 14:41:40 / cg"
!

request:aString displayAt:aPoint initialAnswer:initial
    "launch a Dialog, which allows user to enter something.
     The boxes topLeft is placed at aPoint, or under the mouse pointer (if aPoint is nil).
     Return the entered string (may be empty string) or nil (if cancel was pressed)"

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

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

    "Modified: 27.1.1996 / 14:45:47 / 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:false 
	action:nil 
	initialAnswer:initial

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

    "Modified: 27.1.1996 / 14:44:22 / cg"
!

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

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

    ^ cancelAction value

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

    "Modified: 27.1.1996 / 14:46:00 / cg"
!

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

    self 
	request:aString 
	displayAt:nil 
	centered:false 
	action:[:result | ^ result] 
	initialAnswer:''.

    ^ cancelAction value

    "
     Dialog 
	 request:'enter a string:'
	 onCancel:nil       
    "

    "Created: 27.1.1996 / 14:31:45 / cg"
    "Modified: 27.1.1996 / 14:46:10 / cg"
!

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

!DialogBox class methodsFor:'multiple choice dialogs'!

choose:aString fromList:list values:listValues buttons:buttonLabels values:buttonValues lines:maxLines cancel:cancelBlock
    "launch a Dialog showing the message and list.
     The user can select an item and click ok; in this case, the corresponding value
     from listValues is returned (doubleclick works as well). 
     The list may be suppressed (if the list arg is nil).
     Below the list, an optional row of buttons is shown, which can also be
     clicked upon, and a corresponding value from buttonValues is returned.
     If cancel is pressed, the value of cancelBlock is returned.
     Pressing ok without a selection is treated like cancel."

    |box listView panel answer idx|

    box := Dialog new.
    (box addTextLabel:aString) adjust:#left.

    list notNil ifTrue:[
        maxLines > list size ifTrue:[
            listView := ScrollableView for:SelectionInListView.
        ] ifFalse:[
            listView := SelectionInListView new.
            listView level:-1.
        ].
        listView list:list.
        listView doubleClickAction:[:line | box hide. ^ listValues at:line].
        box addComponent:listView indent:(ViewSpacing // 2) withHeight:(listView heightForLines:maxLines).
        box makeTabable:listView.
    ].

    buttonLabels notNil ifTrue:[
        panel := HorizontalPanelView new.
        panel horizontalLayout:#fitSpace.
        buttonLabels keysAndValuesDo:[:index :label |
            |b|

            b := Button label:label.
            b action:[box hide. ^ buttonValues at:index].
            panel add:b.
            box makeTabable:b.
        ].
        box addComponent:panel indent:0.  "/ panel has its own idea of indenting
    ].
    box addAbortButton.
    list notNil ifTrue:[box addOkButton].

    listView notNil ifTrue:[box stickAtBottomWithVariableHeight:listView].
    panel notNil ifTrue:[box stickAtBottomWithFixHeight:panel].

    box showAtPointer.
    box accepted ifTrue:[
        (answer := listView selection) notNil ifTrue:[
            ^ listValues at:answer
        ]
    ].
    ^ cancelBlock value

    "
     full example:

         Transcript showCr:(
             Dialog 
                choose:'choose any' 
                fromList:#('one' 'two' 'three' 'four') 
                values:#(1 2 3 4) 
                buttons:#('five' 'six' 'seven')
                values:#(5 6 7)
                lines:10 
                cancel:nil
         )


     no buttons:

         Transcript showCr:(
             Dialog 
                choose:'choose any' 
                fromList:#('one' 'two' 'three' 'four') 
                values:#(1 2 3 4) 
                buttons:nil
                values:nil
                lines:4
                cancel:nil
         )


     no list (lines argument is ignored):

         Transcript showCr:(
             Dialog 
                choose:'choose any' 
                fromList:nil
                values:nil
                buttons:#('one' 'two' 'three' 'four') 
                values:#(1 2 3 4) 
                lines:nil
                cancel:nil
         )


      full including cancel value:

         Transcript showCr:(
             Dialog 
                choose:'choose example' 
                fromList:#('one' 'two' 'three' 'four') 
                values:#(1 2 3 4) 
                buttons:#('five' 'six' 'seven')
                values:#(5 6 7)
                lines:4
                cancel:[Transcript flash. #aborted]
         )


     degenerated:

         Transcript showCr:(
             Dialog 
                choose:'choose any' 
                fromList:nil
                values:nil
                buttons:nil
                values:nil
                lines:nil 
                cancel:nil
         )


    "

    "Modified: 19.4.1996 / 19:02:39 / cg"
!

choose:aString fromList:list values:listValues lines:maxLines cancel:cancelBlock
    "launch a Dialog showing the message and list.
     The user can select an item and click ok; in this case, the corresponding value
     from listValues is returned (doubleclick works as well).
     If cancel is pressed, the value of cancelBlock is returned.
     Pressing ok without a selection is treated like cancel."

    ^ self
	choose:aString 
	fromList:list 
	values:listValues
	buttons:nil
	values:nil
	lines:maxLines
	cancel:cancelBlock

    "
     Transcript showCr:(
	 Dialog 
	    choose:'choose any' 
	    fromList:#('one' 'two' 'three' 'four') 
	    values:#(1 2 3 4) 
	    lines:4
	    cancel:nil
     )

     Transcript showCr:(
	 Dialog 
	    choose:'choose example' 
	    fromList:#('one' 'two' 'three' 'four') 
	    values:#(1 2 3 4) 
	    lines:4
	    cancel:[Transcript flash. #aborted]
     )
    "

    "Modified: 27.1.1996 / 14:17:07 / cg"
!

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.
     The default entries button is marked as a return button and entering
     return will choose that value.
     For a good userInterface style, we recommend this being the last
     entry (to make the right-most button the default button)."

    |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

    "no good style (default button is not the rightmost one)

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

     Dialog 
	choose:'choose any' 
	labels:#('cancel' 'foo' 'bar' 'baz') 
	values:#(nil foo bar baz) 
	default:#baz     

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

    "Modified: 27.1.1996 / 13:48:17 / cg"
! !

!DialogBox methodsFor:'accessing'!

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

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

!DialogBox methodsFor:'accessing-behavior'!

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

    abortAction := aBlock
!

acceptCheck:aBlock
    "if nonNil, the acceptCheck-block is evaluated when the dialog is
     accepted (ok-button or Return-key). If it returns true, the box is closed,
     otherwise not."

    acceptCheck := aBlock
!

acceptOnLeave:aBoolean
    "define the behavior when the last input field is left via cursor keys.
     The default is to accept & close the dialog (i.e. true)."

    acceptOnLeave := aBoolean.

    "Modified: 19.4.1996 / 17:05:12 / cg"
!

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

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

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
!

focusOnField:anInputField
    inputFieldGroup makeActive:anInputField







!

focusToOKOnLeave:aBoolean
    "define the behavior when the last input field is left via a return
     or cursor key.
     The default is to shift the focus to the OK button (i.e. true).
     If turned off, the OK is immediately performed, i.e.
     the dialog is accepted & closed."

    focusToOKOnLeave := aBoolean.

    "Modified: 19.4.1996 / 17:05:12 / cg"
    "Created: 19.4.1996 / 17:13:36 / cg"
!

hideOnAccept:aBoolean
    "control if the dialog should close when accepted.
     The default is true"

    hideOnAccept := aBoolean
!

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

    okAction := aBlock
! !

!DialogBox methodsFor:'accessing-components'!

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

    ^ abortButton
!

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

    ^ okButton
! !

!DialogBox methodsFor:'accessing-elements'!

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

inputFieldGroup
    ^ inputFieldGroup
!

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

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

acceptChannel:aValueHolder
    "set the valueHolder which is set to true when the box
     is accepted"

    acceptValue := aValueHolder
! !

!DialogBox methodsFor:'construction-adding'!

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
!

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

    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButtonLabelled:'get out of here'.
     dialog addOkButtonLabelled:'yes thats ok'.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 22:09:40 / cg"
!

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

    ^ self addButton:aButton after:nil

    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addButton:(Button label:'foo' action:[Transcript showCr:'foo']).
     dialog addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addButton:(Button label:'foo' action:[dialog hide. Transcript showCr:'foo']).
     dialog addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "
     |dialog|

     dialog := DialogBox new.
     dialog addButton:(Button label:'foo' action:[dialog hide. Transcript showCr:'foo']).
     dialog addAbortButton.
     dialog addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 22:14:17 / cg"
!

addButton:aButton after:someOtherButtonOrNil
    "add a button into 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
    ].
    needResize := true.
    ^ aButton

    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addOkButton.
     dialog addButton:(Button 
                        label:'foo' 
                        action:[dialog hide. Transcript showCr:'foo'])
                after:(dialog okButton).
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "
    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addOkButton.
     dialog addButton:(Button 
                        label:'foo' 
                        action:[dialog hide. Transcript showCr:'foo'])
                after:(dialog abortButton).
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "
    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addOkButton.
     dialog addButton:(Button 
                        label:'foo' 
                        action:[dialog hide. Transcript showCr:'foo'])
                after:nil.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 22:13:51 / cg"
!

addButton:aButton before:someOtherButtonOrNil
    "add a button into the buttonPanel.
     If the argument someOtherButtonOrNil is nil, the button is
     added upFront."

    |h|

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

    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addOkButton.
     dialog addButton:(Button 
                        label:'foo' 
                        action:[dialog hide. Transcript showCr:'foo'])
                before:(dialog okButton).
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "
    "
     |dialog|

     dialog := DialogBox new.
     dialog addAbortButton.
     dialog addOkButton.
     dialog addButton:(Button 
                        label:'foo' 
                        action:[dialog hide. Transcript showCr:'foo'])
                before:nil.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 22:13:51 / cg"
    "Created: 10.2.1996 / 16:04:35 / cg"
!

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

    ^ self addCheckBox:label on:aModel tabable:true

    "
     |dialog check|

     check := true asValue.

     dialog := DialogBox new.
     dialog addCheckBox:'on or off' on:check.
     dialog addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:check value].
    "

    "Modified: 9.2.1996 / 22:15:38 / cg"
!

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

    "
     |dialog check1 check2 check3|

     check1 := true asValue.
     check2 := false asValue.
     check3 := true asValue.

     dialog := DialogBox new.
     dialog addCheckBox:'on or off' on:check1 tabable:false.
     dialog addHorizontalLine.

     dialog addCheckBox:'on or off' on:check2 tabable:true.
     dialog addCheckBox:'on or off' on:check3 tabable:true.
     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 22:16:49 / cg"
!

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

    self 
        addColumn:aRow 
        fromX:leftX toX:rightX 
        collect:aBlock 
        tabable:false

    "
     |dialog|

     dialog := Dialog new.
     dialog 
        addColumn:#('label1' 'label2' 'lbl3' 'l4' 'label5')
        fromX:0.0
        toX:1.0
        collect:[:label | Label label:label].

     dialog addOkButton.
     dialog open.
    "

    "
     |dialog|

     dialog := Dialog new.
     dialog 
        addColumn:#('label1' 'label2' 'label3' 'label4' 'label5')
        fromX:0.25 
        toX:0.75
        collect:[:label | (Label label:label) adjust:#left].

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

    "Modified: 9.2.1996 / 22:22:12 / cg"
!

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

    self 
        addColumn:aRow 
        fromX:leftX toX:rightX 
        collect:aBlock 
        tabable:tabable 
        horizontalLayout:#fitSpace 

    "
     |dialog y values|

     values := (1 to:4) collect:[:dummy | '' asValue].

     dialog := Dialog new.
     y := dialog yPosition.
     dialog 
        addColumn:#('one' 'two' 'three' 'four')
        fromX:0
        toX:0.3 
        collect:[:label | Label label:label].

     dialog yPosition:y.
     dialog 
        addColumn:values
        fromX:0.3
        toX:1.0 
        collect:[:value | EditField on:value]
        tabable:true.

     dialog addOkButton.
     dialog open.

     dialog accepted ifTrue:[
        Transcript showCr:(values collect:[:holder | holder value])
     ]
    "

    "
     |dialog y values|

     values := #(true true false false false true false true) collect:[:val | val asValue].

     dialog := Dialog new.
     y := dialog yPosition.
     dialog 
        addColumn:(1 to:4)
        fromX:0
        toX:0.5 
        collect:[:idx | CheckToggle on:(values at:idx)]
        tabable:true
        horizontalLayout:#center.

     dialog yPosition:y.
     dialog 
        addColumn:(5 to:8) 
        fromX:0.5 
        toX:1.0 
        collect:[:idx | CheckToggle on:(values at:idx)]
        tabable:true
        horizontalLayout:#center.

     dialog addOkButton.
     dialog open.

     dialog accepted ifTrue:[
        Transcript showCr:(values collect:[:holder | holder value])
     ]
    "

    "Created: 9.2.1996 / 21:51:47 / cg"
    "Modified: 9.2.1996 / 22:22:02 / cg"
!

addColumn:aRow fromX:leftX toX:rightX collect:aBlock tabable:tabable horizontalLayout:hLayout
    "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.
        tabable ifTrue:[self makeTabable: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 horizontalLayout:hLayout.
    helper left:leftX asFloat;
           right:rightX asFloat;
           leftInset:leftIndent;
           rightInset:rightIndent.

    "
     |dialog y values|

     values := (1 to:4) collect:[:dummy | '' asValue].

     dialog := Dialog new.
     y := dialog yPosition.
     dialog 
        addColumn:#('one' 'two' 'three' 'four')
        fromX:0
        toX:0.3 
        collect:[:label | Label label:label].

     dialog yPosition:y.
     dialog 
        addColumn:values
        fromX:0.3
        toX:1.0 
        collect:[:value | EditField on:value]
        tabable:true.

     dialog addOkButton.
     dialog open.

     dialog accepted ifTrue:[
        Transcript showCr:(values collect:[:holder | holder value])
     ]
    "

    "
     |dialog y values|

     values := #(true true false false false true false true) collect:[:val | val asValue].

     dialog := Dialog new.
     y := dialog yPosition.
     dialog 
        addColumn:(1 to:4)
        fromX:0
        toX:0.5 
        collect:[:idx | CheckToggle on:(values at:idx)].

     dialog yPosition:y.
     dialog 
        addColumn:(5 to:8) 
        fromX:0.5 
        toX:1.0 
        collect:[:idx | CheckToggle on:(values at:idx)]
        tabable:true.

     dialog addOkButton.
     dialog open.

     dialog accepted ifTrue:[
        Transcript showCr:(values collect:[:holder | holder value])
     ]
    "

    "Modified: 9.2.1996 / 22:02:22 / cg"
    "Created: 9.2.1996 / 22:20:31 / cg"
!

addComboBoxOn:aModel
    "create a comboBoxView on aModel and add it.
     Returns the comboBoxView."

    ^ self addComboBoxOn:aModel tabable:true

    "
     without a list, the comboBox is disabled:

     |box val|

     val := 'some input' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboBoxOn:val).
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "with a list, it can be pulled:

     |box val|

     val := '' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboBoxOn:val) list:#('one' 'two' 'three' 'four').
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "Modified: 28.2.1996 / 15:17:39 / cg"
    "Created: 4.3.1996 / 17:21:45 / cg"
!

addComboBoxOn:aModel tabable:tabable
    "create a comboBoxView on aModel and add it.
     Returns the comboBoxView."

    |f|

    f := ComboBoxView new.
    f model:aModel.
    self addComponent:f tabable:tabable.
    tabable ifTrue:[
        self addToInputFieldGroup:f editor.
    ].
    ^ f

    "
     without a list, the comboBox is disabled:

     |box val|

     val := 'some input' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboBoxOn:val tabable:true).
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "with a list, it can be pulled:

     |box val|

     val := '' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboBoxOn:val tabable:true) list:#('one' 'two' 'three' 'four').
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "Modified: 4.3.1996 / 17:21:57 / cg"
!

addComboListOn:aModel
    "create a comboListView on aModel and add it.
     Returns the comboListView."

    ^ self addComboListOn:aModel tabable:true 

    "without a list, the comboList is disabled:

     |box val|

     val := 'some input' asValue.

     box := Dialog new.

     (box addTextLabel:'combo list example') adjust:#left.
     box addVerticalSpace.
     (box addComboListOn:val).
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "with a list, it can be pulled:

     |box val|

     val := '' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboListOn:val) list:#('one' 'two' 'three' 'four').
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "Created: 28.2.1996 / 15:16:34 / cg"
    "Modified: 4.3.1996 / 17:22:59 / cg"
!

addComboListOn:aModel tabable:tabable
    "create a comboListView on aModel and add it.
     Returns the comboListView."

    |f|

    f := ComboListView new.
    f model:aModel.
    self addComponent:f tabable:tabable.
    ^ f

    "without a list, the comboList is disabled:

     |box val|

     val := 'some input' asValue.

     box := Dialog new.

     (box addTextLabel:'combo list example') adjust:#left.
     box addVerticalSpace.
     (box addComboListOn:val tabable:true).
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "with a list, it can be pulled:

     |box val|

     val := '' asValue.

     box := Dialog new.

     (box addTextLabel:'combo box example') adjust:#left.
     box addVerticalSpace.
     (box addComboListOn:val tabable:true) list:#('one' 'two' 'three' 'four').
     box addOkButton.
     box open.
     box accepted ifTrue:[
        Transcript showCr:val value
     ].
    "

    "Created: 28.2.1996 / 15:16:34 / cg"
    "Modified: 4.3.1996 / 17:23:38 / cg"
!

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

    ^ self addComponent:aComponent indent:nil tabable:false

    "Modified: 9.2.1996 / 22:22:41 / cg"
!

addComponent:aComponent indent:indent
    "add any component with its preferred height and full width.
     The indent is temporarily changed to indent.
     Returns the component."

    ^ self addComponent:aComponent indent:indent tabable:false

    "Modified: 9.2.1996 / 22:22:44 / cg"
!

addComponent:aComponent indent:indent tabable:tabable
    "add any component with its preferred height and full width.
     The indent is temporarily changed to indent.
     Returns the component."

    |oldLeft oldRight result|

    oldLeft := leftIndent.
    oldRight := rightIndent.
    indent notNil ifTrue:[
        leftIndent := rightIndent := indent.
    ].
    result := self addComponent:aComponent tabable:tabable tabbedComponent:aComponent.
    leftIndent := oldLeft.
    rightIndent := oldRight.
    ^ result

    "Modified: 9.2.1996 / 22:22:50 / cg"
!

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

    |fullSize lI rI|

    indent isNil ifTrue:[
        lI := leftIndent.
        rI := rightIndent.
    ] ifFalse:[
        lI := rI := indent
    ].

    self basicAddComponent:aComponent.
    fullSize := ext + (lI + rI @ 0).
    aComponent extent:fullSize.
    aComponent origin:0.0@yPosition; 
               leftInset:lI; 
               rightInset:rI.
    yPosition := yPosition + aComponent height + ViewSpacing.
    width := fullSize x max:width.
    needResize := true.
    ^ aComponent

    "Modified: 9.2.1996 / 22:22:54 / cg"
!

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

    |lI rI|

    indent isNil ifTrue:[
        lI := leftIndent.
        rI := rightIndent.
    ] ifFalse:[
        lI := rI := indent
    ].
    self basicAddComponent:aComponent.
    aComponent height:height.
    aComponent origin:0.0@yPosition; 
               width:1.0; 
               leftInset:lI;
               rightInset:rI.
    yPosition := yPosition + "aComponent" height + ViewSpacing.
    needResize := true.
    ^ aComponent

    "Modified: 9.2.1996 / 22:22:58 / cg"
!

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

    ^ self addComponent:aComponent tabable:tabable tabbedComponent:aComponent

    "Modified: 9.2.1996 / 22:23:04 / cg"
!

addComponent:aComponent tabable:tabable tabbedComponent:subComponent
    "add any 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).

    "Modified: 9.2.1996 / 22:23:07 / cg"
!

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

    ^ self addComponent:aComponent indent:nil withExtent:ext

    "Modified: 9.2.1996 / 22:23:11 / cg"
!

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

    ^ self addComponent:aComponent indent:nil withHeight:height

    "Modified: 9.2.1996 / 22:23:15 / cg"
!

addFilenameInputFieldOn:aModel in:aDirectory tabable:tabable
    "create a fileName input field on aModel and add it.
     Returns the field. This is much like a normal input field,
     but supports filename completion."

    |f|

    f := FilenameEditField new.
    aDirectory notNil ifTrue:[f directory:aDirectory].
    f model:aModel.
    self addInputField:f tabable:tabable.
    ^ f
!

addHelpButtonFor:pathToHelpText 
    "add a help button to the buttonPanel.
     The argument, pathToHelpText should specify the path to the help
     text under either the doc/online/<language> or the help/<language>
     directory."

    |helpButton|

    helpButton := Button label:(resources string:'help').
    helpButton action:[
        self withWaitCursorDo:[XtHTML openFullOnHelpFile:pathToHelpText]].
    ^ self addButton:helpButton before:nil.

    "Created: 17.9.1995 / 20:17:26 / claus"
    "Modified: 10.2.1996 / 16:47:23 / cg"
!

addHorizontalLine
    "add a horizontal line as separator"

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

    "
     |dialog|

     dialog := DialogBox new.
     dialog 
        addTextLabel:'some title string';
        addHorizontalLine;
        addTextLabel:'more text';
        addOkButton;
        open.
    "

    "
     |dialog|

     dialog := DialogBox new.
     dialog 
        addTextLabel:'some title string';
        addHorizontalLine;
        addTextLabel:'more text'.
     (dialog addHorizontalLine) width:20.
     dialog addTextLabel:'more text'.
     (dialog addHorizontalLine) width:20.
     dialog 
        addTextLabel:'more text';
        addHorizontalLine;
        addOkButton;
        open.
    "

    "Modified: 19.4.1996 / 15:11:30 / cg"
!

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

    ^ self addInputField:aField tabable:true

    "Modified: 9.2.1996 / 20:46:16 / cg"
!

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

    self addComponent:aField tabable:tabable.
    tabable ifTrue:[
        self addToInputFieldGroup:aField.
    ].
    ^ aField

    "Modified: 9.2.1996 / 20:47:28 / cg"
!

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') adjust:#left.

     field := dialog addInputFieldOn:model.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "

    "Modified: 9.2.1996 / 21:34:14 / cg"
!

addInputFieldOn:aModel tabable:tabable
    "create an input field on aModel and add it.
     If tabable is false, the field cannot be tabbed into
     and return does not close the box.
     (pointer must be moved into it).
     Returns the field."

    |f|

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

    " a non-tabable field:

     |dialog model field|

     model := '' asValue.

     dialog := DialogBox new.
     (dialog addTextLabel:'enter a string') adjust:#left.

     field := dialog addInputFieldOn:model tabable:false.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "

    "Modified: 9.2.1996 / 21:36:16 / cg"
!

addLabelledField:aView label:labelString adjust:labelAdjust tabable:tabable separateAtX:relativeX
    "add a label and some view side-by-side.
     The labels goes from 0.0 to relativeX; the inputField from relativeX to 1.0.
     The labels string is defined by labelString and adjusted according to labelAdjust.
     The inputField gets model as its model.
     Return the inputField."

    |y lbl max|

    y := self yPosition.
    lbl := Label label:labelString.
    max := lbl preferredExtent y max:(aView preferredExtent y).

    self addComponent:lbl indent:leftIndent withHeight:max.
    lbl rightInset:0.
    lbl width:relativeX; adjust:labelAdjust; borderWidth:0.

    self yPosition:y.
    self addComponent:aView tabable:tabable.
    aView leftInset:ViewSpacing.
    aView width:(1.0 - relativeX); left:relativeX.

    aView isInputField ifTrue:[
        self addToInputFieldGroup:aView
    ].

    ^ aView

    "
     |dialog model field|

     model := '' asValue.

     dialog := DialogBox new.

     field := dialog 
                addLabelledField:(EditField on:model) label:'input here:' 
                adjust:#left 
                tabable:true 
                separateAtX:0.3.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "

    "
     |dialog model field|

     model := SelectionInList new.
     model list:#('foo' 'bar' 'baz').
     model selectionIndex:2.

     dialog := DialogBox new.

     field := dialog 
                addLabelledField:(PopUpList on:model) label:'select here:' 
                adjust:#left 
                tabable:true 
                separateAtX:0.3.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "

    "Created: 13.4.1996 / 13:41:31 / cg"
    "Modified: 19.4.1996 / 17:39:46 / cg"
!

addLabelledInputField:labelString adjust:labelAdjust on:model tabable:tabable separateAtX:relativeX
    "add a label and an inputField side-by-side.
     The labels goes from 0.0 to relativeX; the inputField from relativeX to 1.0.
     The labels string is defined by labelString and adjusted according to labelAdjust.
     The inputField gets model as its model.
     Return the inputField."


    ^ self 
        addLabelledField:(EditField on:model) label:labelString 
        adjust:labelAdjust
        tabable:tabable 
        separateAtX:relativeX.

    "
     |dialog model field|

     model := '' asValue.

     dialog := DialogBox new.

     field := dialog 
                addLabelledInputField:'enter a string' 
                adjust:#left 
                on:model 
                tabable:true 
                separateAtX:0.3.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:model value].
    "

    "
     |dialog model1 model2 field|

     model1 := '' asValue.
     model2 := '' asValue.

     dialog := DialogBox new.

     dialog addTextLabel:'a two-input box'.
     dialog addHorizontalLine.

     field := dialog 
                addLabelledInputField:'string1:' 
                adjust:#right 
                on:model1 
                tabable:true 
                separateAtX:0.4.

     field := dialog 
                addLabelledInputField:'string2:' 
                adjust:#right 
                on:model2 
                tabable:true 
                separateAtX:0.4.

     dialog addAbortButton; addOkButton.
     dialog open.
     dialog accepted ifTrue:[
        Transcript showCr:model1 value.
        Transcript showCr:model2 value.
     ].
    "

    "Created: 13.4.1996 / 13:41:31 / cg"
    "Modified: 19.4.1996 / 17:39:46 / cg"
!

addListBoxOn:aModel
    "add a selectionInListView to the box"

    ^ self 
        addListBoxOn:aModel 
        withNumberOfLines:nil 
        hScrollable:false 
        vScrollable:true. 

    "
     |dialog model listView|

     model := SelectionInList new.
     model list:#('one' 'two' 'three' 'four').
     model selectionIndex:2.

     dialog := DialogBox new.
     (dialog addTextLabel:'select any') adjust:#left.

     listView := dialog addListBoxOn:model.

     dialog addAbortButton; addOkButton.
     dialog open.

     dialog accepted ifTrue:[Transcript show:'selection is:'; showCr:model selection].
    "

    "Modified: 19.4.1996 / 13:05:42 / cg"
!

addListBoxOn:aModel class:aListViewClass
    "create & add an instance of aListViewClass to the box"

    ^ self 
        addListBoxOn:aModel
        class:aListViewClass
        withNumberOfLines:nil 
        hScrollable:false 
        vScrollable:true.

    "Created: 19.4.1996 / 13:06:14 / cg"
!

addListBoxOn:aModel class:aListViewClass withNumberOfLines:numLines
    "create and add an instance of aListViewClass to the box.
     The list has numLines (if nonNil) number of lines shown."

    ^ self 
        addListBoxOn:aModel
        class:aListViewClass
        withNumberOfLines:numLines 
        hScrollable:false 
        vScrollable:true.

    "Created: 19.4.1996 / 13:05:05 / cg"
!

addListBoxOn:aModel class:aListViewClass withNumberOfLines:numLines hScrollable:hs vScrollable:vs
    "add an instance ofaListViewClass selectionInListView to the box.
     The list has numLines (if nonNil) number of lines shown."

    |l scr h dH|

    l := aListViewClass new.
    l model:aModel.
    l doubleClickAction:[:name | self okPressed].

    vs ifTrue:[
        hs ifTrue:[
            scr := HVScrollableView forView:l miniScrollerH:true .
        ] ifFalse:[
            scr := ScrollableView forView:l
        ].
        scr resize.
        "/ Transcript show:scr height; show:' '; showCr:l height.
        dH := scr height - l height.
    ] ifFalse:[
        l level:-1.
        scr := l.
        dH := 0.
    ].

    numLines notNil ifTrue:[
        h := l heightForLines:numLines.
    ] ifFalse:[
        h := l preferredExtent y
    ].
    self addComponent:scr withHeight:(h + dH).
    ^ l

    "
     |dialog listView|

     dialog := DialogBox new.
     (dialog addTextLabel:'select any') adjust:#left.

     listView := dialog 
                        addListBoxOn:nil 
                        class:FileSelectionList
                        withNumberOfLines:10 
                        hScrollable:false 
                        vScrollable:false.

     listView directory:'/etc'.

     dialog addAbortButton; addOkButton.
     dialog open.

     dialog accepted ifTrue:[Transcript show:'selection is:'; showCr:listView selectionValue].
    "

    "Created: 22.2.1996 / 15:40:07 / cg"
    "Modified: 19.4.1996 / 13:08:55 / cg"
!

addListBoxOn:aModel withNumberOfLines:numLines
    "add a selectionInListView to the box.
     The list has numLines (if nonNil) number of lines shown."

    ^ self 
        addListBoxOn:aModel 
        withNumberOfLines:numLines 
        hScrollable:false 
        vScrollable:true. 

    "
     |dialog model listView|

     model := SelectionInList new.
     model list:#('one' 'two' 'three' 'four').
     model selectionIndex:2.

     dialog := DialogBox new.
     (dialog addTextLabel:'select any') adjust:#left.

     listView := dialog addListBoxOn:model withNumberOfLines:3.

     dialog addAbortButton; addOkButton.
     dialog open.

     dialog accepted ifTrue:[Transcript show:'selection is:'; showCr:model selection].
    "

    "Created: 22.2.1996 / 15:40:07 / cg"
    "Modified: 19.4.1996 / 13:04:34 / cg"
!

addListBoxOn:aModel withNumberOfLines:numLines hScrollable:hs vScrollable:vs
    "add a selectionInListView to the box.
     The list has numLines (if nonNil) number of lines shown."

    ^ self 
        addListBoxOn:aModel 
        class:SelectionInListView
        withNumberOfLines:numLines 
        hScrollable:hs 
        vScrollable:vs

    "
     |dialog model listView|

     model := SelectionInList new.
     model list:#('one' 'two' 'three' 'four').
     model selectionIndex:2.

     dialog := DialogBox new.
     (dialog addTextLabel:'select any') adjust:#left.

     listView := dialog addListBoxOn:model withNumberOfLines:3 hScrollable:true vScrollable:true.

     dialog addAbortButton; addOkButton.
     dialog open.

     dialog accepted ifTrue:[Transcript show:'selection is:'; showCr:model selection].
    "

    "
     |dialog model listView|

     model := SelectionInList new.
     model list:#('one' 'two' 'three' 'four').
     model selectionIndex:2.

     dialog := DialogBox new.
     (dialog addTextLabel:'select any') adjust:#left.

     listView := dialog addListBoxOn:model withNumberOfLines:3 hScrollable:false vScrollable:false.

     dialog addAbortButton; addOkButton.
     dialog open.

     dialog accepted ifTrue:[Transcript show:'selection is:'; showCr:model selection].
    "

    "Created: 22.2.1996 / 15:40:07 / cg"
    "Modified: 22.2.1996 / 15:41:25 / cg"
!

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

    "
     |dialog|

     dialog := DialogBox new.
     dialog addOkButton.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 21:37:02 / cg"
!

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.

    "
     |dialog b|

     b := Button label:((Image fromFile:'garfield.gif') magnifiedBy:0.5).

     dialog := DialogBox new.
     dialog addOkButton:b.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 17.9.1995 / 20:20:41 / claus"
    "Modified: 9.2.1996 / 21:38:48 / cg"
!

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.

    "
     |dialog|

     dialog := DialogBox new.
     dialog addOkButtonLabelled:'get out of here'.
     dialog open.
     dialog accepted ifTrue:[Transcript showCr:'yes'].
    "

    "Modified: 9.2.1996 / 21:39:34 / cg"
!

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
!

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
!

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

    ^ self addPopUpList:nil 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
!

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

    self 
        addRow:aCol 
        fromX:leftX toX:rightX 
        collect:aBlock 
        tabable:true 
        horizontalLayout:#spread 

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

    "Modified: 9.2.1996 / 22:25:16 / cg"
!

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

    self 
        addRow:aCol 
        fromX:leftX toX:rightX 
        collect:aBlock 
        tabable:tabable 
        horizontalLayout:#spread

    "Created: 9.2.1996 / 22:25:35 / cg"
!

addRow:aCol fromX:leftX toX:rightX collect:aBlock tabable:tabable horizontalLayout:hLayout
    "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.
        tabable ifTrue:[self makeTabable: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 horizontalLayout:hLayout.
    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]
        tabable:false
        horizontalLayout:#fit.

     dialog addOkButton.
     dialog open.
    "

    "
     |dialog|

     dialog := Dialog new.
     dialog 
        addRow:#('one' 'two' 'three' 'four')
        fromX:0
        toX:1
        collect:[:label | Button label:label]
        tabable:false
        horizontalLayout:#fit.

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

    "Created: 9.2.1996 / 22:24:31 / cg"
    "Modified: 9.2.1996 / 22:28:14 / cg"
!

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.
    l borderWidth:0.
    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
    "
!

addToInputFieldGroup:aComponentOrSubcomponent
    "add a component to the input group."

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

    "Created: 9.2.1996 / 20:23:04 / cg"
!

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

    self addVerticalSpace:(ViewSpacing).

    "
     |dialog|

     dialog := DialogBox new.
     dialog addTextLabel:'some title string'.
     dialog addVerticalSpace.
     dialog addTextLabel:'more text'.

     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 21:41:10 / cg"
!

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

    yPosition := yPosition + nPixel.
    needResize := true.

    "
     |dialog|

     dialog := DialogBox new.
     dialog addTextLabel:'some title string'.
     dialog addVerticalSpace:50.
     dialog addTextLabel:'more text'.

     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 21:41:23 / cg"
!

leftIndent
    "return the current indent 
     (current x position - thats where the next component will be located)."

    ^ leftIndent

    "Modified: 27.1.1996 / 18:21:31 / cg"
!

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

    leftIndent := aNumber.
    needResize := true.

    "
     |dialog|

     dialog := DialogBox new.
     (dialog addTextLabel:'label1') adjust:#left.
     dialog leftIndent:20.
     (dialog addTextLabel:'label2') adjust:#left.
     dialog leftIndent:40.
     (dialog addTextLabel:'label3') adjust:#left.
     dialog leftIndent:60.
     (dialog addTextLabel:'label4') adjust:#left.

     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 21:42:20 / cg"
!

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.

    (aComponentOrSubcomponent isInputField) ifTrue:[
        self addToInputFieldGroup:aComponentOrSubcomponent
    ].

    "Modified: 4.3.1996 / 11:34:29 / cg"
!

makeTabable:aComponentOrSubcomponent before:anotherComponent
    "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
    ].
    anotherComponent isNil ifTrue:[
        tabableElements addFirst:aComponentOrSubcomponent
    ] ifFalse:[
        tabableElements add:aComponentOrSubcomponent before:anotherComponent.
    ].

    (aComponentOrSubcomponent isInputField) ifTrue:[
        self addToInputFieldGroup:aComponentOrSubcomponent
    ].

    "Modified: 4.3.1996 / 11:33:54 / cg"
!

rightIndent
    "return the current right indent."

    ^ rightIndent

    "Modified: 27.1.1996 / 18:21:31 / cg"
!

rightIndent:aNumber 
    "set the right indent"

    rightIndent := aNumber.
    needResize := true.

    "
     |dialog|

     dialog := DialogBox new.
     (dialog addTextLabel:'label1') adjust:#right.
     dialog rightIndent:20.
     (dialog addTextLabel:'label2') adjust:#right.
     dialog rightIndent:40.
     (dialog addTextLabel:'label3') adjust:#right.
     dialog rightIndent:60.
     (dialog addTextLabel:'label4') adjust:#right.

     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 21:42:46 / cg"
!

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.
    needResize := true.

    "
     |dialog pos|

     dialog := DialogBox new.
     pos := dialog yPosition.
     (dialog addTextLabel:'label1') width:0.5.
     dialog yPosition:pos.
     (dialog addTextLabel:'label2') width:0.5; left:0.5.

     dialog addOkButton.
     dialog open.
    "

    "
     |dialog pos|

     dialog := DialogBox new.
     pos := dialog yPosition.
     #('one' 'two' 'three' 'four') 
     with:#(0.0 0.25 0.5 0.75) do:[:lbl :x |
         dialog yPosition:pos.
        (dialog addComponent:(Button label:lbl) tabable:true)
                width:0.25; left:x.
     ].

     dialog addOkButton.
     dialog open.
    "

    "Modified: 9.2.1996 / 21:46:40 / cg"
! !

!DialogBox methodsFor:'explicit focus control'!

focusOnOk
    windowGroup focusView:okButton

    "Modified: 19.4.1996 / 16:57:58 / cg"
! !

!DialogBox methodsFor:'initialization'!

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
!

initialize
    |mm|

    super initialize.

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

    mm := ViewSpacing.

    acceptReturnAsOK := true.
    acceptOnLeave := true.
    focusToOKOnLeave := true.
    hideOnAccept := true.
    autoAccept := 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 // 2).
    needResize := true.

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

    "Modified: 23.4.1996 / 17:13:18 / cg"
!

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

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

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

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

resize
    needResize ifTrue:[
	needResize := false.
	super resize
    ]

    "Created: 27.1.1996 / 17:22:33 / cg"
    "Modified: 27.1.1996 / 18:25:40 / cg"
! !

!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 prefX scale rel relX|

                        prefX := element preferredExtent x.

                        "/ special (for your convenience)
                        "/ if the element has been added with a relative width,
                        "/ scale it to get at least its preferred width

                        (rel := element relativeExtent) notNil ifTrue:[
                            relX := rel x.
                            (relX isNil or:[relX isInteger]) ifFalse:[
                                prefX := (prefX * (1 / relX)) rounded
                            ].
                        ].
                        eExt := prefX + (element borderWidth * 2). "/ max:element extent x.
                        max max:(eExt + element leftInset + element rightInset)].
    ] 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

    "Modified: 9.2.1996 / 19:44:46 / cg"
! !

!DialogBox methodsFor:'special geometry settings'!

stickAtBottomWithFixHeight:aComponent
    "arrange for a component to be positioned at a constant offset
     from the bottom of the box and its height to remain the same.
     This will keep the component at a constant distance from the bottom
     (without this setup, it would stay at a constant offset from the top)"

    self resize.

    aComponent
	topInset:(self height - aComponent top) negated;
	bottomInset:(self height - aComponent bottom); 
	origin:0.0 @ 1.0; corner:1.0 @ 1.0.

    "
     compare the resizing behavior of:

	|box|

	box := Dialog new.
	box addTextLabel:'hello'.
	box addTextLabel:'hello2'.
	box addOkButton.
	box show

     with:

	|box l2|

	box := Dialog new.
	box addTextLabel:'hello'.
	l2 := box addTextLabel:'hello2'.
	box addOkButton.
	box stickAtBottomWithFixHeight:l2.
	box show
   "

    "Created: 27.1.1996 / 17:17:41 / cg"
    "Modified: 27.1.1996 / 18:29:03 / cg"
!

stickAtBottomWithVariableHeight:aComponent
    "arrange for a component to be positioned at a constant offset
     from the bottom of the box and its height to be adjusted.
     This will resize the component for a constant distance from the top,
     and the bottom.
     (without this setup, its height would remain constant)"

    self resize.

    aComponent
	bottomInset:(self height - aComponent bottom); 
	corner:1.0@1.0.

    "
     compare the resizing behavior of:

	|box|

	box := Dialog new.
	box addTextLabel:'hello'.
	(box addComponent:(SelectionInListView new)) level:-1.
	box addOkButton.
	box show

     with:

	|box list|

	box := Dialog new.
	box addTextLabel:'hello'.
	list := (box addComponent:(SelectionInListView new)) level:-1.
	box addOkButton.
	box stickAtBottomWithVariableHeight:list.
	box show
   "

    "Modified: 27.1.1996 / 18:27:36 / cg"
! !

!DialogBox methodsFor:'user actions'!

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
!

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

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

    "Modified: 4.3.1996 / 12:14:56 / cg"
!

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

    <resource: #keyboard (#Return)>

    (aKey == #Return) ifTrue:[
        (okButton notNil and:[okButton isReturnButton]) ifTrue:[
            ^ self okPressed
        ].
        (abortButton notNil and:[abortButton isReturnButton]) ifTrue:[
            ^ self abortPressed
        ].
    ].
    super keyPress:aKey x:x y:y

    "Modified: 7.3.1996 / 13:15:09 / cg"
!

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

    acceptOnLeave ifTrue:[
        acceptReturnAsOK ifTrue:[
            focusToOKOnLeave ifTrue:[
                self focusOnOk.
                ^ self.
            ].
            self okPressed
        ]
    ].
    inputFieldGroup activateFirst

    "Modified: 19.4.1996 / 17:09:02 / cg"
!

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.

    acceptCheck notNil ifTrue:[
	acceptCheck value ifFalse:[^ self]
    ].

    hideOnAccept ifTrue:[
	"/ actually, only hides if I have been opened modal
	self hideAndEvaluate:okAction.
    ] ifFalse:[
	okAction value
    ]
! !

!DialogBox class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/DialogBox.st,v 1.65 1996-04-23 15:17:11 cg Exp $'
! !
DialogBox initialize!