PopUpView.st
author Claus Gittinger <cg@exept.de>
Mon, 22 Apr 1996 23:41:34 +0200
changeset 587 c0fb8bc13596
parent 523 2de6065d37c8
child 616 56cf67c82664
permissions -rw-r--r--
commentary

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

TopView subclass:#PopUpView
	instanceVariableNames:'shadowView haveControl exclusivePointer mapTime'
	classVariableNames:'DefaultShadow DefaultLevel DefaultBorderWidth DefaultBorderColor'
	poolDictionaries:''
	category:'Views-Basic'
!

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

documentation
"
    this class implements an abstract superclass for all views which bypass the 
    window manager and pop up on top of the screen. A typical example is
    a PopUpMenu. PopUpView itself is abstract, providing basic mechanisms.
    They are not decorated by window managers.

    styleSheet parameters:

	popupShadow         <Boolean>           if true, popupViews show a shadow below
	popupLevel          <nil | Integer>     3D level
	popupBorderWidth    <nil | Integer>     borderWidth
"
! !

!PopUpView class methodsFor:'defaults'!

defaultExtent
    "return the default extent of my instances.
     The value returned here is usually ignored, and
     the value from preferredExtent taken instead."

    ^ (Display width // 3) @ (Display height // 3)

    "Modified: 22.4.1996 / 23:37:12 / cg"
!

shadows
    "return the shadows-flag. False means: turned off."

    ^ DefaultShadow
!

shadows:aBoolean
    "turn on/off shadows under popUpViews. 
     On slow displays, turning them off makes menus appear a bit snappier.
     The default is set via the styleSheet and changes when the viewStyle
     is changed."

    DefaultShadow := aBoolean
!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style (#popupShadow #popupLevel
                       #popupBorderWidth
                       #popupBorderColor)>

    ShadowView isNil ifTrue:[
        DefaultShadow := false
    ] ifFalse:[
        DefaultShadow := StyleSheet at:'popupShadow' default:false.
    ].
    DefaultLevel := StyleSheet at:'popupLevel'.
    DefaultBorderWidth := StyleSheet at:'popupBorderWidth'.
    DefaultBorderColor := StyleSheet colorAt:'popupBorderColor'.

    "Modified: 1.3.1996 / 13:45:26 / cg"
! !

!PopUpView methodsFor:'accessing'!

exclusivePointer:aBoolean
    exclusivePointer := aBoolean
!

noShadow
    "turn off the shadow"

    shadowView := nil
! !

!PopUpView methodsFor:'activation'!

hide
    "hide the view, leave its modal event loop"

    windowGroup notNil ifTrue:[
	windowGroup removeView:self.
	windowGroup := nil.
    ].
    self unrealize.
!

show
    "realize the view at its last position"

    self fixSize.
    self openModal:[true] "realize     "
!

showAt:aPoint
    "realize the view at aPoint"

    self showAt:aPoint resizing:true 
!

showAt:aPoint resizing:aBoolean
    "realize the view at aPoint"

    aBoolean ifTrue:[
	self fixSize.
    ].
    self origin:aPoint.
    self makeFullyVisible.
    self openModal:[true] "realize     "
!

showAtPointer
    "realize the view at the current pointer position"

    self showAt:(device pointerPosition) resizing:true
!

showCenteredIn:aView
    "make myself visible at the screen center."

    |top|

    top := aView topView.
    top raise.
    self showAt:(top origin 
		 + (aView originRelativeTo:top) 
		 + (aView extent // 2)
		 - (self extent // 2))
! !

!PopUpView methodsFor:'dispatching'!

modalLoop
    haveControl := true.

    "this is a kludge - we do not have multiple processes, therefore
     we start another dispatch loop, which exits when control is lost"

    device dispatchFor:nil while:[haveControl]
! !

!PopUpView methodsFor:'initialize / release'!

create
    super create.
    shadowView isNil ifTrue:[
	self saveUnder:true
    ]
!

destroy
    haveControl := false.
    super destroy.
    shadowView notNil ifTrue:[shadowView destroy. shadowView := nil]
!

initStyle
    super initStyle.

    styleSheet is3D == true ifTrue:[
	borderWidth := 0.
	level := 2
    ] ifFalse:[
	borderWidth := 1.
	level := 0
    ].

    DefaultBorderColor notNil ifTrue:[
	self borderColor:(DefaultBorderColor on:device).
    ].
    DefaultBorderWidth notNil ifTrue:[
	borderWidth := DefaultBorderWidth.
    ].
"/    DefaultEdgeStyle notNil ifTrue:[
"/        edgeStyle := DefaultEdgeStyle.
"/    ].
    DefaultLevel notNil ifTrue:[
	self level:DefaultLevel.
    ].

    DefaultShadow ifTrue:[
	shadowView := (ShadowView onDevice:device) for:self.
    ].
!

initialize
    super initialize.
    exclusivePointer := true.
    haveControl := false.
    type := #popup 
!

releasePointer 
    device activePointerGrab == self ifTrue:[
	device ungrabPointer.
    ].
! !

!PopUpView methodsFor:'private'!

leaveControl
    haveControl := false
!

regainControl
    device grabPointerInView:self. 
device grabKeyboardInView:self.

    "Modified: 1.3.1996 / 13:18:22 / cg"
!

takeControl
^ self.
    haveControl := true.

    "this is a kludge - we do not have multiple processes, therefore
     we start another dispatch loop, which exits when control is lost"

    device dispatchFor:drawableId while:[haveControl]
! !

!PopUpView methodsFor:'queries'!

isPopUpView
    ^ true
! !

!PopUpView methodsFor:'realize / unrealize'!

mapped
    "grab the pointer here, when visible (but not control is already lost). 
     If the grab fails, try again and unrealize myself if that fails too."

    mapTime := Time millisecondClockValue.

    super mapped.

    (haveControl 
    and:[true "/ exclusivePointer
    and:[realized]]) ifTrue:[
        (device grabPointerInView:self) ifFalse:[
            "wait a little bit and try again"
"/            'grab pointer failed' errorPrintNL.
            Delay waitForSeconds:0.1.
            (device grabPointerInView:self) ifFalse:[
                "give up"
                'could not grab pointer' errorPrintNL.
                self unrealize
            ]
        ].
        exclusivePointer ifFalse:[
            self releasePointer
        ].
device grabKeyboardInView:self.
        self getKeyboardFocus
    ]

    "Modified: 8.3.1996 / 13:40:26 / cg"
!

realize
    shadowView notNil ifTrue:[shadowView realize].
    self raise.
    haveControl := true.
    super realize.
!

restarted
    ^ self
!

unrealize
    haveControl := false.
    device activePointerGrab == self ifTrue:[
	device ungrabPointer.
    ].
    super unrealize.
    shadowView notNil ifTrue:[shadowView unrealize].
! !

!PopUpView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/PopUpView.st,v 1.26 1996-04-22 21:41:23 cg Exp $'
! !