Skip to content

Commit

Permalink
replace transcript calls
Browse files Browse the repository at this point in the history
  • Loading branch information
VincentBlondeau committed Aug 30, 2019
1 parent 8c8e4d3 commit 5098f59
Show file tree
Hide file tree
Showing 16 changed files with 209 additions and 171 deletions.
130 changes: 100 additions & 30 deletions src/Balloon/BalloonEngine.class.st
Expand Up @@ -82,48 +82,118 @@ BalloonEngine class >> primitiveSetBitBltPlugin: pluginName [
{ #category : #profiling }
BalloonEngine class >> printBezierStats [
<script>
Transcript
cr; nextPutAll:'Bezier statistics:';
cr; tab; print: (BezierStats at: 1); tab; nextPutAll:' non-monoton curves splitted';
cr; tab; print: (BezierStats at: 2); tab; nextPutAll:' curves splitted for numerical accuracy';
cr; tab; print: (BezierStats at: 3); tab; nextPutAll:' curves splitted to avoid integer overflow';
cr; tab; print: (BezierStats at: 4); tab; nextPutAll:' curves internally converted to lines';
endEntry.
self
trace:
(String
streamContents: [ :stream |
stream
cr;
nextPutAll: 'Bezier statistics:';
cr;
tab;
print: (BezierStats at: 1);
tab;
nextPutAll: ' non-monoton curves splitted';
cr;
tab;
print: (BezierStats at: 2);
tab;
nextPutAll: ' curves splitted for numerical accuracy';
cr;
tab;
print: (BezierStats at: 3);
tab;
nextPutAll: ' curves splitted to avoid integer overflow';
cr;
tab;
print: (BezierStats at: 4);
tab;
nextPutAll: ' curves internally converted to lines' ])
]

{ #category : #profiling }
BalloonEngine class >> printStat: time count: n string: aString [
Transcript
BalloonEngine class >> printStat: time count: n string: aString on: aStream [
aStream
cr;
print: time; tab;
nextPutAll:' mSecs -- ';
print: n; tab;
nextPutAll:' ops -- ';
print: ((time asFloat / (n max: 1) asFloat) roundTo: 0.01); tab;
print: time;
tab;
nextPutAll: ' mSecs -- ';
print: n;
tab;
nextPutAll: ' ops -- ';
print: (time asFloat / (n max: 1) asFloat roundTo: 0.01);
tab;
nextPutAll: ' avg. mSecs/op -- ';
nextPutAll: aString.
nextPutAll: aString
]

{ #category : #profiling }
BalloonEngine class >> printStats [
<script: '
<script:
'
BalloonEngine doProfileStats: true.
BalloonEngine printStats.
BalloonEngine resetStats'>

Transcript cr; nextPutAll:'/************** BalloonEngine statistics ****************/'.
self printStat: (Times at: 1) count: (Counts at: 1) string: 'Initialization'.
self printStat: (Times at: 2) count: (Counts at: 2) string: 'Finish test'.
self printStat: (Times at: 3) count: (Counts at: 3) string: 'Fetching/Adding GET entries'.
self printStat: (Times at: 4) count: (Counts at: 4) string: 'Adding AET entries'.
self printStat: (Times at: 5) count: (Counts at: 5) string: 'Fetching/Computing fills'.
self printStat: (Times at: 6) count: (Counts at: 6) string: 'Merging fills'.
self printStat: (Times at: 7) count: (Counts at: 7) string: 'Displaying span buffer'.
self printStat: (Times at: 8) count: (Counts at: 8) string: 'Fetching/Updating AET entries'.
self printStat: (Times at: 9) count: (Counts at: 9) string: 'Changing AET entries'.
Transcript cr; print: Times sum; nextPutAll:' mSecs for all operations'.
Transcript cr; print: Counts sum; nextPutAll: ' overall operations'.
Transcript endEntry.
| string |
string := String
streamContents: [ :aStream |
aStream
cr;
nextPutAll: '/************** BalloonEngine statistics ****************/'.
self
printStat: (Times at: 1)
count: (Counts at: 1)
string: 'Initialization'
on: aStream.
self
printStat: (Times at: 2)
count: (Counts at: 2)
string: 'Finish test'
on: aStream.
self
printStat: (Times at: 3)
count: (Counts at: 3)
string: 'Fetching/Adding GET entries'
on: aStream.
self
printStat: (Times at: 4)
count: (Counts at: 4)
string: 'Adding AET entries'
on: aStream.
self
printStat: (Times at: 5)
count: (Counts at: 5)
string: 'Fetching/Computing fills'
on: aStream.
self
printStat: (Times at: 6)
count: (Counts at: 6)
string: 'Merging fills'
on: aStream.
self
printStat: (Times at: 7)
count: (Counts at: 7)
string: 'Displaying span buffer'
on: aStream.
self
printStat: (Times at: 8)
count: (Counts at: 8)
string: 'Fetching/Updating AET entries'
on: aStream.
self
printStat: (Times at: 9)
count: (Counts at: 9)
string: 'Changing AET entries'
on: aStream.
aStream
cr;
print: Times sum;
nextPutAll: ' mSecs for all operations'.
aStream
cr;
print: Counts sum;
nextPutAll: ' overall operations' ].
self trace: string
]

{ #category : #private }
Expand Down
2 changes: 1 addition & 1 deletion src/FFI-Kernel/ExternalUnion.class.st
Expand Up @@ -66,7 +66,7 @@ ExternalUnion class >> compileFields: specArray withAccessors: aSymbol [
ifTrue: [:sym | externalType := ExternalType structTypeNamed: sym].
].
externalType == nil ifTrue:[
Transcript show: '(' , fieldType , ' is void)'.
self trace: '(' , fieldType , ' is void)'.
externalType := ExternalType void.
].
isPointerField ifTrue: [externalType := externalType asPointerType: self pointerSize]].
Expand Down
5 changes: 2 additions & 3 deletions src/Flashback-Decompiler-Tests/FBDExamples.class.st
Expand Up @@ -1196,9 +1196,8 @@ FBDExamples >> exampleToDoArgumentNotInlined [
{ #category : #'examples-blocks-optimized' }
FBDExamples >> exampleToDoInsideBlock [
| tmp1 block |
tmp1 := {1.2.
3.4} asOrderedCollection.
block := [ (tmp1 at: 1) to: (tmp1 at: 4) do: [ :arg1 | Transcript show: arg1 ] ]
tmp1 := {1.2 . 3.4} asOrderedCollection.
block := [ (tmp1 at: 1) to: (tmp1 at: 4) do: [ :arg1 | self trace: arg1 ] ]
]

{ #category : #'examples-blocks-optimized' }
Expand Down
Expand Up @@ -38,6 +38,6 @@ GLMLipsumWithSegmentsExample >> presentation [
seg := RubUnderlinedSegmentMorph from: 1000 to: 1030.
seg icon: (self iconNamed: #smallHelpIcon).
seg label: 'Print it'.
seg iconBlock: [ :segment :event | Transcript show: segment getText ].
seg iconBlock: [ :segment :event | self trace: segment getText ].
t addTextSegment: seg]
]
57 changes: 29 additions & 28 deletions src/Kernel-Tests/DelayBenchmark.class.st
Expand Up @@ -32,37 +32,38 @@ DelayBenchmark class >> runAll [
{ #category : #benchmarks }
DelayBenchmark >> bench [
"DelayBenchmark runAll."

"DelayBenchmark run."

| sampleSetSeeds trialOfNumberConcurrent completed |
sampleSetSeeds := #( 42 "5975 13746 22634 44022" ). "uncomment items to get a better average"
trialOfNumberConcurrent := #( 1000 2000 3000 4000 5000 6000 7000 8000 9000 10000 ).
sampleSetSeeds := #(42). "5975 13746 22634 44022" "uncomment items to get a better average"
trialOfNumberConcurrent := #(1000 2000 3000 4000 5000 6000 7000 8000 9000 10000).
completed := Semaphore new.

Transcript cr; crShow: 'Benchmarking ' , Delay delaySchedulerClass printString.
[ trialOfNumberConcurrent do: [ :numberConcurrent |
Transcript crShow: '#ConcurrentDelays: ' , numberConcurrent printString ; space.
EnterCount := ExitCount := 0.
sampleSetSeeds do: [ :seed |
Transcript show: '.'.
self
trialConcurrent: numberConcurrent
priority: Processor userSchedulingPriority + 1
maxDuration: 50
fromSeed: seed.
].
Transcript space ;
show: 'EnterCount: ' , (EnterCount // (sampleSetSeeds size)) printString ; space ;
show: 'ExitCount: ' , (ExitCount // (sampleSetSeeds size)) printString .
self currentWorld doOneCycle. "since we are a higher priority would prevent transcript showing"
].
completed signal.
] forkAt: Processor userSchedulingPriority + 2. "To avoid UI loop influencing result"

completed wait.




self
crTrace: String cr , 'Benchmarking ' , Delay delaySchedulerClass printString.
[ trialOfNumberConcurrent
do: [ :numberConcurrent |
self
crTrace: '#ConcurrentDelays: ' , numberConcurrent printString , String space.
EnterCount := ExitCount := 0.
sampleSetSeeds
do: [ :seed |
self trace: '.'.
self
trialConcurrent: numberConcurrent
priority: Processor userSchedulingPriority + 1
maxDuration: 50
fromSeed: seed ].
self trace: String space.
self
trace:
'EnterCount: ' , (EnterCount // sampleSetSeeds size) printString
, String space.
self
trace: 'ExitCount: ' , (ExitCount // sampleSetSeeds size) printString.
self currentWorld doOneCycle "since we are a higher priority would prevent transcript showing" ].
completed signal ] forkAt: Processor userSchedulingPriority + 2. "To avoid UI loop influencing result"
completed wait
]

{ #category : #benchmarks }
Expand Down
55 changes: 17 additions & 38 deletions src/Keymapping-Core/KMLog.class.st
Expand Up @@ -10,58 +10,37 @@ Class {
#category : #'Keymapping-Core-Debugging'
}

{ #category : #'class initialization' }
KMLog class >> initialize [
debug := false
]

{ #category : #logging }
KMLog class >> log: aKeyEvent [

debug == true ifFalse: [ ^self ].

self logger
nextPutAll: aKeyEvent printString;
cr;
flush.
debug ifFalse: [ ^ self ].
self traceCr: aKeyEvent printString
]

{ #category : #logging }
KMLog class >> logCompleteMatch: aKeymap [

debug == true ifFalse: [ ^self ].

self logger
nextPutAll: 'Complete match: ';
nextPutAll: aKeymap printString;
cr;
flush.
debug
ifFalse: [ ^ self ].
self traceCr: 'Complete match: ' , aKeymap printString
]

{ #category : #logging }
KMLog class >> logCompleteMatchBetween: aMorph and: aKeymap [

debug == true ifFalse: [ ^self ].

self logger
nextPutAll: aMorph printString;
nextPutAll: ' Complete match: ';
nextPutAll: aKeymap printString;
cr;
flush.
debug
ifFalse: [ ^ self ].
self
traceCr: aMorph printString , ' Complete match: ' , aKeymap printString
]

{ #category : #logging }
KMLog class >> logPartialMatch: anEvent [

debug == true ifFalse: [ ^self ].

self logger
nextPutAll: 'Partial match: ';
nextPutAll: anEvent printString;
cr;
flush.
]

{ #category : #accessing }
KMLog class >> logger [

^Transcript
debug
ifFalse: [ ^ self ].
self traceCr: 'Partial match: ' , anEvent printString
]

{ #category : #debugging }
Expand Down
4 changes: 1 addition & 3 deletions src/Metacello-Base/Metacello.class.st
Expand Up @@ -601,9 +601,7 @@ Metacello >> onWarning: aBlock [
Metacello >> onWarningLog [
self
onWarning: [ :ex |
Transcript
cr;
show: ex description.
self crTrace: ex description.
ex resume ]
]

Expand Down
Expand Up @@ -412,9 +412,7 @@ MCGitBasedNetworkRepository >> flushCache [
[ localRepository flushCache ]
on: Error
do: [ :ex |
Transcript
cr;
show: 'Error for: ' , self description printString , ' during flushCache: ', ex description printString ].
self crTrace: 'Error for: ' , self description printString , ' during flushCache: ', ex description printString ].
self class flushDownloadCache.

directory := self calculateRepositoryDirectory.
Expand Down

0 comments on commit 5098f59

Please sign in to comment.