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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 25 21:16:48 UTC 2010


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

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

Name: Graphics-nice.140
Author: nice
Time: 25 June 2010, 11:09:20.113 pm
UUID: a1f90174-88db-499e-858e-5e58b7222015
Ancestors: Graphics-cmm.138

Replace some underscore assignments...

=============== Diff against Graphics-cmm.138 ===============

Item was changed:
  ----- Method: PNMReadWriter>>nextImage (in category 'reading') -----
  nextImage
  	"read one image"
  	| data p |
  	first ifNil:[
+ 		first := false.
+ 		data := stream contentsOfEntireFile.
+ 		stream := (RWBinaryOrTextStream with: data) reset.
- 		first _ false.
- 		data _ stream contentsOfEntireFile.
- 		stream _ (RWBinaryOrTextStream with: data) reset.
  	]
  	ifNotNil:[
  		type < 4 ifTrue:[
  			self error:'Plain PBM, PGM or PPM have only one image'
  		].
  	].
  	stream ascii.
+ 	p := stream next.
+ 	type := (stream next) asInteger - 48.
- 	p _ stream next.
- 	type _ (stream next) asInteger - 48.
  	(p = $P and:[type > 0 and:[type < 8]]) ifFalse:[
  		self error:'Not a PNM file'
  	].
  	type = 7 ifTrue:[
  		self readHeaderPAM
  	]
  	ifFalse: [
  		self readHeader
  	].
  	type caseOf: {
  		[1] 	->	[^self readPlainBW].
  		[2] 	->	[^self readPlainGray].
  		[3] 	->	[^self readPlainRGB].
  		[4] 	->	[^self readBWreverse: false].
  		[5] 	->	[^self readGray].
  		[6] 	->	[^self readRGB].
  		[7] 	->	[	"PAM"
  					(tupleType asUppercase) caseOf: {
  						['BLACKANDWHITE'] 		-> [^self readBWreverse: true].
  						['GRAYSCALE'] 			-> [^self readGray].
  						['RGB'] 					-> [^self readRGB].
  						['RGB_ALPHA'] 			-> [^self error:'Not implemented'].
  						['GRAYSCALE_ALPHA'] 	-> [^self error:'Not implemented'].
  					} otherwise: [^self readData].
  				]
  	}!

Item was changed:
  ----- Method: BDFFontReader>>read (in category 'reading') -----
  read
  	| xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width blt lastAscii pointSize ret stream |
+ 	form := encoding := bbx := nil.
- 	form _ encoding _ bbx _ nil.
  	self readAttributes.
