OptionBox.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 01:50:10 +0100
changeset 193 6ccc226ce3a6
parent 188 04f5f20990ac
child 197 00927189c882
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1991 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:#OptionBox
	 instanceVariableNames:'formLabel textLabel buttonPanel buttons actions
				defaultButtonIndex'
	 classVariableNames:'WarnBitmap'
	 poolDictionaries:''
	 category:'Views-DialogBoxes'
!

!OptionBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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.
"
!

version
    ^ '$Header: /cvs/stx/stx/libwidg/OptionBox.st,v 1.22 1995-11-22 12:46:57 cg Exp $'
!

documentation
"
    OptionBoxes are like YesNoBoxes but with as many buttons as you like;
    this will finally be a superclass of WarnBox and YesNoBox - or maybe merged
    all into DialogBox..
    Use them for multiway questions.
    For a consistent user interface, the rightmost button is the default return
    button (i.e. pressing return in the box performs this buttons function).

    examples:

	|box|

	box := OptionBox title:'hello' numberOfOptions:4.
	box showAtPointer



	|box|
	box := OptionBox title:'hello' numberOfOptions:3.
	box buttonTitles:#('one' 'two' 'three').
	box showAtPointer


     performing an action:

	|box|
	box := OptionBox title:'hello' numberOfOptions:3.
	box buttonTitles:#('one' 'two' 'three').
	box action:[:which | Transcript show:'button ';
					show: which;
					showCr:' was pressed'].
	box showAtPointer


     returning a value:

	|what|
	what := OptionBox 
		      request:('text has not been accepted.\\Your modifications will be lost when continuing.') withCRs
		      label:' Attention'
		      form:(WarningBox iconBitmap)
		      buttonLabels:#('abort' 'accept' 'continue')
		      values:#(#abort #accept #continue).

	...
	someObject perform:what.
	...

    CAVEAT: this is a leftover - functionality will be merged into DialogBox
"
! !

!OptionBox class methodsFor:'easy startup '!

request:title label:label form:aForm buttonLabels:labels values:values 
    "create a new optionBox, open it modal and return the value of
     the corresponding values collection."

    ^ self request:title label:label form:aForm buttonLabels:labels values:values default:nil
!

request:title label:label form:aForm buttonLabels:labels values:values default:defaultValue
    "create a new optionBox, open it modal and return the value of
     the corresponding values collection."

    |box|

    box := OptionBox title:title numberOfOptions:(labels size).
    box buttonTitles:labels.
    box defaultButtonIndex:(values indexOf:defaultValue). 
    box action:[:n | ^ values at:n].
    box label:label; form:aForm.
    box showAtPointer.
    ^ defaultValue

    "
     OptionBox request:'please select'
	       label:'select any'
	       form:(WarningBox iconBitmap)
	       buttonLabels:#('one' 'two' 'three')
	       values:#(1 2 3)
	       default:3
    "
! !

!OptionBox class methodsFor:'instance creation'!

title:titleString numberOfOptions:nOptions
    "create a new optionBox with title, aTitleString and nOptions options"

    |box|

    box := (self basicNew) numberOfOptions:nOptions.
    box device:Screen current.
    box initialize.
    box title:titleString.
    ^ box
! !

!OptionBox methodsFor:'accessing'!

title:aString
    "set the boxes title"

    aString ~= textLabel label ifTrue:[
	textLabel label:aString withoutSeparators.
	textLabel forceResize.
	shown ifTrue:[self resize]
    ]
!

title:aString numberOfOptions:nOptions
    "set the boxes title and number of options"

    self title:aString.
    buttons grow:nOptions.
    actions grow:nOptions
!

formLabel
    "return the label-view which displays a bitmap"

    ^ formLabel
!

form:aFormOrImage
    "set the image shown in the label-view"

    formLabel form:aFormOrImage
!

numberOfOptions:nOptions
    "set the number of options"

    buttons := (OrderedCollection new:nOptions) grow:nOptions.
    actions := (OrderedCollection new:nOptions) grow:nOptions
