PopUpView.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Jan 1997 18:24:33 +0100
changeset 1263 f5af4e2abd71
parent 1174 6889dc61d701
child 1732 e6b92cfc32a7
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

    [author:]
        Claus Gittinger
"
! !

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

    |screen|

    screen := Screen current.
    ^ (screen width // 3) @ (screen height // 3)

    "Modified: 5.7.1996 / 13:55:08 / 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
    "set/clear the exclusive pointer flag;
     DANGER: if set, no interaction with other views is possible,
     while the popUp is active"

    exclusivePointer := aBoolean

    "Modified: 12.5.1996 / 22:02:52 / cg"
!

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

    "Modified: 3.5.1996 / 23:48:22 / stefan"
!

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
    "obsolete support for small configuration without threads.
     This is no longer used"

    haveControl := true.

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

    device dispatchFor:nil while:[haveControl]

    "Modified: 12.5.1996 / 22:03:52 / cg"
! !

!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
    "setup viewStyle specifics"

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

    "Modified: 22.1.1997 / 11:57:38 / cg"
!

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

releasePointer 
    "release the mouse pointer"

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

    "Modified: 12.5.1996 / 22:04:09 / cg"
! !

!PopUpView methodsFor:'private'!

regainControl
    "get exclusive access to pointer and keyboard"

    shown ifTrue:[
        device grabPointerInView:self. 
        device grabKeyboardInView:self.
    ].

    "Modified: 6.5.1996 / 22:33:39 / stefan"
    "Modified: 12.5.1996 / 22:04:42 / cg"
! !

!PopUpView methodsFor:'queries'!

isPopUpView
    "return true, since I want to come up without decoration 
     and popUp to top immediately."

    ^ true

    "Modified: 12.5.1996 / 21:57:51 / cg"
! !

!PopUpView methodsFor:'realize / unrealize'!

mapped
    "grab the pointer here, when visible (but not control is already lost). 
     If the grab fails, try again and unmap 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"
                'PopUpView [warning]: could not grab pointer' errorPrintCR.
                self unmap
            ]
        ].
        exclusivePointer ifFalse:[
            self releasePointer
        ].
        device grabKeyboardInView:self.
        self getKeyboardFocus
    ]

    "Modified: 3.5.1996 / 23:48:37 / stefan"
    "Modified: 10.1.1997 / 18:00:31 / cg"
!

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

restarted
    ^ self
!

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

    "Modified: 3.5.1996 / 23:46:06 / stefan"
! !

!PopUpView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/PopUpView.st,v 1.33 1997-01-22 17:24:12 cg Exp $'
! !