WindowGroup.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Mar 1996 01:06:44 +0100
changeset 496 71ecf6bfdff2
parent 429 0d3bebf239ab
child 500 a313e9fda9f0
permissions -rw-r--r--
checkin from browser

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

Object subclass:#WindowGroup
	instanceVariableNames:'views topViews myProcess mySensor isModal previousGroup focusView
		focusSequence preEventHook postEventHook pointerView
		isForModalSubview'
	classVariableNames:'LastActiveGroup LastActiveProcess LeaveSignal'
	poolDictionaries:''
	category:'Interface-Support'
!

!WindowGroup class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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
"
    In Smalltalk/X, the known (ST-80) concept of a controller has been
    extended (split) into a WindowGroup which handles process related stuff, 
    and the Controller, which only handles events for a view and defines the user interaction.
    All interaction is via event queues - there is no polling in controllers (not even conceptionally).

    WindowGroups are responsible to wait for and forward events for a group of 
    windows. All views in a windowGroup share a single windowSensor which holds the
    event queue (therefore views all share the same input event queue).

    The event queues are filled with incoming events as arriving from the physical display.
    This is done by a separate process (so called event-dispatcher) which runs at a higher
    priority. The event dispatcher determines the queue into which an event has to be placed
    by the view for which the event is destined (via the views sensor).
    There may be multiple event dispatchers running (to support multiple displays);
    see the documentation/examples in DeviceWorkstation/XWorkstation on how this is done.

    Except for modal boxes, a separate process is created for each windowGroup 
    which waits for events to arrive and processes them, by sending corresponding
    event messages to the views controller or the view (*). 
    The controller is determined by asking the view (for which the event is destined);
    if the returned controller is nil, the event is sent directly to the view.
    This allows for simple views to work without a controller.
    (all of this is actually done in a WindowEvent method)

    Therefore, multiple applications run pseudo parallel.
    Even if some window performs a long time computation, events are still received
    and entered into the corresponding event queues (because the event dispatcher process
    runs at a higher priority). However, the actual processing of the event is only
    possibly if no other process is busy at the same or a higher priority.
    It is possible to change a windowProcesses priority in order to give other windows
    a chance to execute (some views do this while performing longtime actions).

    Modal boxes create an extra window group for the components of the modal
    box, but execute the event-processing loop for this new group in the original process - 
    therefore, the original windowgroup is blocked for the duration of the modal 
    interaction.
    However, the modal-event processing loop peeks into the original groups event queue
    from time to time, and handles expose events. Thus, even while blocked for user input,
    the original group continues to get update/redraw events.

    Normally, one windowgroup is associated to each topview (StandardSystemView)
    and all of its subviews. However, this is not strictly required; 
    it is possible to create extra windowgroups for subviews, which will let them
    run in parallel 
	(for example, the FileBrowsers kill-Button is created that 
	 way, to allow a kill of an executing unix command, while the browser 
	 itself reads the pipeStream for incoming text.
	 Even if the fileBrowser is busy reading the pipe, the killButton is still
	 working and allows terminating the pipe-read action).

    On the other hand, multiple topviews can be placed into the same windowGroup;
    which allows for multiview applications, of which only one communicates with
    the user at a time.

    Multiple topviews within a windowGropup can be configured to behave like one 
    unit with respect to iconification, deiconification and termination.
    This is done by creating multiple topViews in one group, and setting up a master/slave
    or partner relation among them (see TopView>>beSlave and TopView>>bePartner).

    WindowGroups also support a focus window: this is the one that gets the
    keyboard input - even if the cursor is located in another subview.
    (this is a brand new feature and not yet fully released for public use)

    Finally, windowgroups are the perfect place for things like defining a
    cursor for all associated views, flushing all input, waiting for expose
    events etc.

    Dont get confused:
	You dont have to care for details in the normal case, a windowgroup is
	created for you automatically, when a view is opened.
	All of the internals are not required to be known for most applications.


    instance variables:

	views                   collection of views of this group

	topViews                collection of topviews of this group

	myProcess               the process executing the events

	mySensor                my input sensor

	isModal                 true if this is for a modal box

	previousGroup           if modal, the group that started this one

	focusView               the one that has the focus (or nil)

	focusSequence           defines the focus sequence


    clas variables:
	LeaveSignal             if raised, a modal box leaves (closes)


    (*) 
	due to historic reasons, many views have the controller functionality
	integrated, and handle events themself. The windowSensor takes care
	of this, by checking if a view has a controller, and, if so, forwarding 
	the events to it. Otherwise, events are sent directly to the view.

	In the future, all views will be rewritten to actually use a controller.
	Currently (being in the middle of this migration), only some views
	(buttons, toggles and subclasses) do so.






    For more information, read 'introduction to view programming' in the
    doc/online directory.
