parent previous next question (Smalltalk Textbook 30)

Tips

Let me give you some useful messages and programs in this section.

(1) Examination

Open the browser for any object.


Program-30-1: (Array; browse)
--------------------------------------------------
| anObject |
        anObject := Array new.
        anObject browse
--------------------------------------------------

Open the inspector for any object.


Program-30-2: (Array; inspect)
--------------------------------------------------
| anObject |
        anObject := Array new.
        anObject inspect
--------------------------------------------------

Browse definitions of a message.


Program-30-3: (Browser; browseAllImplementorsOf:)
--------------------------------------------------
        Browser browseAllImplementorsOf: #size
--------------------------------------------------

Browse places where a message is sent.


Program-30-4: (Browser; browseAllCallsOn:, browseAllCallsOn:and:, 
browseAllCallsOn:within:)
--------------------------------------------------
        Browser browseAllCallsOn: #pi
        Browser browseAllCallsOn: #pi and: #cos
        Browser browseAllCallsOn: #pi within: Geometric
--------------------------------------------------

When you evaluate 'Browser browseAllCallsOn: #pi', examine 'EllipticalArc computePoints' carefully. What 'pi' was found? What does this tell you about how the search is being carried out?

Browse methods which meet conditions you specify ( 8 or more arguments in this case).


Program-30-5: (Browser; browseAllSelect:, numArgs)
--------------------------------------------------
        Browser browseAllSelect: [:method | method numArgs >= 8]
--------------------------------------------------

Browse methods which use a specified global variable.


