SystemStatusMonitor.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Aug 1997 16:30:22 +0200
changeset 1273 3a8a91e6c5fa
parent 1053 9b1b15ef1e34
child 1806 c596b8441e25
permissions -rw-r--r--
give my listView a fixed font.

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


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

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

    "
     ProcessMonitor open
    "

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

!SystemStatusMonitor methodsFor:'destroying'!

destroy
    updateBlock notNil ifTrue:[
	Processor removeTimedBlock:updateBlock.
	Processor removeTimedBlock:listUpdateBlock.
    ] ifFalse:[
	updateProcess notNil ifTrue:[updateProcess terminate]
    ].
    super destroy

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

!SystemStatusMonitor methodsFor:'drawing'!

updateView
    self updateList.
    self updateStatus

    "Created: 23.1.1997 / 02:27:05 / 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 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].
        listUpdateBlock := [self updateList].
    ].

    "
     ProcessMonitor open
    "

    "Modified: 4.8.1997 / 01:44:47 / cg"
!

mapped
    super mapped.
    self updateStatus.
    self updateList.

    "Created: 23.1.1997 / 02:30:05 / 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:0.5.

                "
                 every 20ms, we look which process runs;
                 every half second, the status is updated.
                 every 5 seconds, the list of processes is
                 built up again
                "
                [true] whileTrue:[
                    1 to:9 do:[:i |
"/                        cpuUsages := IdentityDictionary new.
"/                        1 to:25 do:[:i |
"/                            (Delay forSeconds:0.02) wait.
"/                            id := Processor interruptedProcess id.
"/                            cnt := cpuUsages at:id ifAbsent:[0].
"/                            cpuUsages at:id put:cnt + 1.
"/                        ].
                        myDelay wait.
                        self updateStatus.
                    ].
                    myDelay wait.
                    self updateList.
                ]
            ] valueOnUnwindDo:[
                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: 24.1.1997 / 21:40:11 / cg"
! !

!SystemStatusMonitor methodsFor:'queries'!

preferredExtent
    "return my preferred extent"

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

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

!SystemStatusMonitor class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/SystemStatusMonitor.st,v 1.5 1997-08-05 14:30:01 cg Exp $'
! !