StdSysV.st
author Claus Gittinger <cg@exept.de>
Sat, 27 Apr 1996 20:14:40 +0200
changeset 621 decaeae1910d
parent 616 56cf67c82664
child 625 4d8f6dc3af75
permissions -rw-r--r--
examples

"
 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:#StandardSystemView
	instanceVariableNames:'label icon iconView iconLabel minExtent maxExtent sizeFixed
		application windowEventsForApplication'
	classVariableNames:'DefaultIcon TakeFocusWhenMapped IncludeHostNameInLabel'
	poolDictionaries:''
	category:'Views-Basic'
!

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

documentation
"
    I represent topViews i.e. those views which have a title-label,
    an icon etc. 
    In ST/X, StandardSystemViews were subclassed for special views
    in the past (for example: FileBrowser, ChangesBrowser etc.).

    Although this worked, it may lead to the following
    problems and inconveniences:
        - applications inherit a big number of methods through the
          SimpleView->View->TopView->StandardSystemView hierarchy.
          There is quite a danger that by accident, some method gets
          redefined which is required by one of those classes.
          (typical candidates are: terminate, destroy, open ...)
          This may lead to strange effects, which may not be obvious to
          non experts ...

        - applications with multiple topViews are difficult to implement
          and manage.

        - use of a windowBuilder is difficult.

    For all those reasons, we HIGHLY recommend to NOT define applications
    as subclasses of StandardSystemView, but instead base them on
    ApplicationModel, and reference the topView(s) as instance variables of
    if (if at all).

    [instance variables:]
        label                   <String>    the label in the windows title

        icon                    <Form>      the icon
                                            [ignored if the display does not 
                                             support icons]

        iconView                <View>      an optional icon-view (for animated icons)
                                            [ignored if the display does not
                                             supports this]

        iconLabel               <String>    the label in the icon
                                            [ignored if the display does not 
                                             support label-tabs with icons]

        minExtent               <Point>     the minimum size
                                            No limit, if nil
                                            [the window manager may have its own
                                             limit; typically some small area]

        maxExtent               <Point>     the maximum size
                                            No limit, if nil.
                                            [the window manager may have its own
                                             limit; typically the screen size]

        sizeFixed               <Boolean>   prevents the view from resizing itself
                                            (especially to freeze a dialogs size)

        application             <AppModel>  if nonNil, thats the application
                                            Many requests (such as open/close etc.
                                            are forwarded to it, if present.



     [class variables:]

        DefaultIcon             <Form>      cached default icon

        TakeFocusWhenMapped     <Boolean>   if true, views grab the keyboard
                                            focus (convenient with some stupid
                                            windowManagers)

        IncludeHostNameInLabel  <Boolean>   if true, the windows title shall
                                            include the hostname.
                                            (convenient if you have many remote
                                            views open simultaneously)

    [author:]
        Claus Gittinger

    [see also:]
        WindowGroup
        ApplicationModel
"
!

examples
"
    simple, empty topView:
                                                                        [exBegin]
        |topView|

        topView := StandardSystemView new.
        topView label:'my first view'.
        topView extent:200 @ 200.
        topView open.
                                                                        [exEnd]

    with an icon & iconLabel:
                                                                        [exBegin]
        |topView|

        topView := StandardSystemView extent:200 @ 200.
        topView label:'Hello world'.

        topView icon:(Image fromFile:'hello_world.icon').
        topView open.
                                                                        [exEnd]


    with an animated iconView [not supported on all display devices]:
                                                                        [exBegin]
        |iconView topView|

        iconView := ClockView new.

        topView := StandardSystemView extent:200 @ 200.
        topView label:'Hello world'.

        topView iconView:iconView.
        topView open.
                                                                        [exEnd]


    placing a subView into it:
                                                                        [exBegin]
        |topView button|

        topView := StandardSystemView new.
        topView label:'my second view'.
        topView extent:200 @ 200.

        button := Button label:'close' in:topView.
        button action:[topView destroy].

        topView open.
                                                                        [exEnd]

    same, relative sized subview:
                                                                        [exBegin]
        |topView button|

        topView := StandardSystemView new.
        topView label:'my second view'.
        topView extent:200 @ 200.

        button := Button label:'close' in:topView.
        button action:[topView destroy].
        button origin:0.25 @ 0.25 corner:0.75 @ 0.75.

        topView open.
                                                                        [exEnd]

    multiple buttons in a panel in a topView:
                                                                        [exBegin]
        |topView panel button1 button2 button3|

        topView := StandardSystemView new.
        topView label:'my second view'.
        topView extent:200 @ 200.

        panel := HorizontalPanelView origin:0.0@0.0 corner:1.0@1.0 in:topView.
        panel inset:10.
        panel level:-1.

        button1 := Button label:'one' in:panel.
        button1 action:[Transcript showCr:'one pressed'].

        button2 := Button label:'two' in:panel.
        button2 action:[Transcript showCr:'two pressed'].

        button3 := Button label:'three' in:panel.
        button3 action:[Transcript showCr:'three pressed'].

        topView open.
                                                                        [exEnd]
"
! !

!StandardSystemView class methodsFor:'instance creation'!

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
!

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
!

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

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
!

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 defaultControllerClass new view:newView).
    ^ newView
