TopView.st
author Claus Gittinger <cg@exept.de>
Tue, 22 Jul 2003 19:56:20 +0200
changeset 3916 5452ecf8d6ef
parent 3884 dc9ea4cfc963
child 3978 a7a7e5aa016d
permissions -rw-r--r--
map at old position (remap)

"
 COPYRIGHT (c) 1995 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.
"

"{ Package: 'stx:libview' }"

View subclass:#TopView
	instanceVariableNames:'type iconified keyboardProcessor'
	classVariableNames:'TakeFocusWhenMapped ForceModalBoxesToOpenAtCenter
		ForceModalBoxesToOpenAtPointer'
	poolDictionaries:''
	category:'Views-Basic'
!

!TopView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    I am an abstract superclass of StandardSystemView and PopUpView;
    i.e. views which have no superview.

    Do not get confused by the name TopView - your applications
    topViews are typically instances of StandardSystemView.

    [instance variables:]
	type		<Symbol>	one of #normal, #master, #slave or #partner
					for modeless views
					(#master, #slave or #partner link multiple views 
					into a windowManagers windowGroup -> de-iconification) 
					#dialog for modal views; #popup for popup views.

    [see also:]
        StandardSystemView PopUpView DialogBox 
        ( introduction to view programming :html: programming/viewintro.html )

    [author:]
        Claus Gittinger
"
! !

!TopView class methodsFor:'defaults'!

defaultExtent
    "return the default extent of my instances.
     Topviews extents is 2/3 of screen by default"

    |display|

    display := Screen current.
    display isNil ifTrue:[
        ^ 600 @ 400
    ].
    ^ display defaultExtentForTopViews
!

forceModalBoxesToOpenAtCenter
    "return the flag which forces all modal views to be opened 
     at the screens center"

    ^ ForceModalBoxesToOpenAtCenter ? false
!

forceModalBoxesToOpenAtCenter:aBoolean
    "set/clear a flag which forces all modal views to be opened
     at the screens center"

    ForceModalBoxesToOpenAtCenter := aBoolean

    "
     TopView forceModalBoxesToOpenAtCenter:true
     TopView forceModalBoxesToOpenAtCenter:false
    "
!

forceModalBoxesToOpenAtPointer
    "return the flag which forces all modal views to be opened 
     at the current pointer position"

    ^ ForceModalBoxesToOpenAtPointer ? false
!

forceModalBoxesToOpenAtPointer:aBoolean
    "set/clear the flag which forces all modal views to be opened 
     at the current pointer position"

    ForceModalBoxesToOpenAtPointer := aBoolean
! !

!TopView methodsFor:'Compatibility-ST80'!

displayBox
    ^ self bounds

    "Created: 3.3.1997 / 16:31:33 / cg"
!

displayBox:aRectangle
    self origin:aRectangle origin corner:aRectangle corner

    "Created: 3.3.1997 / 16:34:38 / cg"
! !

!TopView methodsFor:'accessing'!

keyboardProcessor
    "return my keyboard processor"

    ^ keyboardProcessor

    "Created: / 18.6.1998 / 18:52:42 / cg"
    "Modified: / 18.6.1998 / 20:00:18 / cg"
!

keyboardProcessor:something
    "set my keyboard processor"

    keyboardProcessor := something.

    "Created: / 18.6.1998 / 18:52:42 / cg"
    "Modified: / 18.6.1998 / 20:00:30 / cg"
! !

!TopView methodsFor:'accessing-behavior'!

beIndependent
    "make this an independent view; i.e. remove any master/slave or partner
     attribute (this is the default).
     However, the view remains in the current windowGroup"

    type := nil
!

beMaster
    "make this a master-view. All slave views within the same
     windowGroup will be closed if any master is closed."

    type := #master

    "
     see example in TopView>>beSlave
    "

    "Created: 10.12.1995 / 13:30:50 / cg"
!

