[Pkg] The Trunk: Graphics-nice.94.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Dec 26 22:18:35 UTC 2009


Nicolas Cellier uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-nice.94.mcz

==================== Summary ====================

Name: Graphics-nice.94
Author: nice
Time: 26 December 2009, 11:17:59 am
UUID: 23b5323f-9265-43d4-99f7-97bac434ac77
Ancestors: Graphics-nice.93

Cosmetic: puch a few temps inside closures

=============== Diff against Graphics-nice.93 ===============

Item was changed:
  ----- Method: XBMReadWriter class>>initialize (in category 'class initialization') -----
  initialize
  	"XBMReadWriter initialize"
- 	| flippedByte |
  	Flipbits := (0 to: 255) collect:
+ 		[:n |  "Compute the bit-reversal of the 8-bit value, n"
+ 		| flippedByte |
+ 		flippedByte := 0.
+ 		0 to: 7 do: 
+ 			[:i | 
+ 			flippedByte := flippedByte bitOr: ((n >> i bitAnd: 1) << (7-i))].
+ 			flippedByte]!
-      [:n |  "Compute the bit-reversal of the 8-bit value, n"
-      flippedByte := 0.
-      0 to: 7 do: 
-          [:i | 
-          flippedByte := flippedByte bitOr: ((n >> i bitAnd: 1) << (7-i))].
-          flippedByte]!

Item was changed:
  ----- Method: StrikeFont class>>convertFontsNamed: (in category 'examples') -----
  convertFontsNamed: familyName  " StrikeFont convertFontsNamed: 'NewYork' "
  	"This utility is for use after you have used BitFont to produce data files 
  	for the fonts you wish to use.  It will read the BitFont files and then 
  	write them out in strike2 (*.sf2) format which is much more compact,
  	and which can be read in again very quickly."
  	"For this utility to work as is, the BitFont data files must be named
  	'familyNN.BF', and must reside in the same directory as the image."
- 	| f |
  	(FileDirectory default fileNamesMatching: familyName , '*.BF') do:
