FramedBox.st
author claus
Thu, 07 Sep 1995 14:46:28 +0200
changeset 155 d6f3836d2b51
parent 139 7dd008efa3d8
child 174 d80a6cc3f9b2
permissions -rw-r--r--
.

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

'From Smalltalk/X, Version:2.10.5 on 9-may-1995 at 12:04:53 pm'!

SimpleView subclass:#FramedBox
	 instanceVariableNames:'label labelPosition fgColor showFrame frame3D
				horizontalSpace'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Layout'
!

FramedBox comment:'
COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/FramedBox.st,v 1.15 1995-09-07 12:44:58 claus Exp $
'!

!FramedBox 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/FramedBox.st,v 1.15 1995-09-07 12:44:58 claus Exp $
"
!

documentation
"
    a frame around something. The frame may have a label, whose position
    is controlled by the labelPosition variable, a symbol which may be one of:
    [#topCenter #topLeft #topRight #bottomLeft #bottomCenter #bottomRight]

    The default labelPosition is controlled by the styleSheet variable:
    'framedBoxLabelPosition' (usually, #topCenter).

    Its also possible, to not show the frame but only the label, by setting
    showFrame to false.
"
!

examples 
"
    simple:

	|top frame1 frame2 frame3|

	top := StandardSystemView new.
	top extent:300@200.

	frame1 := FramedBox origin:0.0@0.0 corner:0.5@0.5 in:top.
	frame1 label:'frame1'.

	frame2 := FramedBox origin:0.5@0.0 corner:1.0@0.5 in:top.
	frame2 label:'frame2'.

	frame3 := FramedBox origin:0.0@0.5 corner:1.0@1.0 in:top.
	frame3 label:'frame3'.

	top open


    placing something inside:

	|top frame1 frame2 frame3 v1 v2 v3|

	top := StandardSystemView new.
	top extent:300@200.

	frame1 := FramedBox origin:0.0@0.0 corner:0.5@0.5 in:top.
	frame1 label:'frame1'.
	v1 := View origin:0.0@0.0 corner:1.0@1.0 in:frame1.
	v1 viewBackground:(Color yellow);
	   level:1.

	frame2 := FramedBox origin:0.5@0.0 corner:1.0@0.5 in:top.
	frame2 label:'frame2'.
	v2 := View origin:0.0@0.0 corner:1.0@1.0 in:frame2.
	v2 viewBackground:(Color red);
	   level:1.

	frame3 := FramedBox origin:0.0@0.5 corner:1.0@1.0 in:top.
	frame3 label:'frame3'.
	v3 := View origin:0.0@0.0 corner:1.0@1.0 in:frame3.
	v3 viewBackground:(Color green);
	   level:1.

	top open


    placing something inside a frame in a dialog:

	|box panel frame1 frame2 frame3 v1 v1b v2 v3|

	box := Dialog new.

	frame1 := FramedBox label:'frame1'.
	panel := HorizontalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame1.
	v1 := View extent:100@100 in:panel.
	v1 viewBackground:(Color red);
	   level:1.
	v1b := View extent:100@100 in:panel.
	v1b viewBackground:(Color yellow);
	    level:1.

	box addComponent:frame1.

	frame2 := FramedBox label:'frame2'.
	v2 := View origin:0.0@0.0 corner:1.0@1.0 in:frame2.
	v2 viewBackground:(Color green);
	   level:1.
	box addComponent:frame2.

	frame3 := FramedBox label:'frame3'.
	v3 := View origin:0.0@0.0 corner:1.0@1.0 in:frame3.
	v3 viewBackground:(Color blue);
	   level:1.
	box addComponent:frame3.

	box addOkButton.
	box open


    placing something inside a frame in a dialog:

	|box panel frame1 frame2 frame3 v1 v1b v2 v3|

	box := Dialog new.

	frame1 := FramedBox label:'frame1'.
	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:frame1.
	v1 := View extent:100@100 in:panel.
	v1 viewBackground:(Color red);
	   level:1.
	v1b := View extent:100@100 in:panel.
	v1b viewBackground:(Color yellow);
	    level:1.

	box addComponent:frame1.

	frame2 := FramedBox label:'frame2'.
	v2 := View origin:0.0@0.0 corner:1.0@1.0 in:frame2.
	v2 viewBackground:(Color green);
	   level:1.
	box addComponent:frame2.

	frame3 := FramedBox label:'frame3'.
	v3 := View origin:0.0@0.0 corner:1.0@1.0 in:frame3.
	v3 viewBackground:(Color blue);
	   level:1.
	box addComponent:frame3.

	box addOkButton.
	box open
"
! !

!FramedBox methodsFor:'drawing'!

drawFrame
    "redraw the frame"

    |halfSepX halfSepY w h|

    "
     if there is no label, give more real estate to the inside
    "
    label isNil ifTrue:[
	halfSepX := halfSepY := 2
    ] ifFalse:[
	halfSepX := halfSepY := font height // 2.
    ].
    horizontalSpace notNil ifTrue:[
	halfSepX := horizontalSpace.
    ].

    w := width - halfSepX - halfSepX.
    h := height - halfSepY - halfSepY.

    frame3D ifFalse:[
	self displayRectangleX:halfSepX 
			     y:halfSepY
			 width:w 
			height:h.
	^ self
    ].

    w := w + 1.
    h := h + 1.

    self paint:shadowColor.
    self displayRectangleX:halfSepX-1 
			 y:halfSepY-1
		     width:w 
		    height:h.

    self paint:lightColor.
    self displayRectangleX:halfSepX 
			 y:halfSepY
		     width:w
		    height:h
!

redraw
    "redraw the frame and name if present"

    |labelLen l x y|

    label isNil ifTrue:[
	labelLen := 0
    ] ifFalse:[
	l := ' ' , label , ' '.
	labelLen := font widthOf:l
    ].

    showFrame ifTrue:[
	self drawFrame.
    ].

    labelLen > 0 ifTrue:[
	labelLen < width ifTrue:[
	    (labelPosition == #topLeft 
	    or:[labelPosition == #topCenter
	    or:[labelPosition == #topRight]]) ifTrue:[
		"
		 label at top
		"
		y := font ascent.
	    ] ifFalse:[
		"
		 label at bottom
		"
		y := height - font descent.
	    ].
	    (labelPosition == #topLeft
	    or:[labelPosition == #bottomLeft]) ifTrue:[
		"
		 label at left
		"
		x := font height
	    ] ifFalse:[
		(labelPosition == #topRight
		or:[labelPosition == #bottomRight]) ifTrue:[
		    "
		     label at right
		    "
		    x := width - labelLen - font height
		] ifFalse:[
		    "
		     label at center
		    "
		    x := (width - labelLen) // 2
		]
	    ].
	    self paint:fgColor on:viewBackground.
	    self displayOpaqueString:l x:x y:y
	]
    ]
! !

!FramedBox methodsFor:'queries'!

viewRectangle
    "return the inside area 
     - redefined to save frame from relative computations."

    |m2 sep|

    sep := font height.
    m2 := sep + sep.

    showFrame ifFalse:[
	^ (0 @ sep) extent:(width @ (height - m2))
    ].
    ^ (sep @ sep) extent:((width - m2) @ (height - m2))

"/    |m2 sepH sepV|
"/
"/    sepV := font height.
"/
"/    showFrame ifFalse:[
"/        ^ (0 @ sepV) extent:(width @ (height - sepV - sepV))
"/    ].
"/    sepH := sepV // 2.
"/    ^ (sepH @ sepH) extent:((width - sepH - sepH) @ (height - sepV - sepV))
!

preferredExtent
    "redefined to add space for the frame to the default extent" 

    |m2 sep|

    sep := font height.
    m2 := sep + sep.

    showFrame ifFalse:[
	^ super preferredExtent + (0 @ m2)
    ].
    ^ super preferredExtent+(m2 @ m2)
! !

!FramedBox methodsFor:'private'!

redrawIfShown
    shown ifTrue:[
	self clear.
	self redraw
    ]
! !

!FramedBox methodsFor:'accessing'!

label:aString
    "set the frames labelstring"

    (label ~= aString) ifTrue:[
	aString isEmpty ifTrue:[
	    label := nil
	] ifFalse:[
	    label := aString.
	].
	self redrawIfShown
    ]

    "Modified: 5.9.1995 / 17:20:05 / claus"
!

foregroundColor
    "return the frame labels foreground color"

    ^ fgColor
!

foregroundColor:aColor
    "set the frame labels foreground color"

    aColor ~= fgColor ifTrue:[
	fgColor := aColor.
	self redrawIfShown
    ]
!

frameShown
    "return true, if frame is shown;
     if false, oly the label is shown.
     OBSOLETE; use #showFrame."

    ^ showFrame
!

showFrame
    "return if the view shows its frame.
     If false, only the label is drawn"

    ^ showFrame

    "Modified: 5.9.1995 / 17:21:37 / claus"
!

showFrame:aBoolean
    "turn on/off showing of the frame -
     without a frame, only the label is shown at its position"

    aBoolean ~~ showFrame ifTrue:[
	showFrame := aBoolean.
	self redrawIfShown
    ]
!

label
    "return the frames labelstring"

    ^ label
!

font:aFont
    "set the frame labelstrings font"

    (font ~= aFont) ifTrue:[
	super font:aFont.
	self redrawIfShown
    ]
!

labelPosition
    "return the labelPosition, which is a symbol describing
     the labels position."

    ^ labelPosition
!

labelPosition:aSymbol
    "define the position of the label;
     aSymbol may be one of: 
	#topLeft, #topCenter, #topRight;
	#bottomLeft, #bottomCenter or #bottomRight"

    labelPosition ~~ aSymbol ifTrue:[
	labelPosition := aSymbol.
	self redrawIfShown
    ]
!

horizontalSpace:aNumber 
    "set the number of pixels by which the frame is inset horizontally.
     The default, nil, lets the box compute the horizontal inset from the
     labels font height."

    horizontalSpace := aNumber
!

horizontalSpace
    "return the number of pixels by which the frame is inset horizontally.
     The default, nil, lets the box compute the horizontal inset from the
     labels font height."

    ^ horizontalSpace

    "Modified: 5.9.1995 / 17:24:21 / claus"
!

layout
    "OBSOLETE compatibility interface. Will vanish"

    self obsoleteMethodWarning:'use #labelPosition'.
    ^ labelPosition
!

layout:something
    "OBSOLETE compatibility interface. Will vanish.
     In the meantime, try to figure out what is meant ... a kludge"

    something isLayout ifTrue:[^ super layout:something].

    self obsoleteMethodWarning:'use #labelPosition:'.
    ^ self labelPosition:something

    "Modified: 31.8.1995 / 23:07:00 / claus"
! !

!FramedBox methodsFor:'initialization'!

initialize
    super initialize.
    showFrame := true
!

initStyle
    "default position is top-center, except for ms-windows, where
     the text is positioned at top-left"

    super initStyle.

    fgColor := StyleSheet at:'framedBoxForegroundColor' default:Black.
    labelPosition := StyleSheet at:'framedBoxLabelPosition' default:#topCenter.
    frame3D := StyleSheet at:'framedBox3DFrame' default:true.
    borderWidth := 0.
! !

!FramedBox methodsFor:'event handling'!

sizeChanged:how
    self redrawIfShown.
    super sizeChanged:how
! !