"

! !

!WindowGroup class methodsFor:'initialization'!

initialize
    LeaveSignal isNil ifTrue:[
	LeaveSignal := (Signal new) mayProceed:true.
	LeaveSignal nameClass:self message:#leaveSignal.
	LeaveSignal notifierString:'unhandled leave signal'.
    ].

    "WindowGroup initialize"
! !

!WindowGroup class methodsFor:'instance creation'!

new
    "create and return a new WindowGroup object"

    ^ self basicNew initialize
! !

!WindowGroup class methodsFor:'Signal constants'!

leaveSignal
    "return the signal which is used to exit a modal loop.
     This private signal, is always cought while a modalbox is active.
     Raising it will exit the modal loop and return from the views #openModal
     method."

    ^ LeaveSignal
! !

!WindowGroup class methodsFor:'accessing'!

activeGroup
    "return the currently active windowGroup.
     The returned value may not be fully correct, in case the current process
     handles multiple windowGroups simulaniously. In this case, 
     the first group is returned (prefering a modal if there is one). 
     (maybe we should return a collection of windowGroups here).

     This method is required to simulate the historic ST-80 single display
     behavior for Cursor>>show / Cursor>>showWhile and some others (raising the
     activeGroups topView when modalBoxes appear) on multiple display screens. 
     These methods should change the cursor for the currently 
     active windowGroup ONLY, instead of globally affecting the display or
     all views
     (since, depending on the priority, other views could be unaffacted by this 
      and an overall cursor change does not make sense.)"

    |activeProcess groups wg|

    Processor isNil ifTrue:[^ nil]. "/ only during very early init phase

    activeProcess := Processor activeProcess.
    " caching the last value ..."
    activeProcess == LastActive ifTrue:[
	LastActiveGroup process == LastActive ifTrue:[
	    ^ LastActiveGroup
	]
    ].
    groups := self scheduledWindowGroups 
		select:[:wg | wg process == activeProcess].
    groups size == 1 ifTrue:[
	wg := groups anElement
    ] ifFalse:[
	wg := groups detect:[:wg | wg isModal] ifNone:nil.
	wg isNil ifTrue:[
	    wg := groups anElement
	]
    ].
    wg notNil ifTrue:[
	LastActiveProcess := activeProcess.
	LastActiveGroup := wg.
    ].
    ^ wg

    "
     WindowGroup activeGroup 
    "

    "Modified: 3.9.1995 / 14:49:53 / claus"
!