+ 		[:fname |
+ 		| f |
+ 		Transcript cr; show: fname.
- 		[:fname | Transcript cr; show: fname.
  		f := StrikeFont new readFromBitFont: fname.
  		f writeAsStrike2named: f name , '.sf2']!

Item was changed:
  ----- Method: CornerRounder>>saveBitsUnderCornersOf:on:in:corners: (in category 'all') -----
  saveBitsUnderCornersOf: aMorph on: aCanvas in: bounds corners: cornerList
  
+ 	| corners |
- 	| offset corner mask form corners rect |
  	underBits := Array new: 4.
  	corners := bounds corners.
  	cornerList do:[:i|
+ 		| offset corner mask form rect |
  		mask := cornerMasks at: i.
  		corner := corners at: i.
  		i = 1 ifTrue: [offset := 0 at 0].
  		i = 2 ifTrue: [offset := 0 at mask height negated].
  		i = 3 ifTrue: [offset := mask extent negated].
  		i = 4 ifTrue: [offset := mask width negated at 0].
  		rect := corner + offset extent: mask extent.
  		(aCanvas isVisible: rect) ifTrue:[
  			form := aCanvas contentsOfArea: rect.
  			form copyBits: form boundingBox from: mask at: 0 at 0 clippingBox: form boundingBox rule: Form and fillColor: nil map: (Bitmap with: 16rFFFFFFFF with: 0).
  			underBits at: i put: form]].
  !

Item was changed:
  ----- Method: PNGReadWriter>>processInterlaced (in category 'chunks') -----
  processInterlaced
+ 	| z startingCol colIncrement rowIncrement startingRow |
- 	| z filter bytesPerPass startingCol colIncrement rowIncrement startingRow cx sc temp |
  	startingCol := #(0 4 0 2 0 1 0 ).
  	colIncrement := #(8 8 4 4 2 2 1 ).
  	rowIncrement := #(8 8 8 4 4 2 2 ).
  	startingRow := #(0 0 4 0 2 0 1 ).
  	z := ZLibReadStream on: chunk from: 1 to: chunk size.
  	1 to: 7 do: [:pass |
+ 		| cx sc bytesPerPass |
  		(self doPass: pass)
  			ifTrue:
  				[cx := colIncrement at: pass.
  				sc := startingCol at: pass.
  				bytesPerPass := width - sc + cx - 1 // cx * bitsPerPixel + 7 // 8.
  				prevScanline := ByteArray new: bytesPerPass.
  				thisScanline := ByteArray new: bytesPerScanline.
  				(startingRow at: pass)
  					to: height - 1
  					by: (rowIncrement at: pass)
  					do: [:y |
+ 						| filter temp |
  						filter := z next.
  						filtersSeen add: filter.
  						(filter isNil or: [(filter between: 0 and: 4) not])
  							ifTrue: [^ self].
  						thisScanline := z next: bytesPerPass into: thisScanline startingAt: 1.
  						self filterScanline: filter count: bytesPerPass.
  						self copyPixels: y at: sc by: cx.
  						temp := prevScanline.
  						prevScanline := thisScanline.
  						thisScanline := temp.
  					]
  				]
  	].
  	z atEnd ifFalse:[self error:'Unexpected data'].!

Item was changed:
  ----- Method: PNGReadWriter>>writePLTEChunkOn: (in category 'writing') -----
  writePLTEChunkOn: aStream
  	"Write the PLTE chunk"
+ 	| colors |
- 	| r g b colors |
  	aStream nextPutAll: 'PLTE' asByteArray.
  	(form isColorForm) 
  		ifTrue:[colors := form colors]
  		ifFalse:[colors := Color indexedColors copyFrom: 1 to: (1 bitShift: form depth)].
  	colors do:[:aColor|
+ 		| r g b |
  		r := (aColor red * 255) truncated.
  		g := (aColor green * 255) truncated.
  		b := (aColor blue * 255) truncated.
  		aStream nextPut: r; nextPut: g; nextPut: b.
  	].!

Item was changed:
  ----- Method: CornerRounder>>tweakCornersOf:on:in:borderWidth:corners: (in category 'all') -----
  tweakCornersOf: aMorph on: aCanvas in: bounds borderWidth: w corners: cornerList
  	"This variant has a cornerList argument, to allow some corners to be rounded and others not"
+ 	| fourColors mask shadowColor corners |
- 	| offset corner saveBits fourColors mask outBits shadowColor corners |
  	shadowColor := aCanvas shadowColor.
  	aCanvas shadowColor: nil. "for tweaking it's essential"
  	w > 0 ifTrue:[
  			fourColors := shadowColor 
  				ifNil:[aMorph borderStyle colorsAtCorners]
  				ifNotNil:[Array new: 4 withAll: Color transparent]].
  	mask := Form extent: cornerMasks first extent depth: aCanvas depth.
  	corners := bounds corners.
  	cornerList do:[:i|
+ 		| offset corner saveBits outBits |
  		corner := corners at: i.
  		saveBits := underBits at: i.
  		saveBits ifNotNil:[
  			i = 1 ifTrue: [offset := 0 at 0].
  			i = 2 ifTrue: [offset := 0 at saveBits height negated].
  			i = 3 ifTrue: [offset := saveBits extent negated].
  			i = 4 ifTrue: [offset := saveBits width negated at 0].
  
  			"Mask out corner area (painting saveBits won't clear if transparent)."
  			mask copyBits: mask boundingBox from: (cornerMasks at: i) at: 0 at 0 clippingBox: mask boundingBox rule: Form over fillColor: nil map: (Bitmap with: 0 with: 16rFFFFFFFF).
  			outBits := aCanvas contentsOfArea: (corner + offset extent: mask extent).
  			mask displayOn: outBits at: 0 at 0 rule: Form and.
  			"Paint back corner bits."
  			saveBits displayOn: outBits at: 0 at 0 rule: Form paint.
  			"Paint back corner bits."
  			aCanvas drawImage: outBits at: corner + offset.
  
  			w > 0 ifTrue:[
  				
  				aCanvas stencil: (cornerOverlays at: i) at: corner + offset
  						color: (fourColors at: i)]]].
  	aCanvas shadowColor: shadowColor. "restore shadow color"
  !

Item was changed:
  ----- Method: StrikeFont>>widen:by: (in category 'character shapes') -----
  widen: char by: delta
- 	| newForm |
  	^ self alter: char formBlock:  "Make a new form, wider or narrower..."
+ 		[:charForm |
+ 		| newForm |
+ 		newForm := Form extent: charForm extent + (delta at 0).
- 		[:charForm | newForm := Form extent: charForm extent + (delta at 0).
  		charForm displayOn: newForm.  "Copy this image into it"
  		newForm]    "and substitute it in the font"!

Item was changed:
  ----- Method: DisplayScanner>>displayLines:in:clippedBy: (in category 'MVC-compatibility') -----
  displayLines: linesInterval in: aParagraph clippedBy: visibleRectangle
  	"The central display routine. The call on the primitive 
  	(scanCharactersFrom:to:in:rightX:) will be interrupted according to an 
  	array of stop conditions passed to the scanner at which time the code to 
  	handle the stop condition is run and the call on the primitive continued 
  	until a stop condition returns true (which means the line has 
  	terminated)."
+ 	| leftInRun |
- 	| runLength done stopCondition leftInRun startIndex string lastPos |
  	"leftInRun is the # of characters left to scan in the current run;
  		when 0, it is time to call 'self setStopConditions'"
  	morphicOffset := 0 at 0.
  	leftInRun := 0.
  	self initializeFromParagraph: aParagraph clippedBy: visibleRectangle.
  	ignoreColorChanges := false.
  	paragraph := aParagraph.
  	foregroundColor := paragraphColor := aParagraph foregroundColor.
  	backgroundColor := aParagraph backgroundColor.
  	aParagraph backgroundColor isTransparent
  		ifTrue: [fillBlt := nil]
  		ifFalse: [fillBlt := bitBlt copy.  "Blt to fill spaces, tabs, margins"
  				fillBlt sourceForm: nil; sourceOrigin: 0 at 0.
  				fillBlt fillColor: aParagraph backgroundColor].
  	rightMargin := aParagraph rightMarginForDisplay.
  	lineY := aParagraph topAtLineIndex: linesInterval first.
  	bitBlt destForm deferUpdatesIn: visibleRectangle while: [
  		linesInterval do: 
  			[:lineIndex | 
+ 			| string startIndex lastPos runLength done stopCondition |
  			line := aParagraph lines at: lineIndex.
  			lastIndex := line first.
                 self setStopConditions. " causes an assignment to inst var.  alignment "
  
  			leftMargin := aParagraph leftMarginForDisplayForLine: lineIndex alignment: (alignment ifNil:[textStyle alignment]).
  			destX := (runX := leftMargin).
  			line := aParagraph lines at: lineIndex.
  			lineHeight := line lineHeight.
  			fillBlt == nil ifFalse:
  				[fillBlt destX: visibleRectangle left destY: lineY
  					width: visibleRectangle width height: lineHeight; copyBits].
  			lastIndex := line first.
  			leftInRun <= 0
  				ifTrue: [self setStopConditions.  "also sets the font"
  						leftInRun := text runLengthFor: line first].
  			destY := lineY + line baseline - font ascent.  "Should have happened in setFont"
  			runLength := leftInRun.
  			runStopIndex := lastIndex + (runLength - 1) min: line last.
  			leftInRun := leftInRun - (runStopIndex - lastIndex + 1).
  			spaceCount := 0.
  			done := false.
  			string := text string.
  			self handleIndentation.
  			[done] whileFalse:[
  				startIndex := lastIndex.
  				lastPos := destX at destY.
  				stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  							in: string rightX: rightMargin stopConditions: stopConditions
  							kern: kern.
  				lastIndex >= startIndex ifTrue:[
  					font displayString: string on: bitBlt 
  						from: startIndex to: lastIndex at: lastPos kern: kern].
  				"see setStopConditions for stopping conditions for displaying."
  				done := self perform: stopCondition].
  			fillBlt == nil ifFalse:
  				[fillBlt destX: destX destY: lineY width: visibleRectangle right-destX height: lineHeight; copyBits].
  			lineY := lineY + lineHeight]]!

Item was changed:
  ----- Method: StrikeFont>>xTableFromHex: (in category 'Mac reader') -----
  xTableFromHex: file
  
+ 	| strike num wid |
- 	| strike num str wid |
  	strike := file.
  	xTable := (Array new: maxAscii + 3) atAllPut: 0.
+ 	minAscii + 1 to: maxAscii + 3 do:
- 	(minAscii + 1 to: maxAscii + 3) do:
  		[:index | 
+ 			num := Number readFrom: (strike next: 4) base: 16. 
- 			num := Number readFrom: (str := strike next: 4) base: 16. 
  			xTable at: index put: num].
  
  	1 to: xTable size - 1 do: [:ind |
  		wid := (xTable at: ind+1) - (xTable at: ind).
  		(wid < 0) | (wid > 40) ifTrue: [
  			file close.
  			self error: 'illegal character width']].
  !

Item was changed:
  ----- Method: Form>>fadeImageCoarse:at: (in category 'transitions') -----
  fadeImageCoarse: otherImage at: topLeft
  	"Display fadeImageCoarse: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
+ 	| d |
- 	| pix j d |
  	d := self depth.
  	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
  		[:i :mask |
+ 		| pix j |
  		i=1 ifTrue: [pix := (1 bitShift: d) - 1.
  					1 to: 8//d-1 do: [:q | pix := pix bitOr: (pix bitShift: d*4)]].
  		i <= 16 ifTrue:
  		[j := i-1//4+1.
  		(0 to: 28 by: 4) do: [:k |
  			mask bits at: j+k
  				put: ((mask bits at: j+k) bitOr: (pix bitShift: i-1\\4*d))].
  		"mask display." true]
  		ifFalse: [false]]!

Item was changed:
  ----- Method: Form>>fadeImageFine:at: (in category 'transitions') -----
  fadeImageFine: otherImage at: topLeft
  	"Display fadeImageFine: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
+ 	| d |
- 	| pix j ii d |
  	d := self depth.
  	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
  		[:i :mask |
+ 		| pix j ii  |
  		i=1 ifTrue: [pix := (1 bitShift: d) - 1.
  					1 to: 8//d-1 do:
  						[:q | pix := pix bitOr: (pix bitShift: d*4)]].
  		i <= 16 ifTrue:
  		[ii := #(0 10 2 8 7 13 5 15 1 11 3 9 6 12 4 14) at: i.
  		j := ii//4+1.
  		(0 to: 28 by: 4) do:
  			[:k | mask bits at: j+k put:
  				((mask bits at: j+k) bitOr: (pix bitShift: ii\\4*d))].
  		true]
  		ifFalse: [false]]!



More information about the Packages mailing list