bePartner
    "make this a partner-view. Each partner-view will automatically 
     close other partner views (within the same windowGroup) when closed."

    type := #partner 

    "
     create two topViews within the same group:
     if any of them is iconified/deiconified/closed, the other one is also

     |top1 top2|

     top1 := StandardSystemView new label:'partner'; extent:300@300.
     top2 := StandardSystemView new label:'partner'; extent:200@200.
     top1 bePartner.
     top2 bePartner.

     top1 open.
     top2 openInGroup:(top1 windowGroup)
    "

    "Created: 10.12.1995 / 13:29:59 / cg"
    "Modified: 25.5.1996 / 11:44:48 / cg"
!

beSlave
    "make this a slave-view. It will be closed automatically,
     whenever any master of the windowgroup is closed.
     See also: #bePartner"

    type := #slave 

    "
     create two topViews within the same group:
     the slave is allowed to be iconified/close independ of the master;
     but if the master is iconified, the slave is also.

     |top1 top2|

     top1 := StandardSystemView new label:'master'; extent:300@300.
     top2 := StandardSystemView new label:'slave'; extent:200@200.
     top1 beMaster.
     top2 beSlave.

     top1 open.
     top2 openInGroup:(top1 windowGroup)
    "

    "Created: 10.12.1995 / 13:29:10 / cg"
    "Modified: 25.5.1996 / 11:45:30 / cg"
!

focusSequence:aCollectionOfSubcomponents
    "define the sequence for stepping through my components."

    windowGroup isNil ifTrue:[
        windowGroup := WindowGroup new.
    ].
    windowGroup focusSequence:aCollectionOfSubcomponents.

    "Created: 6.3.1996 / 15:37:11 / cg"
    "Modified: 30.4.1996 / 15:41:40 / cg"
! !

!TopView methodsFor:'event handling'!

keyPress:key x:x y:y
    "notice: this is going to be moved into the upcoming 
     StandardSystemViewController."

    <resource: #keyboard ( #Tab 
                           #FocusNext #FocusPrevious 
                           #CursorDown #CursorUp ) >

    windowGroup notNil ifTrue:[
        key == #Tab ifTrue:[
            self sensor shiftDown ifTrue:[
                windowGroup focusPrevious
            ] ifFalse:[
                windowGroup focusNext
            ].
            ^ self.
        ].
        (key == #FocusNext or:[key == #CursorDown]) ifTrue:[
            windowGroup focusNext.
            ^ self.
        ].
        (key == #FocusPrevious or:[key == #CursorUp])  ifTrue:[
            windowGroup focusPrevious.
            ^ self.
        ].
    ].

    super keyPress:key x:x y:y

    "Created: 1.2.1996 / 22:08:30 / cg"
    "Modified: 9.1.1997 / 12:17:38 / cg"
!

showActivity:someMessage
    "some activityNotification shalt be communicated to
     the user. 
     Default for activity notifications here: ignore them"

    ^ self

    "Created: 16.12.1995 / 18:40:13 / cg"
    "Modified: 23.4.1996 / 21:38:27 / cg"
! !

!TopView methodsFor:'help stubs'!

flyByHelpTextFor:aSubView
    "this will vanish - its temporarily here to allow for stdSysViews to be
     used as a masterApp for dialogs"

    ^ nil
!

helpTextFor:aSubView
    "this will vanish - its temporarily here to allow for stdSysViews to be
     used as a masterApp for dialogs"

    ^ nil
!

showHelp:aHelpText for:aView
    "dummy - added in case a regular topView is installed
     as a dialogs masterApplication.
     Concrete application subclasses may redefine this to
     display a help text in one of its message areas"
! !

!TopView methodsFor:'initialization & release'!