scheduledWindowGroups
    "return a collection of all windowGroups (possibly for different
     display devices) which are scheduled (i.e. which have a process 
     running, handling events)."

    |set screens|

    screens := Screen allScreens.
    screens isNil ifTrue:[^ #()].

    set := IdentitySet new.
    screens do:[:aDevice |
	aDevice allViewsDo:[:aView |
	    |wg|

	    (wg := aView windowGroup) notNil ifTrue:[
		wg process notNil ifTrue:[
		    set add:wg
		]
	    ].
	].
    ].
    ^ set asArray

    "
     WindowGroup scheduledWindowGroups   
    "

    "Modified: 1.9.1995 / 13:43:09 / claus"
!

setActiveGroup:aGroup
    "set the currently active windowGroup.
     Temporary; do not use this interface, it will vanish."

    LastActiveProcess := Processor activeProcess.
    LastActiveGroup := aGroup
! !

!WindowGroup methodsFor:'accessing'!

addTopView:aView
    "add a topview to the group"

    topViews isNil ifTrue:[
	topViews := OrderedCollection new.
    ].
    topViews add:aView
!

addView:aView
    "add aView to the windowGroup"

    views isNil ifTrue:[
	views := OrderedCollection new.
    ].
    views add:aView
!

device
    "return the device, we receive our events from"

    (topViews notNil and:[topViews isEmpty not]) ifTrue:[
	^ topViews first device
    ].
    (views notNil and:[views isEmpty not]) ifTrue:[
	^ views first device
    ].
    ^ nil

    "Created: 13.12.1995 / 14:00:45 / stefan"
    "Modified: 13.12.1995 / 14:18:11 / stefan"
!

isModal
    "return true, if I am in a modal mode"

    ^ isModal
!

mainGroup
    "return the main windowgroup 
     (that is the top one, which is not modal).
     There is one exception to this: the debugger (which is sort of modal)
     returns itself as mainGroup (not its debuggee)."

    |g prev|

    g := self.
    [g notNil and:[g isModal and:[(prev := g previousGroup) notNil]]] whileTrue:[
	g := prev
    ].
    ^ g

    "Modified: 3.9.1995 / 14:57:20 / claus"
!

postEventHook:anObject 
    "set the postEventHook - this one will get all events
     passed after being processed here (via #processEvent:)."

    postEventHook := anObject
!

preEventHook:anObject 
    "set the preEventHook - this one will get all events
     passed before being processed here (via #processEvent:).
     If this returns true, the event is supposed to be already
     processed and ignored here.
     Otherwise, it is processed as usual."

    preEventHook := anObject
!

previousGroup
    "return the windowgroup that started this group.
     (for modal groups only)"

    ^ previousGroup
!

process 
    "return the windowGroups process"

    ^ myProcess
!

removeView:aView
    "remove aView from the windowGroup;
     if this was the last view in this group, 
     also shut down the corresponding process 
     (actually, only wake it up here - it will terminate itself 
      when finding out that all views are gone)"

    |sema|

    views notNil ifTrue:[
	views remove:aView ifAbsent:[].
	views isEmpty ifTrue:[
	    views := nil
	]
    ].
    topViews notNil ifTrue:[
	topViews remove:aView ifAbsent:[].
	topViews isEmpty ifTrue:[
	    topViews := nil
	]
    ].
    "
     wakeup my process to look if last view has been
     removed (modalBoxes terminate their modalLoop if so)
    "
    mySensor notNil ifTrue:[
	(sema := mySensor eventSemaphore) notNil ifTrue:[
	    sema signal
	]
    ]
!

sensor
    "return the windowGroups sensor"

    ^ mySensor
!

sensor:aSensor
    "set the windowGroups sensor"

    mySensor := aSensor
!

topViews
    "return the topviews accociated to this windowGroup"

    ^ topViews
!

views
    "return the views accociated to this windowGroup"

    ^ views
! !

!WindowGroup methodsFor:'activation / deactivation'!

closeDownViews
    "destroy all views associated to this window group"

    topViews notNil ifTrue:[
	topViews do:[:aTopView | aTopView notNil ifTrue:[aTopView destroy]]
    ].
    views := nil.
    topViews := nil.
    mySensor := nil.
!

realizeTopViews:isRestart
    "realize all topViews associated to this windowGroup.
     If this is a restart, tell topViews about it."

    topViews notNil ifTrue:[
	topViews do:[:aView |
	    aView realize.
	    isRestart ifTrue:[
		aView restarted
	    ]
	].
    ].
!

restart
    "restart after a snapin."

    topViews notNil ifTrue:[
	"
	 need a new semaphore, since obsolete processes 
	 (from our previous live) may still sit on the current semaphore
	"
	mySensor eventSemaphore:Semaphore new.
	isModal ifFalse:[
	    self startup:true 
	]
    ]
!

shutdown
    "shutdow the window group; close all views and
     terminate process"

    |p|

    self closeDownViews.
    myProcess notNil ifTrue:[
	p := myProcess.
	myProcess := nil.
	p terminate.
    ]
!

startup:isRestart
    "startup the window-group;
     this creates a new window group process, which
     does the event processing."

    |top nm dev devNm|

    previousGroup := nil.
    myProcess isNil ifTrue:[
	isModal := false.
	myProcess := [
	    self realizeTopViews:isRestart.
	    self eventLoopWhile:[true] onLeave:[]
	] forkAt:Processor userSchedulingPriority.

	(topViews notNil and:[topViews isEmpty not]) ifTrue:[
	    "
	     give the handler process a user friendly name
	    "
	    top := topViews first.
	    nm := top processName.
	    (dev := top device) notNil ifTrue:[
		devNm := dev displayName.
		(devNm notNil and:[devNm ~= Display displayName]) ifTrue:[
		    nm := nm , ' (' , devNm , ')'
		]
	    ]
	] ifFalse:[
	    nm := 'window handler'.
	].
	myProcess name:nm.

	"
	 when the process gets suspended, there maybe still buffered draw requests.
	 Flush them.
	"
	myProcess suspendAction:[ 
	    |dev|
	    dev := self device.
	    dev notNil ifTrue:[dev flush].
	].

	"when the process dies, we have to close-down
	 the views as well
	"
	myProcess exitAction:[self closeDownViews]
    ]

    "Modified: 13.12.1995 / 14:04:53 / stefan"
!

startupModal:checkBlock
    "startup the window-group in a modal loop 
     (i.e. under the currently running process);
     checkBlock is evaluated and the modal loop is left, whenever false is returned."

    ^ self startupModal:checkBlock forGroup:WindowGroup activeGroup.

    "Created: 10.12.1995 / 14:15:11 / cg"
!

startupModal:checkBlock forGroup:mainGroup
    "startup the window-group in a modal loop 
     (i.e. under the currently running process);
     checkBlock is evaluated and loop is left, when false is
     returned.
     The mainGroup info is required to allow peeking into its
     event queue in order for its expose/redraws to be handled."

    "set previousGroup to the main (non-modal) group"

    previousGroup := mainGroup.
    isModal := true.
    self realizeTopViews:false.
    self 
	eventLoopWhile:checkBlock 
	onLeave:[
	    "
	     cleanup, in case of a terminate
	    "
	    previousGroup := nil.
	    topViews := nil.
	    views := nil.
	    "
	     the following is rubbish;
	     the views could be reused ..
	    "
"
	    topViews notNil ifTrue:[
		topViews do:[:aView |
		    aView destroy
		].
		topViews := nil.
	    ].
	    views notNil ifTrue:[
		views do:[:aView |
		    aView destroy
		].
		views := nil.
	    ].
"
	]

    "Created: 10.12.1995 / 14:14:26 / cg"
! !

!WindowGroup methodsFor:'enumerating'!

allTopViewsExcept:aView do:aBlock
    "evaluate aBlock for all topviews except aView in this group.
     This works on a copy of the view collection, to allow for
     destroy and other collection changing operations to be done."

    topViews notNil ifTrue:[
	topViews copy do:[:v |
	    v ~~ aView ifTrue:[aBlock value:v]
	]
    ].
!

allViewsDo:aBlock
    "evaluate aBlock for all views & topviews in this group.
     This works on a copy of the view collection, to allow for
     destroy and other collection changing operations to be done."

    topViews notNil ifTrue:[topViews copy do:aBlock].
    views notNil ifTrue:[views copy do:aBlock]
!

partnersDo:aBlock
    "evaluate aBlock for all partnerViews.
     This works on a copy of the view collection, to allow for
     destroy and other collection changing operations to be done."

    topViews notNil ifTrue:[
	topViews copy do:[:v |
	    v notNil ifTrue:[
		v type == #partner ifTrue:[aBlock value:v].
	    ]
	]
    ].
!

slavesDo:aBlock
    "evaluate aBlock for all slaveViews.
     This works on a copy of the view collection, to allow for
     destroy and other collection changing operations to be done."

    topViews notNil ifTrue:[
	topViews copy do:[:v |
	    v notNil ifTrue:[
		v type == #slave ifTrue:[aBlock value:v].
	    ]
	]
    ].
! !

!WindowGroup methodsFor:'event handling'!

eventLoop
    "loop executed by windowGroup process;
     wait-for and process events forever"

   self eventLoopWhile:[true] onLeave:[]
!

eventLoopWhile:aBlock onLeave:cleanupActions
    "wait-for and process events. 
     Stay in this loop while there are still any views to dispatch for,
     and aBlock evaluates to true."

    |thisProcess|

    thisProcess := Processor activeProcess.

    [
        "/
        "/ on leave, exit the event loop
        "/
        LeaveSignal handle:[:ex |
            ex return
        ] do:[
            |p g mainGroup mySema waitSema|

            waitSema := mySema := mySensor eventSemaphore.

            isModal ifTrue:[
                mainGroup := self mainGroup.
                mainGroup == self ifTrue:[
                    mainGroup := nil
                ].
                mainGroup notNil ifTrue:[
                    waitSema := SemaphoreSet with:mySema 
                                             with:(mainGroup sensor eventSemaphore).
                ].
            ].

            aBlock whileTrue:[ 
                LastActiveGroup := self.
                LastActiveProcess := thisProcess.

                (views isNil and:[topViews isNil]) ifTrue:[
                    myProcess notNil ifTrue:[
                        p := myProcess.
                        myProcess := nil.
                        p terminate.
                        "not reached - there is no life after death"
                    ].
                    "
                     this is the end of a modal loop
                     (not having a private process ...)
                    "
                    ^ self
                ].

                "/
                "/ on abort, stay in the event loop
                "/
                AbortSignal handle:[:ex |
                    ex return
                ] do:[
                    ActivityNotificationSignal handle:[:ex |
                        "/
                        "/ if I am a modal-group, let it be handled
                        "/ by the outer main-groups handler
                        "/
                        isModal ifTrue:[
                            ex reject
                            "never reached"
                        ].
                        self showActivity:(ex errorString).
                        ex proceed.
                    ] do:[
                        |dev gotSema mainView|

                        "/ no more events. Flush device output. This may produce more events.
                        dev := self device.
                        dev notNil ifTrue:[dev flush].

                        thisProcess setStateTo:#eventWait if:#active.
                        gotSema := waitSema wait.
                        LastActiveGroup := self.
                        LastActiveProcess := thisProcess.
                        gotSema == mySema ifTrue:[
                            self processEvents
                        ] ifFalse:[
                            mainGroup topViews notNil ifTrue:[
                                mainView := mainGroup topViews first
                            ].
                            mainView notNil ifTrue:[
                                (mainGroup sensor hasConfigureEventFor:mainView) ifTrue:[
                                     topViews first raiseDeiconified
                                ]
                            ].
                            "
                             if modal, also check for redraw events in my maingroup
                             (we arrive here after we woke up on maingroup sensor eventSemaphore)
                            "
                            mainGroup processExposeEvents.
                        ]
                    ]
                ].
            ].
        ].
    ] valueNowOrOnUnwindDo:[
        cleanupActions notNil ifTrue:[cleanupActions value]
    ]

    "Modified: 14.12.1995 / 11:12:24 / stefan"
    "Modified: 16.12.1995 / 18:39:03 / cg"
!

leaveEventLoop
    "immediately leave the event loop, returning way back.
     This can be used to leave (and closedown) a modal group.
     (for normal views, this does not make sense)"

    ^ LeaveSignal raise
!

processEvents
    "process events from either the damage- or user input queues.
     Abort is assumed to be handled elsewhere."

    <resource: #keyboard (#FocusNext #FocusPrevious #Escape )>

    |event ignore key|

    self processExposeEvents.

    [mySensor hasEvents] whileTrue:[
        event := mySensor nextEvent.
        event notNil ifTrue:[
            (views notNil or:[topViews notNil]) ifTrue:[
                ignore := false.

                (preEventHook  notNil 
                and:[preEventHook processEvent:event]) ifTrue:[
                    ignore := true.
                ].
                ignore ifFalse:[
                    "/
                    "/ FocusStepping is done right here
                    "/
                    event isKeyPressEvent ifTrue:[
                        (key := event key) == #FocusNext ifTrue:[
                            self focusNext.
                            ignore := true
                        ].
                        key == #FocusPrevious ifTrue:[
                            self focusPrevious.
                            ignore := true
                        ].
"/                        key == #Tab ifTrue:[
"/                            focusView notNil ifTrue:[
"/                                focusView canTab ifTrue:[
"/                                    self focusNext.    
"/                                    ignore := true
"/                                ]
"/                            ] ifFalse:[
"/                                pointerView notNil ifTrue:[
"/                                    pointerView canTab ifTrue:[
"/                                        self focusNext.
"/                                        ignore := true.
"/                                    ]
"/                                ] ifFalse:[
"/                                    self focusNext.
"/                                    ignore := true.
"/                                ]
"/                            ]
"/                        ].
                        key == #Escape ifTrue:[
                            isModal ifTrue:[
                                topViews first hideRequest
                            ]
                        ]
                    ].
                    event isPointerEnterEvent ifTrue:[
                        pointerView := event view
                    ].
                    event isPointerLeaveEvent ifTrue:[
                        pointerView := nil
                    ].

                    ignore ifFalse:[
                        "/
                        "/  button events turn off explicit focus, and revert
                        "/  to implicit focus control
                        "/
                        (focusView notNil
                        and:[event isButtonEvent]) ifTrue:[
                            self focusView:nil
                        ].
                        "/
                        "/ let the event forward itself
                        "/
                        LastActiveGroup := self.
                        LastActiveProcess := Processor activeProcess.
                        event sendEventWithFocusOn:focusView.
                    ]
                ].
                postEventHook notNil ifTrue:[
                    postEventHook processEvent:event
                ]
            ]
        ].
    ]

    "Modified: 4.3.1996 / 18:01:09 / cg"
