SystemStatusMonitor.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 29 Jan 2012 12:53:39 +0000
branchjv
changeset 12123 4bde08cebd48
parent 6157 333cde2a5ec7
child 12125 0c49a3b13e43
permissions -rw-r--r--
trunk branched into /branches/jv

"
 COPYRIGHT (c) 1997 by eXept Software AG
              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:libtool' }"

SimpleView subclass:#SystemStatusMonitor
	instanceVariableNames:'listView listUpdateDelay updateDelay updateBlock listUpdateBlock
		updateProcess'
	classVariableNames:''
	poolDictionaries:''
	category:'Monitors-ST/X'
!

!SystemStatusMonitor class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG
              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.
"
! !

!SystemStatusMonitor class methodsFor:'defaults'!

defaultIcon
    ^ StandardSystemView defaultIcon

    "Created: 23.1.1997 / 02:52:25 / cg"
!

defaultLabel
    ^ 'Status Monitor'

    "Created: 23.1.1997 / 02:52:43 / cg"
! !

!SystemStatusMonitor class methodsFor:'startup'!

isVisualStartable
    "return true, if this application can be started via #open.
     (to allow start of a change browser via double-click in the browser)"

    ^ self ~~ SystemStatusMonitor

    "Created: / 10.8.1998 / 16:02:23 / cg"
    "Modified: / 10.8.1998 / 16:02:41 / cg"
!

open
    |top monitor|

    top := StandardSystemView new.
    monitor := self origin:0.0@0.0 corner:1.0@1.0 in:top.
    top extent:monitor preferredExtent.
    top label:self defaultLabel.
    top icon:self defaultIcon.
    top open.

    ^ monitor

    "
     ProcessMonitor open
    "

    "Created: 23.1.1997 / 02:53:42 / cg"
! !

!SystemStatusMonitor methodsFor:'destroying'!

release
    updateBlock notNil ifTrue:[
        Processor removeTimedBlock:updateBlock.
        updateBlock := nil.
    ].
    listUpdateBlock notNil ifTrue:[
        Processor removeTimedBlock:listUpdateBlock.
        listUpdateBlock := nil.
    ].
    updateProcess notNil ifTrue:[
        updateProcess terminate.
        updateProcess := nil.
    ].
    super release

    "Created: 23.1.1997 / 02:26:50 / cg"
! !

!SystemStatusMonitor methodsFor:'drawing'!

updateList
    self subclassResponsibility
!

updateStatus:arg
    self subclassResponsibility
!

updateView
    self updateList.
    self updateStatus:nil

    "Created: / 23.1.1997 / 02:27:05 / cg"
    "Modified: / 14.12.1999 / 20:47:37 / cg"
! !

!SystemStatusMonitor methodsFor:'events'!

canHandle:key
    ^ key == #InspectIt

    "Created: 23.1.1997 / 02:27:15 / cg"
!

keyPress:key x:x y:y
    <resource: #keyboard ( #InspectIt ) >

    key == #InspectIt ifTrue:[
	^ self inspectSelection.
    ].
    ^ super keyPress:key x:x y:y

    "Modified: 23.1.1997 / 02:27:27 / cg"
    "Created: 23.1.1997 / 02:27:45 / cg"
! !

!SystemStatusMonitor methodsFor:'initialization'!

initialize
    |v|

    super initialize.

    v := HVScrollableView for:SelectionInListView miniScrollerH:true in:self.
    v origin:0.0@0.0 corner:1.0@1.0.

    listView := v scrolledView.
    listView font:(EditTextView defaultFont).
    listView menuHolder:self; menuPerformer:self; menuMessage:#statusMenu. 

    listView multipleSelectOk:true.
    "/ listView toggleSelect:true.
    listView delegate:(KeyboardForwarder toView:self).
    listView doubleClickAction:[:line | self doubleClicked].

    updateDelay := 0.5.
    listUpdateDelay := 5.

    "/ event mode is no longer used;
    "/ this event support may vanish
    Processor isPureEventDriven ifTrue:[
        updateBlock := [self updateStatus:nil].
        listUpdateBlock := [self updateList].
    ].

    "
     ProcessMonitor open
    "

    "Modified: / 14.12.1999 / 20:47:57 / cg"
!

mapped
    super mapped.
    self updateStatus:nil.
    self updateList.

    "Created: / 23.1.1997 / 02:30:05 / cg"
    "Modified: / 14.12.1999 / 20:47:54 / cg"
!

realize
    super realize.

    self startUpdateProcess.

    "Created: 23.1.1997 / 02:30:28 / cg"
!

reinitialize
    updateProcess := nil.
    super reinitialize.
    self startUpdateProcess.

    "Modified: 22.12.1995 / 22:51:14 / cg"
    "Created: 23.1.1997 / 02:30:43 / cg"
!

startUpdateProcess
    updateBlock notNil ifTrue:[
        Processor addTimedBlock:updateBlock afterSeconds:updateDelay.
        Processor addTimedBlock:listUpdateBlock afterSeconds:listUpdateDelay.
    ] ifFalse:[
        updateProcess := [
            [
                |id cnt myDelay|

                myDelay := Delay forSeconds:updateDelay.

                "
                 every updateDelay (0.5), we look which process runs;
                 every half second, the status is updated.
                 every listUpdateDelay (5s), the list of processes is
                 built up again
                "
                [true] whileTrue:[
                    ((listUpdateDelay // updateDelay) max:2) - 1 timesRepeat:[
                        myDelay wait.
                        self updateStatus:nil.
                    ].
                    myDelay wait.
                    self updateList.
                ]
            ] ifCurtailed:[
                updateProcess := nil
            ]
        ]  forkAt:(Processor userSchedulingPriority + 1).
        updateProcess name:'monitor [' , 
                           Processor activeProcess id printString ,
                           '] update'.
        "
         raise my own priority
        "
        Processor activeProcess priority:(Processor userSchedulingPriority + 2)
    ].

    "Created: / 23.1.1997 / 02:30:58 / cg"
    "Modified: / 14.12.1999 / 20:47:50 / cg"
! !

!SystemStatusMonitor methodsFor:'queries'!

preferredExtent
    "return my preferred extent"

    ^ (font widthOf:self titleLine) + 40 @ 200

    "Modified: 23.1.1997 / 02:35:01 / cg"
    "Created: 23.1.1997 / 02:51:24 / cg"
! !

!SystemStatusMonitor class methodsFor:'documentation'!

version
    ^ '$Id: SystemStatusMonitor.st 7810 2011-08-12 14:54:02Z vranyj1 $'
! !