assignKeyboardFocusToFirstInputField
    "assign the keyboard focus to the first input field,
     or else to the first keyboardConsumer.
     This prefers inputFields over editTextViews 
     (which may change in the future)"

    |firstConsumer firstCursorConsumer consumer|

    self allSubViewsDo:[:v |
        v isInputField ifTrue:[
            "/ self windowGroup focusView:v.       -- very old
            device platformName = 'WIN32' ifTrue:[
                self windowGroup focusView:v byTab:true.
            ] ifFalse:[
                v requestFocus.                    
            ].
            ^ self
        ].
        (firstConsumer isNil and:[v isKeyboardConsumer]) ifTrue:[
            firstConsumer := v
        ].
        (firstCursorConsumer isNil and:[v isCursorKeyConsumer]) ifTrue:[
            firstCursorConsumer := v
        ].
    ].
    consumer := (firstConsumer ? firstCursorConsumer).
    consumer notNil ifTrue:[
        consumer requestFocus.
        "/ firstConsumer requestFocus. - could be denied; but we force it here
        windowGroup focusView:consumer byTab:false.
    ].

    "Modified: / 20.5.1999 / 18:14:16 / cg"
!

destroy
    "the receiver is to be destroyed - look for partners and slaves"

    |wg dev|

    wg := windowGroup.                  "/ have to fetch windowGroup before;
    dev := device.                      "/ and device ...
    super destroy.                      "/ ... since destroy nils em

"/    dev notNil ifTrue:[
"/        dev flush
"/    ].

    "/
    "/ destroy slaves and partners
    "/
    self masterSlaveMessage:#destroy inGroup:wg

    "Modified: 20.3.1997 / 22:14:16 / cg"
!

