YesNoBox.st
author claus
Thu, 17 Nov 1994 15:38:53 +0100
changeset 63 f4eaf04d1eaf
parent 59 450ce95a72a4
child 79 6d917a89f7b7
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 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.
"

WarningBox subclass:#YesNoBox
       instanceVariableNames:'noButton noAction'
       classVariableNames:'RequestBitmap'
       poolDictionaries:''
       category:'Views-DialogBoxes'
!

YesNoBox comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/YesNoBox.st,v 1.8 1994-11-17 14:38:51 claus Exp $
'!

!YesNoBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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/YesNoBox.st,v 1.8 1994-11-17 14:38:51 claus Exp $
"
!

documentation
"
    this class implements yes-no boxes by adding another (no-) Button to the WarnBox-View.
    They are created with:

	aBox := YesNoBox title:'some title'.
	aBox okAction:[ .. some action to be performed when ok is pressed ].

    and finally shown with:

	aBox showAtPointer

    The default box shows 'yes' and 'no' in its buttons; this can be changed with:

	aBox yesText:'some string'.
	aBox noText:'some string'.

    There is also protocol to set both button titles in one message.
    Also, the action associated to the noButton can be changed.

    For very simple yes/no queries, you can also use the much simpler confirm:.
    Since implemented in Object, everyone understands confirm. You can pass
    a question message (but not change the buttons labels).
    Use is:
	self confirm:'some question'  
    and will return true or false.
"
!

examples
"
    Examples:

	|aBox|

	aBox := YesNoBox title:'Coffee or tee ?'.
	aBox noText:'tee'.
	aBox yesText:'coffee'.
	aBox yesAction:[Transcript showCr:'make coffee'].
	aBox noAction:[Transcript showCr:'make tee'].
	aBox showAtPointer.

    or, shorter:

	|aBox|

	aBox := YesNoBox new.
	aBox title:'Coffee or Tee ?' 
	     yesAction:[Transcript showCr:'make coffee']
	     noAction:[Transcript showCr:'make tee'].
	aBox yesText:'Coffee' noText:'Tee'.
	aBox showAtPointer

    Also, have a look at the inherited protocol; for example, this allows changing
    the bitmap (default: a question mark) and other properties.

    If the box is needed to ask for a simple boolean, you can also use the
    #confirm method, to bring up a box, let it ask for something and return
    true or false. 
    Example:

	|box value|

	box := YesNoBox new.
	value := box confirm:'yes or no:'.
	value ifTrue:[
	    Transcript showCr:'yes'
	] ifFalse:[
	    Transcript showCr:'no'
	]

    of course, this can also be written shorter as:

	(YesNoBox new confirm:'yes or no:') ifTrue:[
	    Transcript showCr:'yes'
	] ifFalse:[
	    Transcript showCr:'no'
	]
"
! !

!YesNoBox class methodsFor:'styles'!

updateStyleCache
    |img|

    img := StyleSheet at:'requestBoxIcon'.
    img notNil ifTrue:[RequestBitmap := img asFormOn:Display].
! !

!YesNoBox class methodsFor:'icon bitmap'!

iconBitmap
    "return the bitmap shown as icon in my instances"

    RequestBitmap isNil ifTrue:[
	RequestBitmap := (Image fromFile:'bitmaps/Request.xbm') asFormOn:Display 
    ].
    ^ RequestBitmap
! !

!YesNoBox class methodsFor:'easy startup '!

XXconfirm:aTitle
    ^ self new confirm:aTitle
! !

!YesNoBox class methodsFor:'instance creation'!

title:t yesText:yesString noText:noString
    ^ (self new) title:t yesText:yesString noText:noString
! !

!YesNoBox methodsFor:'initialization'!

initialize
    super initialize.

    buttonPanel layout:#fit.  "/ looks better; should it come from the StyleSheet ?

    textLabel label:'please Confirm'.
    okButton label:(resources at:'yes').

    noButton := Button new.
    buttonPanel addSubView:noButton before:okButton.
    noButton label:(resources at:'no').
    noButton height:(okButton height).
    noButton action:[
		       noButton turnOffWithoutRedraw.
		       self noPressed
		    ].
    self resize.
! !

!YesNoBox methodsFor:'startup'!

confirm
    "open the receiver and return true for yes, false for no.
     This is an easier interface to use, since no action blocks
     have to be defined. The title is used as previously defined."

    self yesAction:[^ true] noAction:[^ false].
    self showAtPointer.
    self yesAction:nil noAction:nil. "/ clear actions for earlier release of context

    "
     YesNoBox new confirm
    "
!

confirm:aString
    "open the receiver and return true for yes, false for no.
     This is an easier interface to use, since no action blocks
     have to be defined."

    self title:aString.
    ^ self confirm

    "
     YesNoBox new confirm:'really ?'
    "
! !

!YesNoBox methodsFor:'accessing'!

yesButton
    "return the yes-button"

    ^ okButton
!

noButton
    "return the no-button"

    ^ noButton
!

yesAction:aBlock 
    "define the action to be performed when yes is pressed"

    okAction := aBlock
!

noAction:aBlock
    "define the action to be performed when no is pressed"

    noAction := aBlock
!

yesAction:yesBlock noAction:noBlock
    "define both actions"

    okAction := yesBlock.
    noAction := noBlock
!

yesText:aString
    "define the label of the yes-button"

    self okText:aString
!

noText:aString
    "define the label of the no-button"

    aString ~= noButton label ifTrue:[
	noButton label:aString.
	noButton resize.
	self resize
    ]
!

okText:yesString noText:noString
    "define the labels of both buttons - same as yesText:noText"

    ^ self yesText:yesString noText:noString
!

yesText:yesString noText:noString
    "define the labels of both buttons"

    ((yesString ~= okButton label) or:[noString ~= noButton label]) ifTrue:[
	okButton label:yesString.
	noButton label:noString.
	okButton resize.
	noButton resize.
	self resize
    ]
!

title:aString yesText:yesString noText:noString
    "define title and button labels"

    self title:aString.
    self yesText:yesString noText:noString
!

title:aString yesAction:yesBlock noAction:noBlock
    "define title and actions"

    self title:aString.
    okAction := yesBlock.
    noAction := noBlock
! !

!YesNoBox methodsFor:'user interaction'!

noPressed
    "user pressed the no-button;
     hide myself and evaluate the action"

    self hideAndEvaluate:noAction
! !

!YesNoBox methodsFor:'queries'!

preferedExtent 
    |w h max|

    "
     make the two buttons of equal size
    "
    max := okButton preferedExtent x max:noButton preferedExtent x.
    okButton width:max; fixSize.
    noButton width:max; fixSize.
    w := (formLabel width + textLabel width) max:max * 2.
    w := w + (3 * ViewSpacing) + (okButton borderWidth + noButton borderWidth * 2).
    h := ViewSpacing
	 + ((formLabel height) max:(textLabel height))
	 + (ViewSpacing * 3)
	 + okButton heightIncludingBorder
	 + ViewSpacing.

    ^ (w @ h).
! !