[FIX][ENH] 2 Morphic speedups

Henrik Gedenryd Henrik.Gedenryd at lucs.lu.se
Tue Jun 27 13:08:59 UTC 2000


Two speedups:

1. Cache color maps when drawing text (BitBlt and FXBlt).
2. Make buttons (eg. window collapse/close) indicate being pressed already
on mouseDown. 

These ought to go into the updates for 2.8, and not wait till 2.9.

Henrik

-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2344] on 27 June 2000 at 2:13:18 pm'!
"Change Set:		SnappierMorphic-hg
Date:			27 June 2000
Author:			Henrik Gedenryd

Two speedups:

1. Cache color maps when drawing text (BitBlt and FXBlt).
2. Make buttons (eg. window collapse/close) indicate being pressed already on mouseDown. "!

Object subclass: #BitBlt
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap '
	classVariableNames: 'CachedFontColorMaps '
	poolDictionaries: ''
	category: 'Graphics-Primitives'!
Object subclass: #FXBlt
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap sourceMap destMap warpQuad warpQuality sourceKey destKey sourceAlpha tallyMap raiseErrors '
	classVariableNames: 'CachedFontColorMaps RecursionLock '
	poolDictionaries: ''
	category: 'Graphics-FXBlt'!

!BitBlt methodsFor: 'private' stamp: 'hg 6/27/2000 12:27'!
cachedFontColormapFrom: sourceDepth to: destDepth

	| srcIndex map |
	CachedFontColorMaps class == Array 
		ifFalse: [CachedFontColorMaps _ (1 to: 9) collect: [:i | Array new: 32]].
	srcIndex _ sourceDepth.
	sourceDepth > 8 ifTrue: [srcIndex _ 9].
	(map _ (CachedFontColorMaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [^ map].

	map _ (Color cachedColormapFrom: sourceDepth to: destDepth) copy.
	(CachedFontColorMaps at: srcIndex) at: destDepth put: map.
	^ map
! !

!BitBlt methodsFor: 'private' stamp: 'hg 6/27/2000 12:28'!
installStrikeFont: aStrikeFont foregroundColor: foregroundColor backgroundColor: backgroundColor
	| lastSourceDepth |
	sourceForm ifNotNil:[lastSourceDepth _ sourceForm depth].
	sourceForm _ aStrikeFont glyphs.
	(colorMap notNil and:[lastSourceDepth = sourceForm depth]) ifFalse:
		["Set up color map for a different source depth (color font)"
		"Uses caching for reasonable efficiency"
		colorMap _ self cachedFontColormapFrom: sourceForm depth to: destForm depth.
		colorMap at: 1 put: (backgroundColor pixelValueForDepth: destForm depth)].
	sourceForm depth = 1 ifTrue:
		[colorMap at: 2 put: (foregroundColor pixelValueForDepth: destForm depth).
		"Ignore any halftone pattern since we use a color map approach here"
		halftoneForm _ nil].
	sourceY _ 0.
	height _ aStrikeFont height.
! !


!FXBlt methodsFor: 'private' stamp: 'hg 6/27/2000 13:13'!
cachedFontColormapFrom: sourceDepth to: destDepth

	| srcIndex map |
	CachedFontColorMaps class == Array 
		ifFalse: [CachedFontColorMaps _ (1 to: 9) collect: [:i | Array new: 32]].
	srcIndex _ sourceDepth.
	sourceDepth > 8 ifTrue: [srcIndex _ 9].
	(map _ (CachedFontColorMaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [^ map].

	map _ (Color cachedColormapFrom: sourceDepth to: destDepth) copy.
	(CachedFontColorMaps at: srcIndex) at: destDepth put: map.
	^ map
! !

!FXBlt methodsFor: 'private' stamp: 'hg 6/27/2000 13:14'!
installStrikeFont: aStrikeFont foregroundColor: foregroundColor backgroundColor: backgroundColor
	| lastSourceDepth |
	sourceForm ifNotNil:[lastSourceDepth _ sourceForm depth].
	sourceForm _ aStrikeFont glyphs.
	(colorMap notNil and:[lastSourceDepth = sourceForm depth]) ifFalse:
		["Set up color map for a different source depth (color font)"
		"Uses caching for reasonable efficiency"
		colorMap _ self cachedFontColormapFrom: sourceForm depth to: destForm depth.
		colorMap at: 1 put: (backgroundColor pixelValueForDepth: destForm depth).
		self colorMap: colorMap].
	sourceForm depth = 1 ifTrue:
		[colorMap colors at: 2 put: (foregroundColor pixelValueForDepth: destForm depth).
		"Ignore any halftone pattern since we use a color map approach here"
		halftoneForm _ nil].
	sourceY _ 0.
	height _ aStrikeFont height.
! !


!SimpleButtonMorph methodsFor: 'events' stamp: 'hg 6/27/2000 13:58'!
mouseDown: evt

	| now dt |
	now _ Time millisecondClockValue.
	oldColor _ color. 
	actWhen == #buttonDown
		ifTrue: [self doButtonAction]
		ifFalse: [	self updateVisualState: evt; refreshWorld].
	dt _ Time millisecondClockValue - now max: 0.  "Time it took to do"
	dt < 200 ifTrue: [(Delay forMilliseconds: 200-dt) wait]
! !

!SimpleButtonMorph methodsFor: 'events' stamp: 'hg 6/27/2000 14:00'!
mouseMove: evt
	actWhen == #buttonDown ifTrue: [^ self].
	self updateVisualState: evt.
	(actWhen == #whilePressed and: [
			evt anyButtonPressed and: [self containsPoint: evt cursorPoint]])
		ifTrue: [self doButtonAction.
				evt hand noteSignificantEvent: evt]
! !

!SimpleButtonMorph methodsFor: 'visual properties' stamp: 'hg 6/27/2000 13:58'!
updateVisualState: evt
	
	oldColor ifNotNil: [
		 self color: 
			((self containsPoint: evt cursorPoint)
				ifTrue: [oldColor mixed: 1/2 with: Color white]
				ifFalse: [oldColor])]
! !



More information about the Squeak-dev mailing list