!

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

!StandardSystemView class methodsFor:'defaults'!

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

    DefaultIcon isNil ifTrue:[
	DefaultIcon := Image fromFile:'SmalltalkX.xbm'.
	DefaultIcon notNil ifTrue:[
	    DefaultIcon := DefaultIcon on:Display
	]
    ].
    ^ DefaultIcon
!

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

    ^ 'aView'
!

includeHostNameInLabel
    "return the flag which controls if a views label should
     include the hostname.
     This flag is usually set/cleared in your private.rc file;
     the default is false."

    ^ IncludeHostNameInLabel

    "Created: 10.9.1995 / 19:21:16 / claus"
!

includeHostNameInLabel:aBoolean
    "set/clear the flag which controls if a views label should
     include the hostname - this is highly useful if you have 
     multiple smalltalks open simultaneously ...
     This flag is usually set/cleared in your private.rc file;
     the default is false."

    IncludeHostNameInLabel := aBoolean

    "Modified: 24.4.1996 / 09:09:21 / cg"
! !

!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 methodsFor:'accessing'!

application
    "return the topViews application.
     This is new protocol for ST-80 compatibility and not yet fully supported"

    ^ application
!

application:anApplicationModel
    "set the topViews application.
     This is new protocol for ST-80 compatibility and not yet fully supported"

    application := anApplicationModel.
    anApplicationModel notNil ifTrue:[
        anApplicationModel window isNil ifTrue:[
            anApplicationModel window:self
        ]
    ]

    "Modified: 18.4.1996 / 14:55:44 / cg"
!

bePartner
    "define me as a partner-View.
     All partners within the applications windowGroup iconify/deiconify together."

    self setWindowGroupFromApplication.
    super bePartner.

    "
     see example in TopView>>bePartner
    "

    "Created: 22.9.1995 / 17:40:15 / claus"
    "Modified: 6.3.1996 / 16:16:42 / cg"
!

beSlave
    "define me as a slave-View.
     All slaves within the applications windowGroup iconify/deiconify with the masterView(s)"

    self setWindowGroupFromApplication.
    super beSlave.

    "
     see example in TopView>>beSlave
    "

    "Created: 22.9.1995 / 17:40:15 / claus"
    "Modified: 6.3.1996 / 16:16:50 / cg"
!

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

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

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

    self iconLabel:aString
!

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.
        aView setRealized:true.
    ]

    "Modified: 24.4.1996 / 10:30:12 / cg"
!

label
    "return the views name in the title area"

    ^ label
!

label:aString
    "define the views name in the windows title area.
     If IncludeHostNameInLabel is true, prepend the hostname
     (you will appreciate this, if you are working on multiple
      machines simultaneously - as I do ...)"

    |l|

    aString ~= label ifTrue:[
        label := aString.
        drawableId notNil ifTrue: [
            IncludeHostNameInLabel == true ifTrue:[
                l := OperatingSystem getHostName , ': ' , aString.
            ] ifFalse:[
                l := aString
            ].
            device setWindowName:l in:drawableId.
            "
             unbuffered - to make it visible right NOW
            "
            device flush.
        ]
    ]

    "Created: 8.9.1995 / 19:37:06 / claus"
    "Modified: 8.9.1995 / 19:39:18 / claus"
    "Modified: 24.4.1996 / 09:09:17 / cg"
!

label:labelString iconLabel:iconLabelString
    "set both the label and the iconLabel"

    self label:labelString.
    self iconLabel:iconLabelString
!

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

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

    ^ self maxExtent: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
	]
    ]
!