!

processExposeEvents
    "process only expose events from the damage queue"

    |event view rect x y w h sensor thisProcess|

    (sensor := mySensor) isNil ifTrue:[^ self].

    thisProcess := Processor activeProcess.

    [sensor hasDamage] whileTrue:[
	LastActiveGroup := self.
	LastActiveProcess := thisProcess.

	event := sensor nextDamage.
	event notNil ifTrue:[
	    (views notNil or:[topViews notNil]) ifTrue:[
		(preEventHook notNil 
		and:[preEventHook processEvent:event]) ifFalse:[
		    event isDamage ifTrue:[
			view := event view.
			"/
			"/ if the view is no longer shown (iconified or closed),
			"/ this is a leftover event and ignored.
			"/
			view shown ifTrue:[
			    rect := event rectangle.
			    x := rect left.
			    y := rect top.
			    w := rect width.
			    h := rect height.
			    LastActiveGroup := self.
			    LastActiveProcess := thisProcess.
			    view transformation notNil ifTrue:[
				view deviceExposeX:x y:y width:w height:h
			    ] ifFalse:[
				view exposeX:x y:y width:w height:h
			    ]
			]
		    ] ifFalse:[
			"
			 mhmh - could we possibly arrive here ?
			"
			LastActiveGroup := self.
			LastActiveProcess := thisProcess.
			event sendEvent.
		    ]
		].
		postEventHook notNil ifTrue:[
		    postEventHook processEvent:event
		]
	    ]
	]
    ]