Program-30-6: (Browser; browseAllCallsOn:, associationAt:)
--------------------------------------------------
        Browser browseAllCallsOn:
                (Smalltalk associationAt: #Transcript)
--------------------------------------------------

Browse all example programs.


Program-30-7: (Browser; browseAllClassExamples)
--------------------------------------------------
        Browser browseAllClassExamples
--------------------------------------------------

(2) Memory

Available memory in bytes.


Program-30-8: (ObjectMemory; current, availableFreeBytes)
--------------------------------------------------
        ObjectMemory current availableFreeBytes
--------------------------------------------------

Expand memory size by 1 mega byte.


Program-30-9: (ObjectMemory; growMemoryBy:, verboseGrowMemoryBy:)
--------------------------------------------------
        ObjectMemory growMemoryBy: 1000000
        ObjectMemory verboseGrowMemoryBy: 1000000
--------------------------------------------------

Activate the garbage collector explicitly.


Program-30-10: (ObjectMemory; globalGarbageCollect, verboseGlobalCompactingGC)
--------------------------------------------------
        ObjectMemory globalGarbageCollect
        ObjectMemory verboseGlobalCompactingGC
--------------------------------------------------

(3) Date and Time

Get the current date and time.


Program-30-11: (Time; dateAndTimeNow)
--------------------------------------------------
        Time dateAndTimeNow
--------------------------------------------------

Get the current time in milliseconds.


Program-30-12: (Time; millisecondClockValue)
--------------------------------------------------
        Time millisecondClockValue
--------------------------------------------------

Get the elapsed time of a process (this exaample redraws all windows).


Program-30-13: (Time; millisecondsToRun:)
--------------------------------------------------
        Time millisecondsToRun: [ScheduledControllers restore]
--------------------------------------------------

(4) History

show Change Set as text.


Program-30-14: (WriteStream, ChangeSet, Time, ComposedTextView; 
millisecondsToRun:, now)
--------------------------------------------------
        | aStream |
        aStream := WriteStream on: String new.
        Date today printOn: aStream.
        aStream space.
        Time now printOn: aStream.
        aStream cr; cr.
        ChangeSet current printOn: aStream.
        ComposedTextView
                open: (ValueHolder with: aStream contents)
                label: 'Change Set'
--------------------------------------------------

Store Change Set to a file, then browes it by Change List. (This does not work in VW 2.5)


Program-30-15: (WriteStream, ChangeSet, ChangeList, ChangeListView, Time;
totalSeconds, fileOutChanges, scanFile:)
--------------------------------------------------
| timeString fileName aStream aChangeList |
        timeString := Time totalSeconds printString.
        fileName := timeString
                        copyFrom: (timeString size - 7 max: 1)
                        to: timeString size.
        fileName := fileName , '.cs'.
        aStream := fileName asFilename writeStream.
        aStream fileOutChanges.
        aStream := fileName asFilename readStream.
        aChangeList := ChangeList new.
        aChangeList scanFile: aStream.
        ChangeListView openOn: aChangeList
--------------------------------------------------

Initialize the Change Set.


Program-30-16: (ChangeSet; noChanges)
--------------------------------------------------
        ChangeSet noChanges
--------------------------------------------------

Compresses change file ( *.cha ).


Program-30-17: (SourceFileManager; condenseChanges)
--------------------------------------------------
        SourceFileManager default condenseChanges
--------------------------------------------------

(5) Mouse

Examine registerd cursor shapes.


Program-30-18: (Cursor, Delay; classPool, isKindOf:, forSeconds:)
--------------------------------------------------
        Cursor classPool do: [:each |
                (each isKindOf: Cursor)
                        ifTrue:
                                [Transcript cr; show: each name printString.
                                each showWhile: [(Delay forSeconds: 1)
                wait]]]
--------------------------------------------------

(6) Measurement

Count the number of classes.


Program-30-19: (Object, Class; Smalltalk, allBehaviorsDo:, isMeta)
--------------------------------------------------
        | count |
        count := 0.
        Smalltalk allBehaviorsDo: [:each |
                each isMeta ifTrue: [count := count + 1]].
        ^count
--------------------------------------------------

Count the number of unique method names.


Program-30-20: (Set, Symbol, Object, Class; Smalltalk, defaultImplementor,
instanceCount, allBehaviorsDo:, selectors)
--------------------------------------------------
        | set |
        set := Set new: Symbol defaultImplementor instanceCount.
        Smalltalk allBehaviorsDo: [:each | set addAll: each selectors].
        ^set size
--------------------------------------------------

Count the number of methods definitions.


Program-30-21: (Object, Class; Smalltalk, allBehaviorsDo:, selectors)
--------------------------------------------------
        | count |
        count := 0.
        Smalltalk allBehaviorsDo: [:each |
                count := count + each selectors size].
        ^count
--------------------------------------------------

Count the number of times each method is defined. (takes a while)


Program-30-22: (Object, Class; Smalltalk, allBehaviorsDo:, selectors, 
sortBlock:, associationsDo:)
--------------------------------------------------
        | dictionary count collection |
        dictionary := Dictionary
                        new: Symbol defaultImplementor instanceCount.
        Smalltalk allBehaviorsDo: [:each |
                each selectors do:
                        [:selector |
                        count := dictionary
                                        at: selector
                                        ifAbsent: [0].
                        dictionary at: selector put: count + 1]].
        collection := SortedCollection new: dictionary size.
        collection sortBlock: [:x :y | x value > y value].
        dictionary associationsDo: [:assoc | collection add: assoc].
        ^collection
--------------------------------------------------

For each class, count the number of methods which reference the class. ( takes a while ).


Program-30-23: (Object, Class; Smalltalk, allBehaviorsDo:, selectors, 
whichSelectorsReferTo:, sortBlock:, associationsDo:, associationAt:)
--------------------------------------------------
        | reference dictionary collection |
        reference :=
                [:assoc |
                | count refs |
                count := 0.
                Smalltalk allBehaviorsDo:
                        [:each |
                        refs := (each whichSelectorsReferTo: assoc) size.
                        count := count + refs].
                count].
        dictionary := Dictionary new: Smalltalk size.
        Smalltalk allBehaviorsDo:
                [:each | each isMeta ifFalse: [
                | assoc refs |
                assoc := Smalltalk associationAt: each name.
                refs := reference value: assoc.
                dictionary at: each name put: refs.
                Transcript cr; show: each name.
                Transcript space.
                Transcript show: refs printString]].
        collection := SortedCollection new: dictionary size.
        collection sortBlock: [:x :y | x value > y value].
        dictionary associationsDo: [:assoc | collection add: assoc].
        ^collection
--------------------------------------------------

For each method, count the number of methods which use it. (Don't do this unless you have "War and Peace" nearby)


Program-30-24: (Object, Class; Smalltalk, allBehaviorsDo:, selectors, 
whichSelectorsReferTo:, defaultImplementor, instanceCount, sortBlock:, 
associationsDo:, associationAt:)
--------------------------------------------------
        | reference dictionary collection |
        reference :=
                [:selector |
                | count refs |
                count := 0.
                Smalltalk allBehaviorsDo:
                        [:each |
                        refs := (each whichSelectorsReferTo: selector) size.
                        count := count + refs].
                count].
        dictionary := Dictionary
                        new: Symbol defaultImplementor instanceCount.
        Smalltalk allBehaviorsDo:
                [:each |
                | refs |
                each selectors do: [:selector |
                        dictionary
                                at: selector
                                ifAbsent:
                                        [refs := reference value: selector.
                                        dictionary at: selector put: refs.
                                        Transcript cr; show: selector.
                                        Transcript space.
                                        Transcript show: refs printString]]].
        collection := SortedCollection new: dictionary size.
        collection sortBlock: [:x :y | x value > y value].
        dictionary associationsDo: [:assoc | collection add: assoc].
        ^collection
--------------------------------------------------

I have more tips that I won't cover now. It's a good idea to keep this file handy in a Work Space or File List so you can cut-and-paste or evaluate.


parent previous next question
Copyright (C) 1994-1996 by Atsushi Aoki
Translated by Kaoru Rin Hayashi & Brent N. Reeves