SimpleDialog.st
author Claus Gittinger <cg@exept.de>
Wed, 08 Jul 1998 20:04:43 +0200
changeset 996 1e10d01c90b8
parent 978 cd056a68d67a
child 1053 0d77637f9d45
permissions -rw-r--r--
careful: ? is a binary selector.

"
 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 closeAllowedChannel'
	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 class methodsFor:'queries'!

isVisualStartable
    "returns whether this application class can be started via #open"

    self == SimpleDialog ifTrue:[^false].
    ^super isVisualStartable



! !

!SimpleDialog methodsFor:'Refactoring Browser'!

addMultiList: model lines: maxLines validation: valid

	| height layout field grid font scrollW max fullMax |

	height := builder window displayBox height.
	layout := LayoutFrame new.
	layout leftOffset: 16.
	layout rightFraction: 1 offset: -16.
	layout topOffset: height.
	field := SequenceViewSpec model: model menu: nil layout: layout.
	field multipleSelections: true.
	builder add: field.
	builder wrapper widget controller setDispatcher:
		(UIDispatcher new doubleClick: [valid value ifTrue: [accept value: true]]).
	"builder wrapper widget setValidTargetIndex: model selectionIndex."
	scrollW := builder wrapper decorator scrollerComponent.
	scrollW preferredBoundsBlock:
				[:sw | | rect |
				rect := sw component preferredBounds
						translatedBy: sw translation.
				rect height: maxLines*sw scrollGrid y.
				rect].

	font := builder wrapper widget textStyle defaultFont.
	font := Screen default defaultFontPolicy findFont: font.
	max := model list inject: 0 into: [:i :str | i max: str size].
		"Instead of exactly measuring every string, we
		assume that $o will be a fairly representative
		character.  Actually, $o will probably be wider
		than the average, but this will usually be OK."
	max := (font widthOf: $o) * max.

		"Don't let the dialog get too wide."
	fullMax := 350.
	max > fullMax
		ifTrue:
			[max := fullMax.
			builder wrapper decorator useHorizontalScrollBar.
			builder wrapper widget measureWidth: true].

	grid := builder wrapper preferredBounds height.
	layout bottomOffset: height+grid.
	self addGap: grid.
	self minWidth: max + 48.
	^builder wrapper!

chooseMultiple: messageString fromList: list values: listValues buttons: buttons values: buttonValues lines: maxLines cancel: cancelBlock 
	^self
		chooseMultiple: messageString
		fromList: list
		values: listValues
		buttons: buttons
		values: buttonValues
		lines: maxLines
		cancel: cancelBlock
		for: nil!

