SimpleDialog.st
author Claus Gittinger <cg@exept.de>
Mon, 03 Mar 1997 22:30:05 +0100
changeset 481 02d1db5d428a
parent 476 628766c580c3
child 485 9326c85fdf6f
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1996 by eXept Software AG
              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.
"


ApplicationModel subclass:#SimpleDialog
	instanceVariableNames:'accept cancel close escapeIsCancel postBuildBlock postOpenBlock
		preBuildBlock'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Framework'
!

!SimpleDialog class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by eXept Software AG
              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
"
    Since many ST-80 classes are subclasses of SompleDialog, this class
    is provided here to allow easier porting of ST-80 code.

    It does not (currently) provide much functionality and is NOT
    compatible to the corresponding ST80 class; therefore, manual
    changes have to be made to get those applications to run under ST/X.
    (but at least, this enables you to fileIn that code and have a superclass
     for them)

    However, as time goes by, ST/X applications may be converted to use the
    ApplicationModel / SimpleDialog framework as well.

    Notice: this class was implemented using protocol information
    from alpha testers and PD code - it may not be complete or compatible to
    the corresponding ST-80 class. If you encounter any incompatibilities,
    please forward a note to the ST/X team.


    [author:]
        Claus Gittinger

    [see also:]
        StandardSystemView
        WindowGroup DeviceWorkstation DialogBox
"

! !

!SimpleDialog methodsFor:'accessing'!

accept
    "return the value of the instance variable 'accept' (automatically generated)"

    ^ accept
!

bindings
    ^ builder bindings
!

cancel
    "return the value of the instance variable 'cancel' (automatically generated)"

    ^ cancel
!

closeChannel
    "return the value of the instance variable 'close' (automatically generated)"

    ^ close
!

escapeIsCancel
    "return the value of the instance variable 'escapeIsCancel' (automatically generated)"

    ^ escapeIsCancel!

escapeIsCancel:something
    "set the value of the instance variable 'escapeIsCancel' (automatically generated)"

    escapeIsCancel := something.!

postBuildBlock:something
    "set the value of the instance variable 'postBuildBlock' (automatically generated)"

    postBuildBlock := something.!

postOpenBlock:something
    "set the value of the instance variable 'postOpenBlock' (automatically generated)"

    postOpenBlock := something.!

preBuildBlock:something
    "set the value of the instance variable 'preBuildBlock' (automatically generated)"

    preBuildBlock := something.!

source:anApplication
    builder source:anApplication
! !

!SimpleDialog methodsFor:'accessing - window'!

minWidth:nPixels
    |w box |

    w := builder window width.
    builder window width:(w max:nPixels).

"/    box := builder window displayBox.
"/    box width: (box width max: nPixels).
"/    builder window displayBox: box

    "Modified: 3.3.1997 / 21:56:27 / cg"
! !

!SimpleDialog methodsFor:'adding - components'!

addGap:nPixels
    |h|

    h := builder window height.
    builder window height: h+nPixels

    "Modified: 3.3.1997 / 21:48:35 / cg"
!

addLabels:labels values:values default:defaultValue storeInto:result takeKeyboard:takeKeyboard equalize:eqBoolean 
    ^ self
        addLabels:labels
        values:values
        default:defaultValue
        storeInto:result
        takeKeyboard:takeKeyboard
        equalize:eqBoolean
        columns:9999

    "Modified: 3.3.1997 / 21:49:16 / cg"
!