!

waitForExposeFor:aView
    "wait for a noExpose on aView, then process all exposes.
     To be used after a scroll"

    mySensor waitForExposeFor:aView.
    AbortSignal catch:[
	self processExposeEvents
    ]
! !

!WindowGroup methodsFor:'focus control'!

focusNext
    "give focus to next view in focusSequence"

    |index|

    focusSequence size == 0 ifTrue:[^ self].
    focusView notNil ifTrue:[
	index := (focusSequence indexOf:focusView) + 1.
	index > focusSequence size ifTrue:[index := 1].
    ] ifFalse:[
	index := 1.
    ].
    self focusView:(focusSequence at:index)

    "
     |top v1 v2|

     top := StandardSystemView new.
     v1 := EditTextView origin:0.0@0.0 corner:1.0@0.5 in:top.
     v2 := EditTextView origin:0.0@0.5 corner:1.0@1.0 in:top.
     top open.
     top windowGroup focusSequence:(Array with:v1 with:v2).
     top windowGroup focusOn:v1.
     (Delay forSeconds:10) wait.
     top windowGroup focusNext.
    "
!

focusPrevious
    "give focus to previous view in focusSequence"

    |index|

    focusSequence size == 0 ifTrue:[^ self].
    focusView notNil ifTrue:[
	index := (focusSequence indexOf:focusView) - 1.
	index < 1 ifTrue:[index := focusSequence size].
    ] ifFalse:[
	index := focusSequence size.
    ].
    self focusView:(focusSequence at:index)
