StandardSystemView.st
author claus
Mon, 06 Feb 1995 01:38:04 +0100
changeset 89 ea2bf46eb669
parent 82 98a70bce6d51
child 94 8931597dfa3c
permissions -rw-r--r--
*** empty log message ***

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

View subclass:#StandardSystemView
       instanceVariableNames:'label icon iconView iconLabel
			      minExtent maxExtent'
       classVariableNames:   'DefaultIcon TakeFocusWhenMapped'
       poolDictionaries:''
       category:'Views-Basic'
!

StandardSystemView comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/StandardSystemView.st,v 1.15 1995-02-06 00:37:53 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview/StandardSystemView.st,v 1.15 1995-02-06 00:37:53 claus Exp $
"
!

documentation
"
    I represent topViews i.e. those views which have a title-label,
    an icon etc. Usually StandardSystemViews are subclassed for
    special views.
"
! !

!StandardSystemView class methodsFor:'defaults'!

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

    ^ (Display width // 3 * 2) @ (Display height // 3 * 2)
!

defaultLabel
    "return the default label for views of my kind.
     This can be redefined in subclasses or overwritten in
     initialize methods."

    ^ 'aView'
!

defaultIcon
    "return the default icon for views.
     This can be redefined in subclasses or overwritten in
     initialize methods."

    DefaultIcon isNil ifTrue:[
	DefaultIcon := Image fromFile:'bitmaps/SmalltalkX.xbm'
    ].
    ^ DefaultIcon
! !

!StandardSystemView class methodsFor:'startup'!

open
    "create, realize the view - this topview and all its subviews will
     run as a separate process with its own windowGroup"

    ^ self new open 
!

start
    "create, realize the view - this topview and all its subviews will
     run as a separate process with its own windowGroup.
     This method exists for backward compatibility - use open."

    ^ self open
! !

!StandardSystemView class methodsFor:'instance creation'!

model:aModel label:aLabel minimumSize:minExtent
    "ST80-style instance creation"

    |newView|

    newView := self origin:nil 
		    extent:minExtent
		     label:aLabel 
		      icon:nil
		 minExtent:minExtent
		 maxExtent:nil.
    newView model:aModel.
"/    newView controller:(self defaultController new view:newView).
    ^ newView
!

label:aLabel
    "create a new topView and define its label"

    ^ self origin:nil extent:nil
	   label:aLabel icon:nil
	   minExtent:nil maxExtent:nil
!

label:aLabel minExtent:anExtent
    "create a new topView and define its label and minimum extent"

    ^ self origin:nil extent:nil
	   label:aLabel icon:nil
	   minExtent:anExtent maxExtent:nil
!

label:aLabel icon:aForm
    "create a new topView and define its label and icon"

    ^ self origin:nil extent:nil
	   label:aLabel icon:aForm
	   minExtent:nil maxExtent:nil
!

label:aLabel icon:aForm minExtent:anExtent
    "create a new topView and define its label, icon and minumum extent"

    ^ self origin:nil extent:nil
	   label:aLabel icon:aForm
	   minExtent:anExtent maxExtent:nil
!

label:aLabel icon:aForm minExtent:minExtent maxExtent:maxExtent
    "create a new topView and define its label, icon, min and max extents"

    ^ self origin:nil extent:nil
	   label:aLabel icon:aForm
	   minExtent:minExtent maxExtent:maxExtent
!

origin:anOrigin extent:anExtent label:aLabel
    "create a new topView and define its origin, extent and label"

    ^ self origin:anOrigin extent:anExtent
	   label:aLabel icon:nil
	   minExtent:nil maxExtent:nil
!

origin:anOrigin label:aLabel icon:aForm
		minExtent:minExtent maxExtent:maxExtent
    "create a new topView and define its origin, extent, label, icon
     and extent-boundaries."

    ^ self origin:anOrigin extent:nil
	   label:aLabel icon:aForm
	   minExtent:minExtent maxExtent:maxExtent
!

extent:anExtent label:aLabel minExtent:minExtent
    "create a new topView and define its extent, label and minumum extent"

    ^ self origin:nil extent:anExtent
	   label:aLabel icon:nil
	   minExtent:minExtent maxExtent:nil
!

extent:anExtent label:aLabel icon:aForm
    "create a new topView and define its extent, label and icon"

    ^ self origin:nil extent:anExtent
	   label:aLabel icon:aForm
	   minExtent:nil maxExtent:nil
!

extent:anExtent label:aLabel icon:aForm minExtent:minExtent
    ^ self origin:nil extent:anExtent
	   label:aLabel icon:aForm
	   minExtent:minExtent maxExtent:nil
!

extent:anExtent label:aLabel icon:aForm minExtent:minExtent maxExtent:maxExtent
    ^ self origin:nil extent:anExtent
	   label:aLabel icon:aForm
	   minExtent:minExtent maxExtent:maxExtent
! !

!StandardSystemView methodsFor:'initialization'!

initialize
    |screenCenter|

    super initialize.

    self addToCurrentProject.

    screenCenter := device center.
    left := screenCenter x - (width // 2).
    top := screenCenter y - (height // 2).
    borderWidth := 2.         "- notice: many window managers ignore this"
    label := self class defaultLabel.
    minExtent := 10 @ 10.
    maxExtent := (device width) @ (device height).
    icon := self class defaultIcon.
    name := self class name.
!

initEvents
    super initEvents.
    self enableFocusEvents.
!

defaultController
    "for ST-80 compatibility only - not used in ST/X"

    ^ nil "/ StandardSystemController
!

addToCurrentProject
    "add the receiver (a topview) to the current projects set-of-views.
     (If there is a current project)"

    |p|

    "
     the following check allows systems
     without projects and changeSets
    "
    (Project notNil and:[(p := Project current) notNil]) ifTrue:[
	p addView: self
    ]
!

removeFromCurrentProject
    "remove the receiver (a topview) from the current projects set-of-views.
     (If there is a current project)"

    |p|

    "
     the following check allows systems
     without projects and changeSets
    "
    (Project notNil and:[(p := Project current) notNil]) ifTrue:[
	p removeView:self
    ]
!

reinitialize
    "reopen the receiver if if was visible before.
     This is called right after snapIn; Notice, that all instance variables
     (such as shown, realized etc.) are left-overs from the time the snapout
     was done. Remap the receiver, if it was mapped at snapout time"

    |myController|

    "if I have already been reinited - return"
    drawableId notNil ifTrue:[
	^ self
    ].

    "have to kludge with the controller 
     - otherwise its startup performs unwanted actions ..."

    myController := controller.
    controller := nil.

    "physically create the view & subviews"
    self recreate.

    "if I was mapped, do it again"
    realized ifTrue:[
	"if it was iconified, try to remap iconified"
	device mapView:self id:drawableId iconified:(shown not) 
		   atX:left y:top width:width height:height.

	"and restart the window-group process"
	windowGroup notNil ifTrue:[
	    windowGroup restart
	]
    ].

    "restore controller"
    controller := myController
!

recreate
    "recreate the view after a snap-in"

    icon := self convertedIcon.
    super recreate.

    iconView notNil ifTrue:[
	iconView create.
	device setWindowIconWindow:iconView in:drawableId
    ] ifFalse:[
	(icon notNil and:[icon id notNil]) ifTrue:[
	    device setWindowIcon:icon in:drawableId
	].
    ].

    iconLabel notNil ifTrue:[
	device setIconName:iconLabel in:drawableId
    ]
!

reAdjustGeometry
    "when we come up on a smaller display, 
     make certain, that the receiver is visible"

    |dX dY|

    dX := (device horizontalPixelPerMillimeter * 20) rounded.
    dY := (device verticalPixelPerMillimeter * 20) rounded.

    ((self left > (device width - dX)) or:[
      self top > (device height - dY)]) ifTrue:[
	'moving view into visible area' errorPrintNewline.
	self origin:(device width - dX) @ (device height - dY)
    ]
!

realize
    super realize.
    windowGroup notNil ifTrue:[
	windowGroup focusSequence:(self focusSequence)
    ]
!

focusSequence
    "return a sequence which defines the order in which the focus
     is passed for FocusNext and FocusPrevious keys.
     All views which like to support these keys should redefine
     this method and return a collection of (sub-) views"

    ^ nil

! !

!StandardSystemView methodsFor:'destroying'!

destroy
    super destroy.
    self removeFromCurrentProject
! !

!StandardSystemView methodsFor:'private'!

convertedIcon
    "make certain, that the icon is a b&w bitmap;
     do so by converting if required.
     Will add a device supportsDeepIcons and only convert when needed;
     for now, we always have to convert (since there are only Xdisplays)."

    |deviceIcon|

    icon isNil ifTrue:[^ nil].

    device supportsDeepIcons ifFalse:[
	icon depth ~~ 1 ifTrue:[
	    "
	     dither to monochrome
	    "
	    deviceIcon := icon asMonochromeFormOn:device.
	] ifFalse:[
	    deviceIcon := icon
	]
    ].
    deviceIcon notNil ifTrue:[
	"
	 get device pixmap (i.e. allocate colors & resource)
	"
	deviceIcon := deviceIcon on:device
    ].
    ^ deviceIcon
! !

!StandardSystemView methodsFor:'realization'!

physicalCreate
    "common code for create & recreate"

    drawableId := device 
		      createWindowFor:self 
		      origin:(left @ top)
		      extent:(width @ height)
		      minExtent:minExtent
		      maxExtent:maxExtent
		      borderWidth:borderWidth
		      subViewOf:nil 
		      onTop:(self createOnTop)
		      inputOnly:(self inputOnly)
		      label:label
		      cursor:cursor
		      icon:icon
		      iconView:iconView.

    extentChanged := false.
    originChanged := false.

    (borderColor notNil and:[borderColor ~~ Black]) ifTrue:[
	borderColor := borderColor on:device.
	self setBorderColor
    ].

"/  (viewGravity notNil "and:[viewGravity ~~ #NorthWest]") ifTrue:[
"/        device setWindowGravity:viewGravity in:drawableId
"/  ].

"/  (bitGravity notNil "and:[bitGravity ~~ #NorthWest]") ifTrue:[
"/      device setBitGravity:bitGravity in:drawableId
"/  ].

    borderShape notNil ifTrue:[
	device setWindowBorderShape:(borderShape id) in:drawableId
    ].
    viewShape notNil ifTrue:[
	device setWindowShape:(viewShape id) in:drawableId
    ].
    (backed notNil and:[backed ~~ false]) ifTrue:[
	device setBackingStore:backed in:drawableId
    ].
    saveUnder ifTrue:[
	device setSaveUnder:true in:drawableId
    ].
!

create
    "create - make certain that icon is available"

    icon := self convertedIcon.
    super create.

    iconView notNil ifTrue:[
	iconView create.
	device setWindowIconWindow:iconView in:drawableId
    ].
    iconLabel notNil ifTrue:[
	device setIconName:iconLabel in:drawableId
    ]
!

openWithExtent:anExtent
    "set extent and open - for ST-80 compatibility"

    self extent:anExtent.
    self open
! !

!StandardSystemView methodsFor:'misc'!

withWaitCursorDo:aBlock
    "evaluate aBlock while showing a waitCursor in all my views"

    self withCursor:(Cursor wait) do:aBlock
!

withCursor:aCursor do:aBlock
    "evaluate aBlock while showing aCursor in all my views"

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

!StandardSystemView methodsFor:'printing & storing'!

displayString
    "just for your convenience in inspectors ..."

    |s|

    s := super displayString.
    label isNil ifTrue:[
	s := s , '(' , label , ')'
    ].
    ^ s
! !

!StandardSystemView methodsFor:'accessing'!

preferedExtent
    "return my preferred extent - this is the minimum size I would like to have.
     The default here is the classes default extent."

    ^ self class defaultExtent
!

heightIncludingBorder
    "return the views overall-height"

    ^ height
!

widthIncludingBorder
    "return the views overall-width"

    ^ width
!

label
    "return the views name in the title area"

    ^ label
!

label:aString
    "define the views name in the windows title area"

    label := aString.
    drawableId notNil ifTrue: [
	device setWindowName:aString in:drawableId.
	"
	 unbuffered - to make it visible right NOW
	"
	device synchronizeOutput.
    ]
!

iconLabel
    "return the name displayed in the icon"

    ^ iconLabel
!

iconLabel:aString
    "define the name to be displayed in the icon"

    iconLabel := aString.
    drawableId notNil ifTrue:[
	device setIconName:aString in:drawableId.
	"
	 unbuffered - to make it visible right NOW
	"
	device synchronizeOutput.
    ]
!

name
    "return the topViews label"

    ^ label
!

icon
    "return the form defined as icon"

    ^ icon
!

icon:aForm
    "define the form (bitmap) used as icon"

    |invertedIcon i|

    icon := aForm.
    icon notNil ifTrue:[
	drawableId notNil ifTrue:[
	    icon depth ~~ 1 ifTrue:[
		icon := icon asMonochromeFormOn:device.
	    ].
	    "icons assume 1s as black - invert icon if the device thinks different"
	    (device depth == 1 and:[device whitepixel ~~ 0]) ifTrue:[
		i := icon on:device.
		i notNil ifTrue:[
		    invertedIcon := Form width:icon width height:icon height on:device.
		    invertedIcon function:#copy.
		    invertedIcon foreground:Color noColor background:Color allColor.
		    invertedIcon copyFrom:i x:0 y:0 toX:0 y:0 width:icon width height:icon height.
		    i := invertedIcon.
		]
	    ] ifFalse:[
		i := icon on:device.
	    ].
	    (i notNil and:[i id notNil]) ifTrue:[
		device setWindowIcon:i in:drawableId
	    ]
	]
    ]
!

iconView
    "return the view used as icon-view"

    ^ iconView
!

iconView:aView
    "specify the view to be used as icon"

    iconView := aView.
    drawableId notNil ifTrue:[
	aView create.
	device setWindowIconWindow:aView in:drawableId
    ]
!

iconName:aString
    "this method will vanish soon ... - for backward compatibility"

    self iconLabel:aString
!

maximumSize:anExtent
    "same as maxExtent: for ST-80 compatibility"

    ^ self maxExtent:anExtent
!

minimumSize:anExtent
    "same as minExtent: for ST-80 compatibility"

    ^ self minExtent:anExtent
!

minExtent
    "return the views minimum allowed extent"

    ^ minExtent
!

minExtent:min
    "define the minimum extent the view may have -
     depends on good-will of window manager"

    minExtent := min.
    (width notNil and:[height notNil]) ifTrue:[
	((width < (minExtent x)) or:
	 [height < (minExtent y)]) ifTrue: [
	    self extent:minExtent
	]
    ]
!

maxExtent
    "return the views maximum allowed extent"

    ^ maxExtent
!

maxExtent:max
    "define the maximum extent the view may have -
     depends on good-will of window manager"

    maxExtent := max.
    (width notNil and:[height notNil]) ifTrue:[
	((width > (maxExtent x)) or:
	 [height > (maxExtent y)]) ifTrue: [
	    self extent:maxExtent
	]
    ]
! !

!StandardSystemView methodsFor:'event handling'!

focusOut
    "the view lost keyboard focus"

    |v|

    windowGroup notNil ifTrue:[
	(v := windowGroup focusView) notNil ifTrue:[
	    v showNoFocus
	]
    ].
!

focusIn
    "the view got the keyboard focus"

    |v|

    windowGroup notNil ifTrue:[
	(v := windowGroup focusView) notNil ifTrue:[
	    v showFocus
	]
    ].
!

mapped
    "the view got mapped"

    super mapped.
    "
     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.
    ]
! !