+ 	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
+ 	ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
+ 	descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
+ 	pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
- 	height _ Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
- 	ascent _ Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
- 	descent _ Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
- 	pointSize _ (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
  	
+ 	maxWidth := 0.
+ 	minAscii := 9999.
+ 	strikeWidth := 0.
+ 	maxAscii := 0.
- 	maxWidth _ 0.
- 	minAscii _ 9999.
- 	strikeWidth _ 0.
- 	maxAscii _ 0.
  
+ 	charsNum := Integer readFromString: (properties at: #CHARS) first.
+ 	chars := Set new: charsNum.
- 	charsNum _ Integer readFromString: (properties at: #CHARS) first.
- 	chars _ Set new: charsNum.
  
  	1 to: charsNum do: [:i |
+ 		array := self readOneCharacter.
+ 		stream := ReadStream on: array.
+ 		form := stream next.
+ 		encoding := stream next.
+ 		bbx := stream next.
- 		array _ self readOneCharacter.
- 		stream _ ReadStream on: array.
- 		form _ stream next.
- 		encoding _ stream next.
- 		bbx _ stream next.
  		form ifNotNil: [
+ 			width := bbx at: 1.
+ 			maxWidth := maxWidth max: width.
+ 			minAscii := minAscii min: encoding.
+ 			maxAscii := maxAscii max: encoding.
+ 			strikeWidth := strikeWidth + width.
- 			width _ bbx at: 1.
- 			maxWidth _ maxWidth max: width.
- 			minAscii _ minAscii min: encoding.
- 			maxAscii _ maxAscii max: encoding.
- 			strikeWidth _ strikeWidth + width.
  			chars add: array.
  		].
  	].
  
+ 	chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
+ 	charsNum := chars size. "undefined encodings make this different"
- 	chars _ chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
- 	charsNum _ chars size. "undefined encodings make this different"
  
  	charsNum > 256 ifTrue: [
  		"it should be 94x94 charset, and should be fixed width font"
+ 		strikeWidth := 94*94*maxWidth.
+ 		maxAscii := 94*94.
+ 		minAscii := 0.
+ 		xTable := XTableForFixedFont new.
- 		strikeWidth _ 94*94*maxWidth.
- 		maxAscii _ 94*94.
- 		minAscii _ 0.
- 		xTable _ XTableForFixedFont new.
  		xTable maxAscii: 94*94.
  		xTable width: maxWidth.
  	] ifFalse: [
+ 		xTable := (Array new: 258) atAllPut: 0.
- 		xTable _ (Array new: 258) atAllPut: 0.
  	].
  
+ 	glyphs := Form extent: strikeWidth at height.
+ 	blt := BitBlt toForm: glyphs.
+ 	lastAscii := 0.
- 	glyphs _ Form extent: strikeWidth at height.
- 	blt _ BitBlt toForm: glyphs.
- 	lastAscii _ 0.
  	
  	charsNum > 256 ifTrue: [
  		1 to: charsNum do: [:i |
+ 			stream := ReadStream on: (chars at: i).
+ 			form := stream next.
+ 			encoding := stream next.
+ 			bbx := stream next.
+ 			encoding := ((encoding // 256) - 33) * 94 + ((encoding \\ 256) - 33).
- 			stream _ ReadStream on: (chars at: i).
- 			form _ stream next.
- 			encoding _ stream next.
- 			bbx _ stream next.
- 			encoding _ ((encoding // 256) - 33) * 94 + ((encoding \\ 256) - 33).
  			blt copy: ((encoding * maxWidth)@0 extent: maxWidth at height)
  				from: 0 at 0 in: form.
  		].
  	] ifFalse: [
  		1 to: charsNum do: [:i |
+ 			stream := ReadStream on: (chars at: i).
+ 			form := stream next.
+ 			encoding := stream next.
+ 			bbx := stream next.
- 			stream _ ReadStream on: (chars at: i).
- 			form _ stream next.
- 			encoding _ stream next.
- 			bbx _ stream next.
  			lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
  			blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4)))
  					extent: (bbx at: 1)@(bbx at: 2))
  				from: 0 at 0 in: form.
  			xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1).
+ 			lastAscii := encoding.
- 			lastAscii _ encoding.
  		]
  	].
  
+ 	ret := Array new: 8.
- 	ret _ Array new: 8.
  	ret at: 1 put: xTable.
  	ret at: 2 put: glyphs.
  	ret at: 3 put: minAscii.
  	ret at: 4 put: maxAscii.
  	ret at: 5 put: maxWidth.
  	ret at: 6 put: ascent.
  	ret at: 7 put: descent.
  	ret at: 8 put: pointSize.
  	^ret.
  " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"
  !

Item was changed:
  ----- Method: StrikeFont>>makeAssignArrow (in category 'make arrows') -----
  makeAssignArrow
  "Replace the underline character with an arrow for this font"
  
  	| arrowForm arrowCanvas arrowY arrowLeft arrowRight arrowHeadLength |
  
+ 	arrowForm := (self characterFormAt: $_) copy.
+ 	arrowCanvas := arrowForm getCanvas.
- 	arrowForm _ (self characterFormAt: $_) copy.
- 	arrowCanvas _ arrowForm getCanvas.
  	arrowCanvas fillColor: Color white.
+ 	arrowY := arrowForm height // 2.
+ 	arrowLeft := 0. 
+ 	arrowRight := arrowForm width - 2.
+ 	arrowHeadLength := (arrowRight - arrowLeft) * 2 // 5.
- 	arrowY _ arrowForm height // 2.
- 	arrowLeft _ 0. 
- 	arrowRight _ arrowForm width - 2.
- 	arrowHeadLength _ (arrowRight - arrowLeft) * 2 // 5.
  	"Draw the lines"
  	arrowCanvas line: (arrowLeft at arrowY) to: (arrowRight at arrowY) color: Color black.
  	arrowCanvas 
  		line: (arrowLeft at arrowY) 
  		to: ((arrowLeft + arrowHeadLength)@(arrowY - arrowHeadLength)) 
  		color: Color black.
  	arrowCanvas 
  		line: (arrowLeft at arrowY) 
  		to: ((arrowLeft + arrowHeadLength)@(arrowY + arrowHeadLength)) 
  		color: Color black.
  
  	"Replace the glyph"
  	self characterFormAt: $_ put: arrowForm.
  
  !

Item was changed:
  ----- Method: XBMReadWriter>>readHeader (in category 'private') -----
  readHeader
  	"Set width and height, and position stream at start of bytes"
  	| number setwidth setheight fieldName |
+ 	setwidth := setheight := false.
- 	setwidth _ setheight _ false.
  		[((stream atEnd) or: [setwidth and: [setheight]])]
  		whileFalse: [
  	  	self skipCComments.
  		(stream nextMatchAll: '#define ') ifFalse: [^ false].
  		(stream skipTo: $_) ifFalse: [^ false].
+ 		fieldName := String streamContents:
- 		fieldName _ String streamContents:
  			[:source |
  			[(stream atEnd) or: [ stream peek isSeparator ]]
  				whileFalse: [ source nextPut: stream next]].
  	  	(fieldName = 'width') ifTrue: [
  			stream skipSeparators.
+ 			number := Integer readFrom: stream.
- 			number _ Integer readFrom: stream.
  			(number > 0) ifTrue: [setwidth _true].
+ 	  		width := number.].
- 	  		width _ number.].
  		(fieldName = 'height') ifTrue: [
  			stream skipSeparators.
+ 			number := Integer readFrom: stream.
+ 			(number > 0) ifTrue: [setheight := true].
+ 			height := number.
- 			number _ Integer readFrom: stream.
- 			(number > 0) ifTrue: [setheight _ true].
- 			height _ number.
  			].
  		].
  	(setwidth & setheight) ifFalse: [^ false].
  	^ stream skipTo: ${
  !

Item was changed:
  ----- Method: PNGReadWriter class>>test1 (in category 'as yet unclassified') -----
  test1
  "PNGReadWriter test1"
  	| d0 d1 fileInfo book d2 f |
  
+ 	Debugging := true.
- 	Debugging _ true.
  	1 = 1 ifTrue: [
+ 		book := BookMorph new.
- 		book _ BookMorph new.
  		book setProperty: #transitionSpec toValue: {'silence'. #none. #none}.
  	].
+ 	d0 := FileDirectory default.
+ 	d1 := d0 directoryNamed: 'PngSuite Folder'.
+ 	d2 := d0 directoryNamed: 'BIG PNG'.
- 	d0 _ FileDirectory default.
- 	d1 _ d0 directoryNamed: 'PngSuite Folder'.
- 	d2 _ d0 directoryNamed: 'BIG PNG'.
  	{d0. d1. d2}.		"keep compiler quiet"
  "==
  citrus_none_sub.png
  citrus_adm7_adap.png
  citrus_adm7_aver.png
  citrus_adm7_non.png
  citrus_adm7_paeth.png
  pngs-img-ie5mac.png
  =="
+ 	fileInfo := {
- 	fileInfo _ {
  		d2. {'citrus_adm7_adap.png'}.
  		"d1. d1 fileNames."
  	}.
  	fileInfo pairsDo: [ :dir :fileNames |
  		fileNames do: [ :each | | error data t |
  			Transcript cr; show: each.
+ 			data := (dir fileNamed: each) contentsOfEntireFile.
+ 			error := ''.
- 			data _ (dir fileNamed: each) contentsOfEntireFile.
- 			error _ ''.
  			MessageTally spyOn: [
+ 				t := [ | result |
+ 					result := self createAFormFrom: data.
- 				t _ [ | result |
- 					result _ self createAFormFrom: data.
  					f_ result first.
+ 					error := result second.
- 					error _ result second.
  				] timeToRun.].
  			self insertMorph: f asMorph named: each into: book.
  			Transcript show: each,'  ',data size printString,' = ',t printString,' ms',error; cr.
  		].
  	].
  	book ifNotNil: [book openInWorld].
+ 	Debugging := false.!
- 	Debugging _ false.!

Item was changed:
  ----- Method: BDFFontReader>>readChars (in category 'reading') -----
  readChars
  	| strikeWidth ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width pointSize stream |
+ 	form := encoding := bbx := nil.
- 	form _ encoding _ bbx _ nil.
  	self readAttributes.
+ 	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
+ 	ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
+ 	descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
+ 	pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
- 	height _ Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
- 	ascent _ Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
- 	descent _ Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
- 	pointSize _ (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
  	
+ 	maxWidth := 0.
+ 	minAscii := 9999.
+ 	strikeWidth := 0.
+ 	maxAscii := 0.
- 	maxWidth _ 0.
- 	minAscii _ 9999.
- 	strikeWidth _ 0.
- 	maxAscii _ 0.
  
+ 	charsNum := Integer readFromString: (properties at: #CHARS) first.
+ 	chars := Set new: charsNum.
- 	charsNum _ Integer readFromString: (properties at: #CHARS) first.
- 	chars _ Set new: charsNum.
  
  	1 to: charsNum do: [:i |
+ 		array := self readOneCharacter.
+ 		stream := ReadStream on: array.
+ 		form := stream next.
+ 		encoding := stream next.
+ 		bbx := stream next.
- 		array _ self readOneCharacter.
- 		stream _ ReadStream on: array.
- 		form _ stream next.
- 		encoding _ stream next.
- 		bbx _ stream next.
  		form ifNotNil: [
+ 			width := bbx at: 1.
+ 			maxWidth := maxWidth max: width.
+ 			minAscii := minAscii min: encoding.
+ 			maxAscii := maxAscii max: encoding.
+ 			strikeWidth := strikeWidth + width.
- 			width _ bbx at: 1.
- 			maxWidth _ maxWidth max: width.
- 			minAscii _ minAscii min: encoding.
- 			maxAscii _ maxAscii max: encoding.
- 			strikeWidth _ strikeWidth + width.
  			chars add: array.
  		].
  	].
  
+ 	chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
- 	chars _ chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
  
  	^ chars.
  !



More information about the Packages mailing list