!

focusSequence
    "return the focus sequence for focusNext/focusPrevious.
     Focus is stepped in the order in which subviews occur in
     the sequence"

    ^ focusSequence
!

focusSequence:aSequenceableCollection
    "define the focus sequence for focusNext/focusPrevious.
     Focus is stepped in the order in which subviews occur in
     the sequence"

    focusSequence := aSequenceableCollection
!

focusView
    "return the view which currently has the focus"

    ^ focusView
!

focusView:aViewOrNil
    "give focus to aViewOrNil"

    focusView == aViewOrNil ifTrue:[^ self].

    focusView notNil ifTrue:[
	"/ lost explicit focus
	focusView == aViewOrNil ifTrue:[^ self].
	focusView showNoFocus:true.
    ] ifFalse:[
	pointerView notNil ifTrue:[
	    pointerView ~~ aViewOrNil ifTrue:[
		"/ lost implicit focus
		pointerView showNoFocus:false
	    ]
	].
    ].

    focusView := aViewOrNil.
    focusView notNil ifTrue:[
	"/ got explicit focus
	focusView showFocus:true.
    ].

    "
     |top v1 v2|

     top := StandardSystemView new.
     v1 := EditTextView origin:0.0@0.0 corner:1.0@0.5 in:top.
     v2 := EditTextView origin:0.0@0.5 corner:1.0@1.0 in:top.
     top open.
     top windowGroup focusView:v1.
    "

    "Modified: 7.2.1996 / 13:02:34 / cg"