initialize
    "initialize the topViews position for the screens center"

    |screenCenter|

    super initialize.

    device initializeTopViewHookFor:self.

    screenCenter := device center.
    left := screenCenter x - (width // 2).
    top := screenCenter y - (height // 2).
    type := #normal
!

postRealize
    super postRealize.

    keyboardProcessor isNil ifTrue:[
        keyboardProcessor := KeyboardProcessor new.
    ].

    device realizedTopViewHookFor:self
!

release
    keyboardProcessor notNil ifTrue:[
        keyboardProcessor release.
        keyboardProcessor := nil.
    ].
    super release
! !

!TopView methodsFor:'misc'!

raiseDeiconified
    "deiconify & bring to front"

    self isCollapsed ifTrue:[
"/        self unmap.
        self realize.
    ].
    self raise

    "
     Transcript topView raiseDeiconified
    "

    "Modified: 3.5.1996 / 23:49:36 / stefan"
!

waitUntilClosed
    "wait until the receiver has been closed.
     Can be used to synchronize multiple-window applications,
     and (especially) to wait until an application session is finished
     when invoking commands with the rDoit mechanism"

    [drawableId isNil] whileFalse:[
        Delay waitForSeconds:0.1.
    ].

    "asynchronous:

     EditTextView open
    "

    "synchronous:

     EditTextView open topView waitUntilClosed
    "

    "Modified: / 20.5.1998 / 18:03:37 / cg"
!

withCursor:aCursor do:aBlock
    "evaluate aBlock while showing aCursor in all my views.
     Return the value as returned by aBlock."

    windowGroup notNil ifTrue:[
        ^ windowGroup withCursor:aCursor do:aBlock
    ].
    ^ super withCursor:aCursor do:aBlock
! !

!TopView methodsFor:'queries'!

heightIncludingBorder
    "return the views overall-height"

    ^ height
!

isCollapsed
    "ST80 compatibility: return true if the view is not shown (i.e. iconified)"

    "/ ^ device windowIsIconified:drawableId
    ^ shown not

    "Modified: 4.4.1997 / 14:44:39 / cg"
!

isMaster
    "return true, if this is a masterView"

    ^ type == #master
!

isModal
    "return true, if the receiver has been opened modal"

    windowGroup isNil ifTrue:[^ false].
    ^ windowGroup isModal
!

isPartner
    "return true, if this is a partnerView"

    ^ type == #partner
!

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

    ^ type == #popup

    "Created: 28.2.1997 / 22:12:30 / cg"
    "Modified: 28.2.1997 / 22:37:01 / cg"
!

isSlave
    "return true, if this is a slaveView"

    ^ type == #slave
!

isTopView
    "return true, since I am a topView"

    ^ true

    "Created: 22.3.1997 / 14:45:55 / cg"
!

preferredExtent
    "return my preferred extent - this is the minimum size I would like to have.
     The default here is the classes default extent,
     however many subclasses redefine this to compute the actual value
     depending on the sizes of the contents or subcomponents."

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].
    ^ self class defaultExtent

    "Modified: 19.7.1996 / 20:45:41 / cg"
!

type
    "return the views type. This is one of #normal,
     #master, #slave or #partner."

    ^ type
!

widthIncludingBorder
    "return the views overall-width"

    ^ width
!

window
    "for compatibility with applicationModels ... return the receiver"

    ^ self
! !

!TopView methodsFor:'show & hide'!

fixPosition:aPoint
    "set origin to aPoint, but make sure, that the box is fully visible 
     by shifting it into the visible screen area if nescessary.
     This prevents invisible modalBoxes (which you could never close)."

    self origin:aPoint.
    self makeFullyVisible

    "Created: 28.2.1997 / 16:39:31 / cg"
!

map
    "make the view visible on the screen.
     For topViews, the windowManager will choose (or ask for) the
     views position on the screen.
     Notice:
        Actually, this method is only valid for topViews;
        however, it is defined here to allow things like 'Button new realize'"

    self mapAt:(self origin) iconified:false
!

mapIconified
    "make the view visible but iconified.
     In contrast to map, which does it non-iconified"

    realized ifFalse:[
        "
         now, make the view visible
        "
        realized := true.
        device
            mapView:self id:drawableId iconified:true
            atX:left y:top width:width height:height
            minExtent:(self minExtent) maxExtent:(self maxExtent)
    ]

    "Modified: 25.2.1997 / 22:44:33 / cg"
    "Created: 24.7.1997 / 12:48:21 / cg"
!

positionOffset
    "return the delta, by which the box should be
     displaced from the mouse pointer.
     Here, the boxes center is returned as a default.
     Usually redefined in subclasses to have the most convenient
     ok-button appear under the pointer."

    ^ self extent // 2

    "Created: 28.2.1997 / 22:56:34 / cg"
! !

!TopView methodsFor:'startup'!

openAt:aPosition transientFor:anotherView
    "force the view to be opened at some position on the screen
     AND tell the windowManager to NOT let the user choose a position
     (i.e. suppress any ghostframe).
     The view is marked as being a transient (i.e. pop-up) view for
     anotherView - it will deiconify with it and (on some windowManagers)
     have no iconify button of its own.
     Notice, that its up to the windowManager to care for any borders -
     it seems not deterministic, where the view actually ends up being positioned.
     Not all windowManagers (olwm) honor this - some insist on it ..."

    |otherId|

    drawableId isNil ifTrue:[self create].
    anotherView isNil ifTrue:[
        otherId := drawableId.
    ] ifFalse:[
        anotherView create.
        otherId := anotherView id.
    ].
    device setTransient:drawableId for:otherId.
    self origin:aPosition.
    self open

    "
     |v1 v2|

     v1 := StandardSystemView extent:300@300.
     v2 := StandardSystemView extent:300@300.
     v1 open.
     v2 openAt:0@0 transientFor:v1.
    "

    "
     |v1|

     v1 := StandardSystemView extent:300@300.
     v1 openAt:0@0 transientFor:v1.
    "

    "Created: 28.6.1996 / 10:51:55 / cg"
    "Modified: 28.7.1997 / 18:53:16 / cg"
!

openDisplayAt:aPoint
    "ST-80 compatibility: open the view centered around aPoint"

    ^ self openModelessAt:(aPoint - (self extent//2))

    "
     (TopView new extent:200@200) openDisplayAt:300@300
    "
!

openIconified
    "open the view in iconified state"

    self openModelessAt:nil iconified:true

    "
     FileBrowser new openIconified
     ChangesBrowser new openIconified
    "

    "Modified: 24.7.1997 / 14:54:58 / cg"
!

openIn:aBoundaryRectangle
    "set origin & extent and open. 
     The given extent overrides the receivers preferredExtent.
     Added for ST-80 compatibility"

    self 
        origin:aBoundaryRectangle origin; 
        extent:aBoundaryRectangle extent; 
        sizeFixed:true.
    self open

    "Modified: 12.2.1997 / 11:58:21 / cg"
!

openTransientAt:aPosition
    "force the view to be opened at soem position on the screen
     AND tell the windowManager to NOT let the user choose a position
     (i.e. suppress any ghostframe).
     Notice, that its up to the windowManager to care for any borders -
     it seems not deterministic, where the view actually ends up being positioned.
     Not all windowManagers (olwm) honor this - some insist on it ..."

    self openAt:aPosition transientFor:nil

    "normal open:

     |v|

     v := StandardSystemView extent:300@300.
     v open
    "

    "open at position:

     |v|

     v := StandardSystemView extent:300@300.
     v openTransientAt:10@10
    "

    "Created: 28.6.1996 / 10:52:30 / cg"
    "Modified: 28.6.1996 / 10:55:15 / cg"
!

openWithExtent:anExtent
    "set extent and open. The given extent overrides the 
     receivers preferredExtent.
     Added for ST-80 compatibility"

    self extent:anExtent; sizeFixed:true.
    self open
!

openWithPriority:aPriority
    "open the view, run the windowgroup process at
     other than UserScehdulingPriority."

    self open.
    windowGroup process priority:aPriority.

    "Created: 30.4.1996 / 15:34:44 / cg"
! !

!TopView methodsFor:'window events'!

mapped 
    "the recevier was unmapped (i.e. iconified);
     look for partners and slaves."

    realized := true. 
    super mapped.

    "/
    "/ map slaves and partners
    "/
    self masterSlaveMessage:#remap inGroup:windowGroup.

    self isModal ifTrue:[
        "take it away from any popup menu possibly still active"

        self forceUngrabKeyboard.
        self forceUngrabPointer.
        "
         get the focus
        "
        self getKeyboardFocus.
        self enableEnterLeaveEvents
    ] ifFalse:[
        "
         ask for the focus - this avoids having to click on the
         view with WM's which need an explicit click.
         Q: is this a good idea ?
        "
        TakeFocusWhenMapped == true ifTrue:[
            self getKeyboardFocus.
        ]
    ]



    "Modified: / 10.9.1998 / 22:02:52 / cg"
    "Modified: 30.5.1996 / 09:37:22 / cg"
!

masterSlaveMessage:aSelector inGroup:aWindowGroup
    "send aSelector to partners and/or slaves.
     This is a private helper for destroy / mapped / unmapped"

    aWindowGroup notNil ifTrue:[
        "/
        "/ if I am a master or partner, send to all slaves
        "/
        (type == #master or:[type == #partner]) ifTrue:[
            aWindowGroup slavesDo:[:v | v perform:aSelector].
        ].
        "/
        "/ if I am a partner, send to all partners
        "/
        type == #partner ifTrue:[
            aWindowGroup partnersDo:[:v | v ~~ self ifTrue:[v perform:aSelector]].
        ].
    ].
!

unmapped 
    "the recevier was unmapped (i.e. iconified);
     look for partners and slaves."

    |r|

    (windowGroup notNil and:[windowGroup isModal]) ifTrue:[
        "keep the realized flag true (to avoid exiting the modal event loop).
         Consider this a kludge."
        r := realized.
        super unmapped.
        realized := r.
    ] ifFalse:[
        realized := false. 
        super unmapped.
    ].

    "/
    "/ unmap slaves and partners
    "/
    self masterSlaveMessage:#unmap inGroup:windowGroup

    "Modified: 30.5.1996 / 09:37:22 / cg"
! !

!TopView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.82 2003-07-22 17:56:20 cg Exp $'
! !