ShadowView.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 19:17:58 +0200
changeset 616 56cf67c82664
parent 274 30d54aac94a7
child 626 9f4a3aa6f8e2
permissions -rw-r--r--
documentation

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

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.

    [author:]
        Claus Gittinger
"
! !

!ShadowView methodsFor:'accessing'!

for:aView
    "set the view I am for"

    myView := aView
!

isPopUpView
    ^ true
!

shadowColor:aColor
    "to set the shadow color"

    shadowClr := aColor
! !

!ShadowView methodsFor:'event handling'!

redraw
    "fill all of myself with black"

    |ws hs|

    ws := shadowLength x.
    hs := shadowLength y.
    shadowClr isNil ifTrue:[
	imageUnderShadow isNil ifTrue:[^ self].

"
	self foreground:(Color colorId:-1) background:(Color colorId:0).
	self function:#copy.
"
	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:'initialization'!

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

initialize
    super initialize.
    borderWidth := 0.

    shadowClr := StyleSheet at:#popUpShadowColor.

    "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
    ]
!

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
!

unrealize
    imageUnderShadow := nil.
    super unrealize.
! !

!ShadowView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/ShadowView.st,v 1.15 1996-04-25 17:17:16 cg Exp $'
! !