! !

!WindowGroup methodsFor:'initialization'!

initialize
    "setup the windowgroup, by creating a new sensor
     and an event semaphore"

    mySensor := WindowSensor new.
    mySensor eventSemaphore:Semaphore new.
    isModal := false.
    isForModalSubview := false.
!

reinitialize
    "reinitialize the windowgroup after an image restart"

    "throw away old (zombie) process"
    myProcess notNil ifTrue:[
	"careful: the old processes exitaction must be cleared
	 otherwise, it might do destroy or other actions when it
	 gets finalized ...
	"
	myProcess exitAction:nil.
	myProcess suspendAction:nil.
	myProcess := nil.
    ].

    "throw away old events"
    mySensor reinitialize

    "Modified: 13.12.1995 / 13:45:35 / stefan"
! !

!WindowGroup methodsFor:'printing'!

printOn:aStream
    "return a printed representation;
     just for more user friendlyness: add name of process."

    myProcess isNil ifTrue:[
	(previousGroup notNil and:[previousGroup process notNil]) ifTrue:[
	    aStream nextPutAll:('WindowGroup(modal in ' , previousGroup process nameOrId , ')').
	    ^ self.
	].
	^ super printOn:aStream
    ].
    aStream nextPutAll:('WindowGroup(' , myProcess nameOrId , ')')