minimumSize
    "same as minExtent for ST-80 compatibility"

    ^ self minExtent
!

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

    ^ self minExtent:anExtent
!

name
    "return the topViews label"

    ^ label
!

sizeFixed:aBoolean
    "this prevents the view from resizing itself when realized.
     For normal topViews, this is void, since they dont do this anyway.

     However, modalBoxes (especially: DialogBoxes) typically resize themselfes 
     to the preferredExtent of their components. In some cases, this behavior is 
     not desired and it should be turned off by setting sizeFixed to true.

     To avoid confusion:
	This does NOT prevent the window manager from resizing the view, 
	instead it tells the view to NOT resize ITSELF."

    sizeFixed := aBoolean.

    "example: dialog which resizes itself on #open: 
	      (thereby ignoring the 200@200 extent)

	|dialog|

	dialog := Dialog new.
	dialog addInputFieldOn:'' asValue.
	dialog addOkButton.
	dialog extent:200@200.
	dialog open.


    using sizeFixed:

	|dialog|

	dialog := Dialog new.
	dialog addInputFieldOn:'' asValue.
	dialog addOkButton.
	dialog extent:200@200; sizeFixed:true.
	dialog open.


    using openWithExtent (also sets sizeFixed):

	|dialog|

	dialog := Dialog new.
	dialog addInputFieldOn:'' asValue.
	dialog addOkButton.
	dialog openWithExtent:200@200.
    "
! !

!StandardSystemView methodsFor:'destroying'!

closeRequest 
    "programmatic close request"

    ^ self terminate
!