!

numberOfOptions
    "return the number of options"

    ^ buttons size
!

buttons
    "return the buttons collection"

    ^ buttons
!

buttonTitles:titles
    "set the button titles"

    titles keysAndValuesDo:[:index :aString |
	|b|

	(b := buttons at:index) label:aString.
	b resize.
    ].
    shown ifTrue:[self resize]
!

actions:actionBlocks
    "define the actions"

    actions := actionBlocks
!

action:actionBlock
    "define a single the action for all buttons.
     The action will be evaluated with the button index as argument."

    buttons keysAndValuesDo:[:index :button |
	button action:[
		       button turnOffWithoutRedraw.
		       self hide.
		       actionBlock value:index
		      ]
    ].
!

buttonTitles:titles actions:actionBlocks
    "define both button titles and actions"

    self buttonTitles:titles.
    actions := actionBlocks.
!

defaultButtonIndex:index
    defaultButtonIndex notNil ifTrue:[
	(buttons at:defaultButtonIndex) isReturnButton:false
    ].
    (index notNil and:[index ~~ 0]) ifTrue:[
	defaultButtonIndex := index.
	defaultButtonIndex notNil ifTrue:[
	    (buttons at:defaultButtonIndex) isReturnButton:true 
	].
    ]
! !

!OptionBox methodsFor:'initializing'!

initialize
    |nButt|

    super initialize.

    formLabel := Label in:self.
    self initFormBitmap.
    formLabel borderWidth:0.
    formLabel origin:(ViewSpacing @ ViewSpacing).

    textLabel := Label label:'Select' in:self.
    textLabel borderWidth:0.
    textLabel origin:((ViewSpacing + formLabel width + ViewSpacing) @ ViewSpacing).

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

    nButt := buttons size.

    1 to:nButt do:[:index |
	|button|

	button := Button label:'press'.
	button action:[
		       |action|

		       (buttons at:index) turnOffWithoutRedraw.
		       self hide.
		       action := actions at:index.
		       action notNil ifTrue:[
			   action value
		       ]
		      ].
"/        index == nButt ifTrue:[
"/            button isReturnButton:true
"/        ].
	buttonPanel addSubView:button.
	buttons at:index put:button.
    ].

    "
     |box|

     box := OptionBox title:'hello' numberOfOptions:4.
     box open
    "
!

initFormBitmap
    WarnBitmap isNil ifTrue:[
	WarnBitmap := Form fromFile:'Warning.xbm' resolution:100 on:Display 
    ].
    formLabel form:WarnBitmap
!

focusSequence
    ^ buttons
! !

!OptionBox methodsFor:'events'!

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

    |action|

    defaultButtonIndex notNil ifTrue:[
	(aKey == #Return) ifTrue:[
	    self hide.
	    action := actions at:defaultButtonIndex.
	    action notNil ifTrue:[
		action value
	    ]
	]
    ].
    super keyPress:aKey x:x y:y
! !

!OptionBox methodsFor:'queries'!

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

    |idx butt|

    buttonPanel setChildPositionsIfChanged.
    idx := buttons findFirst:[:b | b isReturnButton].
    idx ~~ 0 ifTrue:[
	butt := buttons at:idx.
	^ (butt originRelativeTo:self) + (butt extent // 2)
    ].
    ^ self extent // 2
!

preferredExtent 
    "return a size to make everything fit into myself"

    |w w1 h maxH prefPanel|

    w1 := ViewSpacing + formLabel width + ViewSpacing + textLabel width + ViewSpacing.
    prefPanel := buttonPanel preferredExtent.
    w := w1 max:prefPanel x.

"/    maxH := 0.
"/    buttons do:[:button |
"/        maxH := maxH max:(button preferredExtent y)
"/    ].
    maxH := prefPanel y.

    h := ViewSpacing
	 + ((formLabel height) max:(textLabel height))
	 + ViewSpacing + ViewSpacing
	 + maxH
	 + ViewSpacing.

    ^ w @ h
! !