addLabels:labels values:values default:defaultValue storeInto:result takeKeyboard:takeKeyboard equalize:eqBoolean columns:nColumns
    | num maxButtonWidth maxButtonHeight separation buttonWAs buttonWidth window box layout left top actualColumns actualRows |

    num := labels size.
    maxButtonWidth := 0.
    maxButtonHeight := 0.
    separation := 20.
    buttonWAs := OrderedCollection new.
    window := builder window.
    box := window displayBox.
    actualColumns := nColumns min: labels size.
    actualRows := num + actualColumns - 1 // actualColumns.

    layout := LayoutFrame new.
    layout leftFraction: 0.5; rightFraction: 0.5.
    builder newComposite.

    1 to: num do:
            [:index |
            | lbl val buttonSpec buttonW bExt |
            lbl := labels at: index.
            val := values at: index.
            (buttonSpec :=
                    ActionButtonSpec
                            model: (result == nil
                                            ifTrue: [val]
                                            ifFalse: [[result value: val. self close]])
                            label: lbl
                            layout: (0@0 extent: 1@1))
                    defaultable: (values includes: defaultValue);
                    isDefault: val == defaultValue.
            builder add: buttonSpec.
            buttonW := builder wrapper.
            (takeKeyboard and: [val == defaultValue])
                    ifTrue: [builder keyboardProcessor setActive: buttonW widget controller].
            maxButtonWidth := maxButtonWidth max: (bExt := buttonW preferredBounds extent) x.
            maxButtonHeight := maxButtonHeight max: bExt y.
            buttonWAs add: buttonW -> bExt].

    buttonWidth := eqBoolean
            ifTrue: [actualColumns * maxButtonWidth + ((actualColumns - 1) * separation)]
            ifFalse: [buttonWAs
                            inject: separation negated
                            into: [:x :assoc | x + assoc value x + separation]].

    layout topOffset: box height; bottomOffset: box height+(actualRows * maxButtonHeight).
    layout
            leftOffset: 0 - ((buttonWidth + 1) // 2);
            rightOffset: (buttonWidth + 1) // 2.
    builder endCompositeLayout: layout.
    left := 0.
    top := 0.
    1 to: num do:[:index |
        | bttnWA width |

        bttnWA := buttonWAs at: index.
        width := eqBoolean
                        ifTrue: [maxButtonWidth]
                        ifFalse: [bttnWA value x].
        bttnWA key newLayout:
                (Rectangle
                        left: left
                        right: left + width
                        top: top
                        bottom: top + maxButtonHeight).
        index \\ actualColumns = 0
                ifTrue:
                        [left := 0.
                        top := top + maxButtonHeight]
                ifFalse: [left := left + width + separation]
    ].

    self addGap: maxButtonHeight * actualRows.
    buttonWidth := buttonWidth + separation.
    self minWidth: buttonWidth.

    ^ builder wrapper

    "Created: 3.3.1997 / 17:22:49 / cg"
    "Modified: 3.3.1997 / 21:50:56 / cg"
! !

!SimpleDialog methodsFor:'alert dialogs'!

ask: messageString initialAnswer: aString 
	^self builder policy ask: messageString initialAnswer: aString!

caution: messageString initialAnswer: aBoolean 
	^self builder policy caution: messageString initialAnswer: aBoolean!

note: aMessageString
	^self builder policy note: aMessageString!

stop: messageString labels: labels values: values default: defaultValue 
	^self builder policy
		stop: messageString
		labels: labels
		values: values
		default: defaultValue! !

!SimpleDialog methodsFor:'events'!

closeAccept
    self requestForWindowClose ifTrue:[
        self closeWindow
    ]
!

closeCancel
    self requestForWindowClose ifTrue:[
        self closeWindow
    ]
!

closeWindow
    self closeChannel value:true.
    builder window hide
!

requestForWindowClose
    ^ true
! !

!SimpleDialog methodsFor:'initialization'!

initialize
    accept := false asValue.
    close := false asValue.
    cancel := false asValue.
    builder aspectAt:#accept put:accept.
    builder aspectAt:#close put:close.
    builder aspectAt:#cancel put:cancel.
    escapeIsCancel := true.
!

initializeBuilderFor:aView 
    aView notNil ifTrue:[
        builder window:aView.
    ]

    "Created: 3.3.1997 / 16:23:04 / cg"
!

initializeWindowFor:aView
    |v ext|

    (v := aView) isNil ifTrue:[
        v := ModalBox new.
    ].

    builder setupWindowFor:v.

    "Modified: 3.3.1997 / 20:39:46 / cg"
! !

!SimpleDialog methodsFor:'interface opening'!

allButOpenFrom:aSpec
    "create my views but do not open the main window"

    super allButOpenFrom:aSpec.
    self preOpen
!

openFor:anApplication interface:aSelector
    "open the dialog for some appModel from a given spec;
     Return true if accepted, false if canceled"

    ^ self openFor:anApplication interface:aSelector withBindings:nil

    "Modified: 28.2.1997 / 16:22:08 / cg"
!

openFor:anApplication interface:aSelector withBindings:bindings
    "open the dialog for some appModel from a given spec;
     the bindings argument may provide overwriting bindings for the
     dialog.
     Return true if accepted, false if canceled"

    builder addBindings:bindings.
    self source:anApplication.
    ^ self openFrom:(anApplication class interfaceSpecFor:aSelector)

    "Created: 28.2.1997 / 14:09:06 / cg"
    "Modified: 28.2.1997 / 16:22:00 / cg"
!

openFrom:anInterfaceSpec
    "open the dialog from a given spec;
     return true if accepted, false if canceled"

    self allButOpenFrom:anInterfaceSpec.
    self openDialog.
    ^ accept value

    "Modified: 28.2.1997 / 16:40:36 / cg"
!

preOpen
    accept onChangeSend:#closeAccept to:self.
    cancel onChangeSend:#closeCancel to:self.

! !

!SimpleDialog methodsFor:'queries'!

defaultWindowType
    "SimpleDialogs come up modal, by default"

    ^ #dialog

    "Modified: 14.2.1997 / 22:17:20 / cg"
! !

!SimpleDialog class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/SimpleDialog.st,v 1.9 1997-03-03 21:30:05 cg Exp $'
! !