ShadowView.st
author Claus Gittinger <cg@exept.de>
Sat, 11 Nov 1995 16:54:10 +0100
changeset 219 9ff0660f447f
parent 157 891eff44c2e7
child 269 ea536bb319a6
permissions -rw-r--r--
uff - version methods changed to return stings

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

SimpleView subclass:#ShadowView
       instanceVariableNames:'myView shadowLength shadowClr imageUnderShadow'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Basic'
!

!ShadowView 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/libview/ShadowView.st,v 1.12 1995-11-11 15:51:59 cg Exp $'
!

documentation
"
    just to give PopUps and ModalBoxes a shadow. 
    If shadowClr is nil, the shadowView reads the screen-contents under 
    itself before realization, and uses a greyed version of these pixels
    for its background. If shadowClr is non-nil, that color is used
    as shadow (can be used for solid-black shadows).

    The instance variable myView is the view, for which the shadow is for.
"
! !

!ShadowView methodsFor:'initialization'!

initialize
    super initialize.
    borderWidth := 0.

    shadowClr := StyleSheet at:#shadowColor.

    "the length of the shadow from myView"
    shadowLength := (device pixelPerMillimeter * 1.0) rounded
!

realize
    "realize the shadowView some distance away from myView,
     get the pixels under the shadow from the screen"

    |root shW shH right bot kludge clr1 clr0 org blackIs0|

    myView notNil ifTrue:[
	self origin:(myView origin + (myView borderWidth * 2) + shadowLength) 
	     extent:(myView extent).

	shadowClr isNil ifTrue:[
	    "
	     get the pixels under the shadow 
	     (copy from root-view into the 'imageUnderShadow'-form)
	    "
	    imageUnderShadow := Form width:width height:height depth:device depth on:device.
	    imageUnderShadow initGC.
	    device setClipByChildren:false in:imageUnderShadow gcId.

	    shW := shadowLength x.
	    shH := shadowLength y.
	    right := width - shW.
	    bot := height - shH.

	    root := DisplayRootView new.

	    clr0 := Color colorId:0.
	    clr1 := Color colorId:1.

	    kludge := root device depth == 1.
	    blackIs0 := (root device blackpixel == 0).
	    (kludge and:[blackIs0]) ifTrue:[
		imageUnderShadow foreground:clr0  background:clr1.
	    ].

	    org := self origin.

	    imageUnderShadow copyFrom:root x:(org x + right) y:org y 
					 toX:right y:0 width:shW height:height.

	    imageUnderShadow copyFrom:root x:org x y:(org y + bot) 
					 toX:0 y:bot width:width height:shH.

	    "
	     grey out the image (by oring-in a grey pattern)
	     (sometimes we are lucky, and can do it with one raster-op)
	    "
	    (kludge and:[blackIs0]) ifFalse:[
		imageUnderShadow foreground:clr0 background:(Color colorId:-1).
		imageUnderShadow mask:(Form mediumGreyFormOn:device).
		imageUnderShadow function:#and.
		imageUnderShadow fillRectangleX:right y:0 width:shW height:height.
		imageUnderShadow fillRectangleX:0 y:bot width:width height:shH.

		blackIs0 ifFalse:[
		    imageUnderShadow foreground:(Color black on:device) background:clr0.
		    imageUnderShadow function:#or.
		    imageUnderShadow fillRectangleX:right y:0 width:shW height:height.
		    imageUnderShadow fillRectangleX:0 y:bot width:width height:shH.
		]
	    ] ifTrue:[
		imageUnderShadow foreground:clr1 background:clr0.
		imageUnderShadow mask:(Form mediumGreyFormOn:device).
		imageUnderShadow function:#or.
		imageUnderShadow fillRectangleX:right y:0 width:shW height:height.
		imageUnderShadow fillRectangleX:0 y:bot width:width height:shH.
	    ].
	].
	super realize.
	self raise
    ]
!

unrealize
    imageUnderShadow := nil.
    super unrealize.
!

create
    super create.
    self backingStore:false.
    self saveUnder:true
!

recreate
    shadowClr notNil ifTrue:[
	shadowClr := shadowClr on:device
    ].

    "the length of the shadow from myView"
    shadowLength := (device pixelPerMillimeter * 1.0) rounded.

    super recreate.
    self backingStore:false.
    self saveUnder:true
! !

!ShadowView methodsFor:'event handling'!

redraw
    "fill all of myself with black"

    |ws hs|

    shadowClr isNil ifTrue:[
	imageUnderShadow isNil ifTrue:[^ self].

"
	self foreground:(Color colorId:-1) background:(Color colorId:0).
	self function:#copy.
"
	ws := shadowLength x.
	hs := shadowLength y.
	self copyFrom:imageUnderShadow x:(width - ws) y:0 
				     toX:(width - ws) y:0 
				   width:ws height:height.
	self copyFrom:imageUnderShadow x:0 y:(height - hs) 
				     toX:0 y:(height - hs) 
				   width:width height:hs.

    ] ifFalse:[
	self paint:shadowClr.
	self fillRectangleX:(width - ws) y:0 width:ws height:height
    ]
! !

!ShadowView methodsFor:'accessing'!

shadowColor:aColor
    "to set the shadow color"

    shadowClr := aColor
!

for:aView
    "set the view I am for"

    myView := aView
!

isPopUpView
    ^ true
! !