MessageTally.st
author claus
Fri, 11 Aug 1995 18:01:34 +0200
changeset 39 e36b38a77856
parent 38 30fdc5e331f7
child 68 5f7ac0b5c903
permissions -rw-r--r--
.

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


'From Smalltalk/X, Version:2.10.4 on 8-mar-1995 at 22:38:17'!

Object subclass:#MessageTally
	 instanceVariableNames:'process tree ntally theBlock spyInterval'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'System-Debugging-Support'
!

!MessageTally class methodsFor:'documentation'!

version
"
$Header: /cvs/stx/stx/libbasic3/MessageTally.st,v 1.12 1995-08-11 16:01:20 claus Exp $
"
!

documentation
"
    MessageTally allows profiling excution of a block; 
    statistic of method evaluation is output on Transcript.
    To get statistic, use 'MessageTally spyOn:aBlock'.

    example:
	MessageTally spyOn:[
	    (ByteArray uninitalizedNew:1000) sort
	]

    By default, probing is done every 10ms (i.e. the execution of the block is 
    interrupted every 10ms, and the context chain analyzed).
    For better resolution, use smaller clock ticks (if your OperatingSystem
    supports it). Try spyDetailedOn:aBlock, which tries to measure things
    every 1ms. (Notice, that some OS's only provide a resolution of less than
    that time interval)
"
!

examples
"
     MessageTally spyOn:[ #(6 5 4 3 2 1) sort ]
     MessageTally spyOn:[100 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[1000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[10000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[100000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[500000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyDetailedOn:[500000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     Time millisecondsToRun:[500000 timesRepeat:[#(6 5 4 3 2 1) sort] ]

     MessageTally spyOn:[SystemBrowser open ]
     MessageTally spyDetailedOn:[SystemBrowser open ]
"
!

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

!MessageTally class methodsFor:'instance creation'!

spyOn:aBlock interval:ms
    "evaluate aBlock and output time statistic on Transcript"

    |runTime aTally nTally|

    aTally := self new.
    runTime := aTally spyOn:aBlock interval:ms.

    aTally tree isNil ifTrue:[
	Transcript cr.
	Transcript showCr:'TALLY: No probes - execution time too short;'.
	Transcript showCr:'TALLY: retry using: spyOn:[n timesRepeat:[...]]'.
    ] ifFalse:[
	"/ aTally tree inspect.
	nTally := aTally nTally.
	Transcript cr.
	Transcript showCr:('total execution time: '
			   , runTime printString , ' ms '
			   , '(' , nTally printString , ' probes ;'
			   , ' error >= ' 
			   , (1000 // nTally / 10.0) printString
			   , '%)').
	Transcript cr.
	aTally tree printOn:Transcript.
	Transcript cr.
	Transcript cr.

	Transcript showCr:'leafs of calling tree:'.
	Transcript cr.
	aTally tree printLeafsOn:Transcript.
	Transcript cr.

	"
	aTally statistics.
	"
    ].

    "
     MessageTally spyOn:[ #(6 5 4 3 2 1) sort ]
     MessageTally spyOn:[100 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[1000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[10000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[100000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[500000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
     MessageTally spyOn:[SystemBrowser open ]
     MessageTally spyDetailedOn:[SystemBrowser open ]
     Time millisecondsToRun:[500000 timesRepeat:[#(6 5 4 3 2 1) sort] ]
    "
!

spyDetailedOn:aBlock
    "evaluate aBlock and output time statistic on the Transcript.
     Tick is 1ms."

    ^ self spyOn:aBlock interval:1
!

spyOn:aBlock
    "evaluate aBlock and output time statistic on the Transcript.
     Tick is 10ms."

    ^ self spyOn:aBlock interval:10
! !

!MessageTally methodsFor:'private'!

execute
    theBlock value
! !

!MessageTally methodsFor:'accessing'!

tree
    ^ tree
!

nTally 
    ^ ntally 
! !

!MessageTally methodsFor:'setup'!

spyOn:aBlock interval:ms
    "spy on execution time"

    |startTime endTime running delay|

    theBlock := aBlock.

    Processor activeProcess withPriority:23 do:[
	process := [
			[
			    self execute
			] valueNowOrOnUnwindDo:[
			    running := false.
			    theBlock := nil.
			]
		   ] newProcess.

	Processor activeProcess withPriority:24 do:[
	    startTime := OperatingSystem getMillisecondTime.
	    delay := (Delay forMilliseconds:ms).

	    ntally := 0.
	    running := true.
	    process resume.

	    [running] whileTrue:[
		delay wait.
		self count:process suspendedContext
	    ].

	    endTime := OperatingSystem getMillisecondTime.
	].    
    ].    

    tree notNil ifTrue:[tree computePercentage:ntally].
    ^ endTime - startTime
! !

!MessageTally methodsFor:'probes'!

count:aContext
    |con chain info atEnd sender home|

    con := aContext.
    con isNil ifTrue:[^ self].

    ntally := ntally + 1.
    "walk up above the interrupt context"

    [con receiver == Processor] whileTrue:[
	con := con sender
    ].

    "got it - collect info from contexts"

    "walk up"

    con isNil ifTrue:[^ self].

    atEnd := false.

    [atEnd] whileFalse:[
	con isNil ifTrue:[
	    atEnd := true
	] ifFalse:[
	    sender := con sender.
	    sender isNil ifTrue:[
		atEnd := true
	    ] ifFalse:[
		((sender receiver == self) and:[sender selector == #execute]) ifTrue:[
		    atEnd := true
"/                ] ifFalse:[
"/                    (sender isMemberOf:BlockContext) ifTrue:[
"/                        sender sender selector == #execute ifTrue:[
"/                            atEnd := true
"/                        ]
"/                    ]
		]
	    ]
	].
	atEnd ifFalse:[
	    info := CallChain new.
	    (con isMemberOf:BlockContext) ifTrue:[
		home := con methodHome.
		home isNil ifTrue:[
		    info receiver:UndefinedObject
			 selector:'optimized'
			    class:UndefinedObject.
		] ifFalse:[
		    info receiver:home receiver class
			 selector:home selector
			    class:con methodClass.
		].
		info isBlock:true.
	    ] ifFalse:[
		info receiver:con receiver class
		     selector:con selector
			class:con methodClass.
	    ].
	    info rest:chain.
	    chain := info.
	    con := sender
	]
    ].
    "add chain to the tree"

    chain isNil ifTrue:[^ self].

    tree isNil ifTrue:[
	tree := ProfileTree new.
	tree receiver:MessageTally 
	     selector:#execute 
		class:MessageTally .
    ].

    tree addChain:chain
! !