TopView.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Mar 1996 13:54:42 +0100
changeset 510 c0c7a04317a9
parent 501 0a701f42de02
child 586 b91f10f632d5
permissions -rw-r--r--
resources

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

View subclass:#TopView
	instanceVariableNames:'type'
	classVariableNames:''
	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.
"
! !

!TopView class methodsFor:'defaults'!

defaultExtent
    "topviews extent is (0.6 @ 0.6) of screen by default"

    |display|

    display := Screen current.
    ^ (display width // 3 * 2) @ (display height // 3 * 2)
! !

!TopView methodsFor:'accessing & queries'!

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

    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:'top1'; extent:300@300.
     top2 := StandardSystemView new label:'top2'; extent:200@200.
     top1 bePartner.
     top2 bePartner.

     top1 open.
     top2 openInGroup:(top1 windowGroup)
    "

    "Created: 10.12.1995 / 13:29:59 / cg"
!

beSlave
    "make this a slave-view. It will be closed automatically,
     whenever any master of the group is closed."

    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:'top1'; extent:300@300.
     top2 := StandardSystemView new label:'top2'; extent:200@200.
     top1 beMaster.
     top2 beSlave.

     top1 open.
     top2 openInGroup:(top1 windowGroup)
    "

    "Created: 10.12.1995 / 13:29:10 / cg"
!

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

    "Created: 6.3.1996 / 15:37:11 / cg"
    "Modified: 6.3.1996 / 15:37:38 / cg"
!

heightIncludingBorder
    "return the views overall-height"

    ^ height
!

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

    ^ shown not
!

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

    ^ self class defaultExtent
!

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

    ^ type
!

widthIncludingBorder
    "return the views overall-width"

    ^ width
! !

!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 ) >

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

    "Created: 1.2.1996 / 22:08:30 / cg"
    "Modified: 7.3.1996 / 13:19:35 / cg"
! !

!TopView methodsFor:'initialization'!

initialize
    "initialize the topViews position for the screens center"

    |screenCenter|

    super initialize.

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

!TopView methodsFor:'misc'!

raiseDeiconified
    "deiconify & bring to front"

    self isCollapsed ifTrue:[
	self unrealize.
	self realize.
    ].
    self raise

    "
     Transcript topView raiseDeiconified
    "
!

showActivity:someMessage
    "default for activity notifications: ignore them"

    ^ self

    "Created: 16.12.1995 / 18:40:13 / 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:'startup'!

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

!TopView methodsFor:'window events'!

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

    |wg|

    wg := windowGroup.                  "/ have to fetch windowGroup before;
    super destroy.                      "/ since destroy nils it

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

"/    wg notNil ifTrue:[
"/        "/
"/        "/ if I am a master or partner, close all slaves
"/        "/
"/        (type == #master or:[type == #partner]) ifTrue:[
"/            wg slavesDo:[:v | v destroy].
"/        ].
"/        "/
"/        "/ if I am a partner, close all partners
"/        "/
"/        type == #partner ifTrue:[
"/            wg partnersDo:[:v | v ~~ self ifTrue:[v destroy]].
"/        ].
"/    ].
!

mapped
    "the recevier was mapped (i.e. deiconified or just created);
     look for partners and slaves."

    realized := true.
    super mapped.

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

"/    windowGroup notNil ifTrue:[
"/        (type == #master or:[type == #partner]) ifTrue:[
"/            windowGroup slavesDo:[:v | v rerealize].
"/        ].
"/        type == #partner ifTrue:[
"/            windowGroup partnersDo:[:v | v ~~ self ifTrue:[v rerealize]].
"/        ]
"/    ].
!

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

    super unmapped.

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

"/    windowGroup notNil ifTrue:[
"/        (type == #master or:[type == #partner]) ifTrue:[
"/            windowGroup slavesDo:[:v | v unrealize].
"/        ].
"/        type == #partner ifTrue:[
"/            windowGroup partnersDo:[:v | v ~~ self ifTrue:[v unrealize]].
"/        ].
"/    ].
! !

!TopView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.17 1996-03-07 12:53:47 cg Exp $'
! !