! !

!WindowGroup methodsFor:'special'!

restoreCursors
    "restore the original cursors in all of my views"

    self allViewsDo:[:aView |  
	|c dev id cid|

	dev := aView device.
	dev notNil ifTrue:[
	    (id := aView id) notNil ifTrue:[
		c := aView cursor on:dev.
		(cid := c id) notNil ifTrue:[
		    dev setCursor:cid in:id.
		]
	    ]
	]
    ].
!

showActivity:someMessage
    topViews notNil ifTrue:[
	topViews first showActivity:someMessage
    ]

    "Created: 16.12.1995 / 18:39:40 / cg"
!

showCursor:aCursor
    "change the cursor to aCursor in all of my views."

    |c id dev|

    c := aCursor.
    self allViewsDo:[:aView |  
	c := c on:(dev := aView device).
	(id := c id) notNil ifTrue:[
	    dev setCursor:id in:aView id.
	]
    ].
!

withCursor:aCursor do:aBlock
    "evaluate aBlock while showing aCursor in all
     my views (used to show wait-cursor while doing something).
     Return the result as returned by aBlock."

    |oldCursors dev|

    dev := self device.   
    dev isNil ifTrue:[
	^ aBlock value
    ].

    "
     get mapping of view->cursor for all of my subviews
    "
    oldCursors := IdentityDictionary new.
    self allViewsDo:[:aView |
	oldCursors at:aView put:(aView cursor).
	aView cursor:aCursor now:false
    ].
    "/
    "/ here sync looks better; flush leads to almost invisible cursors when accepting.
    "/ I dont really know why (maybe unix does not context-switch to the Xserver
    "/ early enough after the requests have been sent ?)
    "/
"/    dev flush. 
    dev sync.

    ^ aBlock valueNowOrOnUnwindDo:[
	"
	 restore cursors from the mapping
	"
	oldCursors keysAndValuesDo:[:view :cursor |
	    view cursor:cursor now:false.
	].
	dev flush "/ sync.
    ]

    "Modified: 17.12.1995 / 15:45:49 / cg"
!

withWaitCursorDo:aBlock
    "evaluate aBlock while showing a waitCursor in all
     my views (used to show wait-cursor while doing something time consuming).
     Return the result as returned by aBlock."

    ^ self withCursor:(Cursor wait) do:aBlock

    "Created: 6.2.1996 / 19:51:53 / cg"
! !

!WindowGroup methodsFor:'special accessing'!

isForModalSubview 
    "special for windowgroups for modal subviews.
     These must be flagged specially to avoid the views being reassigned
     to the maingroup.
     This is a private interface to the SimpleView class"

    ^ isForModalSubview
!

isForModalSubview:aBoolean
    "special for windowgroups for modal subviews.
     These must be flagged specially to avoid the views being reassigned
     to the maingroup.
     This is a private interface to the SimpleView class"

    isForModalSubview := aBoolean
!

setModal:aBoolean
    "special entry for debugger: set the modal flag.
     Not for public use"

    isModal := aBoolean

    "Modified: 3.9.1995 / 14:51:04 / claus"
!

setPreviousGroup:aGroup
    "special entry for debugger:
     set the windowgroup that started this group (for modal groups only).
     This is not a public interface."

    previousGroup := aGroup

    "Modified: 3.9.1995 / 14:55:40 / claus"
!

setProcess:aProcess 
    "special entry for debugger: set the windowGroups process.
     Not for public use."

    myProcess := aProcess

    "Modified: 3.9.1995 / 14:25:38 / claus"
! !

!WindowGroup class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/WindowGroup.st,v 1.68 1996-03-05 00:06:44 cg Exp $'
! !
WindowGroup initialize!