destroy
    "destroy the view."

    self removeFromCurrentProject.
    windowGroup notNil ifTrue:[
	windowGroup focusSequence:nil.
    ].
    application notNil ifTrue:[
	application windowEvent:(#close -> self) from:self
    ].
    super destroy.
!

saveAndTerminate
    "save & terminate request from the windowManager. The application should 
     save its data/files/text etc. somehow and close.
     If there is an application, let it decide how do do that.
     Otherwise, forward it to superclasses which knows how to do this.
     (it defaults to a terminate there).
     Notice, that not all windowmanagers are nice enough
     to send this request; some simply distroy the view."

    application notNil ifTrue:[
	application saveAndTerminateRequest
    ] ifFalse:[
	super saveAndTerminate
    ]
!

terminate
    "terminate request from the windowManager. If there is an application,
     let it decide if it really wants to be close. Otherwise, forward it to
     superclasses terminate which knows how to do this.
     Notice, that not all windowmanagers are nice enough
     to send this request; some simply distroy the view."

    application notNil ifTrue:[
	application closeRequest
    ] ifFalse:[
	super terminate
    ]
! !

!StandardSystemView methodsFor:'event handling'!

focusIn
    "the view got the keyboard focus (via the window manager)"

    |v|

    windowGroup notNil ifTrue:[
	(v := windowGroup focusView) notNil ifTrue:[
	    v showFocus:false.
	    ^ self
	]
    ].
    delegate notNil ifTrue:[
	delegate showFocus:false.
    ]
!

focusOut
    "the view lost keyboard focus (via the window manager)"

    |v|

    windowGroup notNil ifTrue:[
	(v := windowGroup focusView) notNil ifTrue:[
	    v showNoFocus:false.
	    ^ self
	]
    ].
    delegate notNil ifTrue:[
	delegate showNoFocus:false.
    ]
!

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

sendWindowEvents:collectionOfEventSymbols
    "define the events that are to be forwarded to the application.
     This is being implemented ..."

    windowEventsForApplication := collectionOfEventSymbols
!

showActivity:someMessage
    "some activityNotification shalt be communicated to
     the user. Forward it to my application (if any).
     (that one should know how to deal with it).
     Otherwise, simply ignore it."

    application notNil ifTrue:[
        application showActivity:someMessage
    ]

    "Created: 16.12.1995 / 18:40:44 / cg"
    "Modified: 23.4.1996 / 21:38:11 / cg"
! !

!StandardSystemView methodsFor:'initialization'!

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

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

    ^ nil "/ StandardSystemController
!

initEvents
    super initEvents.
    self enableFocusEvents.
!

initialize
    super initialize.

    borderWidth := 2.         "- notice: many window managers ignore this"
    minExtent := 10 @ 10.
    maxExtent := (device width) @ (device height).
    label isNil ifTrue:[label := self class defaultLabel].
    icon isNil ifTrue:[icon := self class defaultIcon].
    name := self class name.
!

reAdjustGeometry
    "sent as a final step when an image is restarted.
     when we come up on a smaller display, 
     make certain, that the receiver is visible"

    |dX dY limitRight limitBottom|

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

    limitRight := device width - dX.
    limitBottom := device height - dY.
    ((self left > limitRight) or:[
      self top > limitBottom]) ifTrue:[
        'STDSYSVIEW: moving view into visible area' infoPrintNL.
        self origin:limitRight @ limitBottom
    ]

    "Modified: 7.3.1996 / 19:29:12 / cg"
!

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
!

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

restarted
    "sent by my windowGroup, when restarted from an image.
     Nothing done here, but can be redefined to perform any actions
     required to reset the application after an image-restart.
     (for example: check if application files are still around, restart
     subprocesses etc.)."

    application notNil ifTrue:[
	application restarted
    ].
! !

!StandardSystemView methodsFor:'printing & storing'!

displayString
    "just for your convenience in inspectors ...
     ... add the views label to the displayString."

    |s|

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

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

setWindowGroupFromApplication
    "get the applications topView and set my windowGroup to its wg."

    |win|

    windowGroup isNil ifTrue:[
        application notNil ifTrue:[
            (win := application window) notNil ifTrue:[
                windowGroup := win windowGroup.
            ]
        ]
    ].

    "Created: 22.9.1995 / 17:40:36 / claus"
    "Modified: 6.3.1996 / 16:17:32 / cg"
! !

!StandardSystemView methodsFor:'queries'!

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 either redefine
     this method and return a collection of (sub-) views.
     Or, if the model is some applicationModel, it may itself define
     the focusSequence.
     Or, somehow let me (via focusSequence:) know about the order.

     Notice: I dont think this is good style: the focusSequence seems
     to belong into the controller, ..."

    "/
    "/ if I have an application, its supposed to
    "/ know about the focusSequence
    "/
    application notNil ifTrue:[
        ^ application focusSequence
    ].

    (model notNil
    and:[(model respondsTo:#focusSequence)
    and:[model ~~ self]]) ifTrue:[
        ^ model focusSequence
    ].
    ^ nil

    "Modified: 6.3.1996 / 16:14:20 / cg"
!

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

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

    "Created: 10.12.1995 / 13:11:17 / cg"
    "Modified: 24.4.1996 / 09:46:31 / cg"
!

processName
    "return a string to be shown for my process in the
     process monitor. This has no semantic meaning, but exists
     for your convenience only."

    application notNil ifTrue:[
        ^ application processName
    ].
    label notNil ifTrue:[^ label].
    ^ super processName

    "Modified: 24.4.1996 / 09:47:01 / cg"
! !

!StandardSystemView methodsFor:'realization'!

create
    "create - make certain that icon is available"

    icon := self convertedIcon.
    super create.

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

    "Modified: 24.4.1996 / 10:29:53 / cg"
!

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

    self open.
    windowGroup process priority:aPriority.
!

physicalCreate
    "common code for create & recreate"

    |l|

    IncludeHostNameInLabel == true ifTrue:[
	l := OperatingSystem getHostName , ': ' , label.
    ] ifFalse:[
	l := label
    ].

    drawableId := device 
		      createWindowFor:self 
		      origin:(left @ top)
		      extent:(width @ height)
		      minExtent:minExtent
		      maxExtent:maxExtent
		      borderWidth:borderWidth
		      subViewOf:nil 
		      onTop:(self isPopUpView)
		      inputOnly:(self inputOnly)
		      label:l
		      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
    ].
!

realize
    "realize the view i.e. make it visible."

    super realize.
    windowGroup notNil ifTrue:[
        "/
        "/ have to wait till now with focus-setting, 
        "/ up to now, I may have had no windowGroup (its set in realize)
        "/
        "/
        "/ no longer donw here - wg asks for the sequence
"/        windowGroup focusSequence:self focusSequence.

        "/
        "/ let the application add its views to the current project
        "/
        application notNil ifTrue:[
            application opened.
        ] ifFalse:[
            self addToCurrentProject.
        ].
    ]

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

recreate
    "recreate the view after a snap-in"

    icon := self convertedIcon.
    super recreate.

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

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

    "Modified: 24.4.1996 / 10:30:04 / cg"
! !

!StandardSystemView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Attic/StdSysV.st,v 1.48 1996-04-27 18:14:07 cg Exp $'
! !