chooseMultiple: messageString fromList: list values: listValues buttons: buttons values: buttonValues lines: maxLines cancel: cancelBlock for: aVisualOrNil
	"Ask the user a question.  Let the user pick from a row of buttons made up
	to match the labels collection.  Return the response from the corresponding
	item from the values collection."

	"aVisualOrNil, if not nil, may be either a VisualPart or a
	ScheduledWindow.  It controls the look and feel and color choices
	used by the dialog, and supplies the dialog's master window, which
	is used by some window systems to create a visual connection between
	the dialog and the window that created it."

	"SimpleDialog new
		chooseMultiple: 'Which one do you want?'
		fromList: #('first' 'second' 'third' 'fourth') values: #(1 2 3 4)
		buttons: #() values: #()
		lines: 8
		cancel: [#noChoice]
		for: Dialog defaultParentWindow"

	| result spec okValue sequence wrappers listW |
	wrappers := OrderedCollection new.
	result := ValueHolder new.
	sequence := MultiSelectionInList new.
	sequence list: list.
	spec := (self class interfaceSpecFor: #emptySpec).
	okValue := Object new.
	self initializeBuilderFor: aVisualOrNil.
	builder add: spec window.
	builder add: spec component.
	self initializeWindowFor: aVisualOrNil.

	self setInitialGap.
	self addMessage: messageString centered: false.
	self addGap: 8.
	listW := self
			addMultiList: sequence
			lines: (maxLines min: list size+2)
			validation: [true].
	self addGap: 4.
	wrappers add: (self addOK: [sequence selectionIndex ~= 0]).
	buttons isEmpty
		ifFalse:
			[self addGap: 4.
			wrappers add: (self addDivider).
			self addGap: 4.
			wrappers add:
					(self addLabels: buttons
						values: buttonValues
						default: okValue
						storeInto: result
						takeKeyboard: true
						equalize: true)].
	self addGap: 6.
	self bottomAlignLowerEdge: listW.
	self bottomAlign: wrappers.

	self preOpen.
	builder openDialogWithExtent: builder window displayBox extent.
	^accept value
		ifTrue: [sequence selectionIndexes collect: [:each | listValues at: each]]
		ifFalse: [cancel value ifTrue: [cancelBlock value] ifFalse: [result value]]! !

!SimpleDialog methodsFor:'accessing'!

accept
    "return the valueholder which gets set by the accept button.
     Also, when this valueHolder gets a true stuffed into it, the
     dialog is closed."

    ^ accept

    "Modified: / 20.5.1998 / 20:51:05 / cg"
!

bindings
    "return my builders bindings"

    ^ builder bindings

    "Modified: / 20.5.1998 / 20:51:15 / cg"
!

cancel
    "return the valueholder which gets set by the cancel button.
     Also, when this valueHolder gets a true stuffed into it, the
     dialog is closed."

    ^ cancel

    "Modified: / 20.5.1998 / 20:51:02 / cg"
!

closeAllowedChannel
    "return the value-provider which controls if close is allowed.
     This is initialized to true."

    ^ closeAllowedChannel

    "Created: / 20.5.1998 / 21:52:32 / cg"
    "Modified: / 20.5.1998 / 21:53:18 / cg"
!

closeAllowedChannel:aValueHolderOrBlock
    "set a value-provider which controls if close is allowed."

    ^ closeAllowedChannel

    "Created: / 20.5.1998 / 21:52:53 / cg"
!

closeChannel
    "return the closeChannel; If a true is stuffed into this valueHolder,
     I will close myself."

    ^ close

    "Modified: / 20.5.1998 / 20:52:29 / cg"
!

escapeIsCancel
    "return the escapeIsCancel setting"

    ^ escapeIsCancel

    "Modified: / 20.5.1998 / 20:52:44 / cg"
!

escapeIsCancel:something
    "set/clear the escapeIsCancel option.
     If on, an ESC-key will be treated like a cancel action."

    escapeIsCancel := something.

    "Modified: / 20.5.1998 / 20:53:23 / cg"
!

postBuildBlock:something
    "set postBuildBlock; if non-nil, this is evaluated after the build process"

    postBuildBlock := something.

    "Modified: / 20.5.1998 / 20:54:06 / cg"
!

postOpenBlock:something
    "set the postBuildBlock; if non-nil, this is evaluated after the view is opened"

    postOpenBlock := something.

    "Modified: / 20.5.1998 / 20:54:23 / cg"
!

preBuildBlock:something
    "set the preBuildBlock; if non-nil, this is evaluated before the view is constructed"

    preBuildBlock := something.

    "Modified: / 20.5.1998 / 20:54:41 / cg"
!

source:anApplication
    "define the application which provides resources, aspects etc."

    builder source:anApplication

    "Modified: / 20.5.1998 / 20:55:07 / cg"
! !

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

closeAccept
    "accept was pressed. close the dialog"

    self requestForWindowClose ifTrue:[
        self closeWindow
    ]

    "Modified: 17.6.1997 / 14:10:23 / cg"
!

closeCancel
    "cancel was pressed. close the dialog"

    self requestForWindowClose ifTrue:[
        self closeWindow
    ]

    "Modified: 17.6.1997 / 14:10:29 / cg"
!

closeWindow
    "close the dialog"

    self closeChannel value:true.
    "/ must destroy - otherwise there is no #release to
    "/ the  controllers (onChangeSend-dependency problem)
    builder window destroy. "/ hide

    "Modified: 17.6.1997 / 14:10:38 / cg"
!

requestForWindowClose
    "the dialog is about to be closed - this method is ivoked and may
     return false to suppress the close.
     Here the value of closeAllowedChannel is returned, which is
     set to true initially.
     You may redefined this in a special dialog, and/or provide a boolden
     valueHolder or a boolean block via the #closeAllowedChannel: method."

    ^ closeAllowedChannel value

    "Modified: / 20.5.1998 / 21:52:25 / cg"
! !

!SimpleDialog methodsFor:'forced actions'!

doAccept
    "force accept"

    accept value:true

    "Created: / 18.10.1997 / 05:18:09 / cg"
    "Modified: / 20.5.1998 / 21:53:35 / cg"
!

doCancel
    "force cancel"

    cancel value:true

    "Created: / 18.10.1997 / 05:18:22 / cg"
    "Modified: / 20.5.1998 / 21:53:40 / cg"
! !

!SimpleDialog methodsFor:'initialization'!

initialize
    accept := (ValueHolder with:false).
    close := (ValueHolder with:false).
    cancel := (ValueHolder with:false).
    self createBuilder.
    builder aspectAt:#accept put:accept.
    builder aspectAt:#close put:close.
    builder aspectAt:#cancel put:cancel.
    escapeIsCancel := true.
    closeAllowedChannel := true

    "Modified: / 19.6.1998 / 03:35:48 / cg"
!

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

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

initializeWindowFor:aView
    |v|

    (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 specSymbol;
     the application must provide an interfaceSpec for that symbol.
     The bindings argument may provide overwriting bindings for the
     dialog.
     Return true if accepted, false if canceled"

    ^ self
        openFor:anApplication 
        interfaceSpec:(anApplication class interfaceSpecFor:aSelector)
        withBindings:bindings

    "Modified: 18.10.1997 / 04:43:13 / cg"
!

openFor:anApplication interfaceSpec:aSpec 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:aSpec

    "Modified: 28.2.1997 / 16:22:00 / cg"
    "Created: 18.10.1997 / 04:41:29 / cg"
!

openFor:anApplication spec:aSpec 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"

    ^ self
        openFor:anApplication 
        interfaceSpec:aSpec
        withBindings:bindings

    "Modified: / 18.10.1997 / 04:43:13 / cg"
    "Created: / 20.5.1998 / 20:28:29 / 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"
!

postBuildWith:aBuilder
    "this is sent after the dialogs widgets have been created
     (but before the dialog is opened).
     If a postBuildBlock was set, evaluate it here."

    postBuildBlock notNil ifTrue:[
        postBuildBlock numArgs == 0 ifTrue:[
            postBuildBlock value
        ] ifFalse:[
            postBuildBlock value:aBuilder
        ]
    ].
    super postBuildWith:aBuilder

    "Created: 18.10.1997 / 05:17:12 / cg"
!

postOpenWith:aBuilder
    "this is sent after the dialogs main window is opened.
     If a postOpenBlock was set, evaluate it here."

    postOpenBlock notNil ifTrue:[
        postOpenBlock numArgs == 0 ifTrue:[
            postOpenBlock value
        ] ifFalse:[
            postOpenBlock value:aBuilder
        ]
    ].
    super postOpenWith:aBuilder

    "Created: 18.10.1997 / 05:15:48 / cg"
!

preBuildWith:aBuilder
    "this is sent before the dialogs widgets are created.
     If a preBuildBlock was set, evaluate it here."

    preBuildBlock notNil ifTrue:[
        preBuildBlock numArgs == 0 ifTrue:[
            preBuildBlock value
        ] ifFalse:[
            preBuildBlock value:aBuilder
        ]
    ].
    super preBuildWith:aBuilder

    "Created: 18.10.1997 / 15:02:27 / cg"
!

preOpen
    "arrange for #closeAccept & #closeCancel to be invoked when
     either accept or close is triggered
     (usually the models of corresponding buttons)"

    accept onChangeSend:#closeAccept to:self.
    cancel onChangeSend:#closeCancel to:self.
    close  onChangeSend:#closeWindow to:self.

    "Modified: / 20.5.1998 / 20:49:26 / cg"
! !

!SimpleDialog methodsFor:'queries'!

defaultWindowType
    "SimpleDialogs come up modal, by default"

    ^ #dialog

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

!SimpleDialog methodsFor:'startup'!

openInterface:aSymbol
    "open a standard interface.
     Redefned to return the accept value instead of the builder."

    super openInterfaceModal:aSymbol.
    ^ accept value.

    "Created: / 23.1.1998 / 18:19:57 / cg"
    "Modified: / 20.5.1998 / 20:21:28 / cg"
!

openSpec:aWindowSpec
    "open a window spec.
     Redefned to open modal and to return the accept value instead 
     of the builder."

    super openSpecModal:aWindowSpec.
    ^ accept value.

    "Modified: / 22.4.1998 / 11:59:05 / cg"
    "Created: / 20.5.1998 / 20:21:17 / cg"
! !

!SimpleDialog class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/SimpleDialog.st,v 1.22 1998-06-19 01:36:40 cg Exp $'
! !