[squeak-dev] The Trunk: Graphics-ar.148.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 5 18:05:25 UTC 2010


Andreas Raab uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-ar.148.mcz

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

Name: Graphics-ar.148
Author: ar
Time: 5 September 2010, 11:03:55.551 am
UUID: c6c6db0b-f43f-8a48-a77f-e381754ba3a4
Ancestors: Graphics-nice.147

Restructurings to reduce package depencencies.

=============== Diff against Graphics-nice.147 ===============

Item was changed:
  ----- Method: Form class>>initialize (in category 'initialize-release') -----
  initialize
  
+ 	FileServices registerFileReader: self!
- 	FileList registerFileReader: self!

Item was changed:
  ----- Method: Form class>>unload (in category 'class initialization') -----
  unload
  
+ 	FileServices unregisterFileReader: self !
- 	FileList unregisterFileReader: self !

Item was changed:
  ----- Method: TextStyle class>>replaceFontsIn:with: (in category 'mime file in/out') -----
  replaceFontsIn: oldFontArray with: newStyle
  	"
  	TextStyle replaceFontsIn: (TextStyle looseFontsFromFamily: #Accuny) with: (TextStyle named: #Accuny)
  	"
  	"Try to find corresponding fonts in newStyle and substitute them for the fonts in oldFontArray"
  
  	newStyle fontArray do: [ :newFont | newFont releaseCachedState ].
  
  	oldFontArray do: [ :oldFont | | newFont |
  		oldFont reset.
  		newFont := (newStyle fontOfPointSize: oldFont pointSize) emphasis: oldFont emphasis.
  		oldFont becomeForward: newFont ].
  
+ 	Smalltalk at: #StringMorph ifPresent:[:cls| cls allSubInstancesDo: [ :s | s layoutChanged]].
+ 	Smalltalk at: #TextMorph ifPresent:[:cls| cls allSubInstancesDo: [ :s | s layoutChanged]].
+ 	Smalltalk at: #SystemWindow ifPresent:[:cls| 
+ 		cls allInstancesDo: [ :w | [ w update: #relabel ] on: Error do: [ :ex | ] ]].
- 	StringMorph allSubInstancesDo: [ :s | s layoutChanged ].
- 	TextMorph allSubInstancesDo: [ :s | s layoutChanged ].
- 	SystemWindow allInstancesDo: [ :w | [ w update: #relabel ] on: Error do: [ :ex | ] ].
  	World ifNotNil: [ :w | w changed ].!

Item was changed:
  ----- Method: BDFFontReader class>>downloadFonts (in category 'resource download') -----
  downloadFonts  "BDFFontReader downloadFonts"
  	"Download a standard set of BDF sources from x.org.  
  	The combined size of these source files is around 1.2M; after conversion 
  	to .sf2 format they may be deleted."
  
  	| heads tails filenames baseUrl basePath |
  	heads := #( 'charR' 'courR' 'helvR' 'lubR' 'luRS' 'lutRS' 'ncenR' 'timR' ).
  	tails := #( '08' '10' '12' '14' '18' '24').
  
  	filenames := OrderedCollection new.
  	heads do: [:head |
  		filenames addAll: (tails collect: [:tail | head , tail , '.bdf'])
  	].
  
+ 	baseUrl := 'http://ftp.x.org/pub/R6.4/xc/fonts/bdf/75dpi/' asUrl.
- 	baseUrl := Url absoluteFromText: 'http://ftp.x.org/pub/R6.4/xc/fonts/bdf/75dpi/'.
  	basePath := baseUrl path.
  
  	filenames do: [:filename | | document f newPath newUrl |
  		newUrl := baseUrl clone.
  		newPath := OrderedCollection newFrom: basePath.
  
  		newPath addLast: filename.
  		newUrl path: newPath.
  
  		Utilities informUser: 'Fetching ' , filename during: 
  			[document := newUrl retrieveContents].
  
  		f := CrLfFileStream newFileNamed: filename.
  		f nextPutAll: document content.
  		f close.
  	].
  !

Item was removed:
- ----- Method: Pen>>arrowHeadForArrowSpec: (in category 'operations') -----
- arrowHeadForArrowSpec: anArrowSpec
- 	"Put an arrowhead on the previous pen stroke"
- "
- 	 | pen aPoint |
- 	aPoint := Point fromUser.
- 	pen := Pen new.
- 	20 timesRepeat: [pen turn: 360//20; go: 20; arrowHeadForArrowSpec: aPoint].
- "
- 
- 
- 	penDown ifTrue:
- 		[self arrowHeadFrom: (direction degreeCos @ direction degreeSin) * -40 + location 
- 			to: location
- 			arrowSpec: anArrowSpec]!

Item was removed:
- ----- Method: PNMReadWriter class>>testFromString (in category 'testing') -----
- testFromString
- 	"read SE file from string
- 		PNMReadWriter testFromString
- 	"
- 	| prw f s |
- 	prw := self new.
- 	s := 
- 'P1
- #origin 1 0
- 3 1
- 1	01'.
- 	prw stream: (ReadStream on: s from: 1 to: (s size)).
- 	f := prw nextImage.
- 	f morphEdit.
- 	Transcript cr;show:'Origin=', prw origin asString; cr.!

Item was removed:
- ----- Method: ImageReadWriter class>>formFromServerFile: (in category 'image reading/writing') -----
- formFromServerFile: fileName
- 	"Answer a ColorForm stored on the file with the given name.  Meant to be called from during the getting of updates from the server.  That assures that (Utilities serverUrls) returns the right group of servers."
- 
- 	| urls |
- 	urls := Utilities serverUrls collect:
- 		[:url | url, fileName].  " fileName starts with: 'updates/'  "
- 	urls do: [:aURL | | form doc |
- 		(fileName findTokens: '.') last asLowercase = 'gif' ifTrue: [
- 			form := HTTPSocket httpGif: aURL.
- 			form = (ColorForm extent: 20 at 20 depth: 8) 
- 				ifTrue: [self inform: 'The file ',aURL,' is ill formed.'].
- 			^ form].
- 		(fileName findTokens: '.') last asLowercase = 'bmp' ifTrue: [
- 			doc := HTTPSocket httpGet: aURL accept: 'image/bmp'.
- 			form := Form fromBMPFile: doc.
- 			doc close.
- 			form ifNil: [self inform: 'The file ',aURL,' is ill formed.'. ^ Form new]
- 				ifNotNil: [^ form]].
- 		self inform: 'File ', fileName, 'does not end with .gif or .bmp'].
- 	self inform: 'That file not found on any server we know'.!

Item was removed:
- ----- Method: Pen>>arrowHeadFrom:to:arrowSpec: (in category 'operations') -----
- arrowHeadFrom: prevPt to: newPt arrowSpec: anArrowSpec
- 	"Put an arrowhead on the pen stroke from oldPt to newPt"
- 
- 	| pm af myColor finalPt delta |
- 	myColor := self color.
- 	delta := newPt - prevPt.
- 	delta r <= 2 "pixels" ifTrue: [^ self].
- 	finalPt := newPt + (Point r: sourceForm width degrees: delta degrees).	"in same direction"
- 	pm := PolygonMorph vertices: (Array with: prevPt asIntegerPoint with: finalPt asIntegerPoint)  
- 		color: myColor  "not used"
- 		borderWidth: sourceForm width borderColor: myColor.
- 	pm makeOpen; makeForwardArrow.
- 	anArrowSpec ifNotNil: [pm arrowSpec: anArrowSpec].
- 	af := pm arrowForms first.
- 	"render it onto the destForm"
- 	(FormCanvas on: destForm "Display") stencil: af at: af offset + (1 at 1)
- 		color: myColor!

Item was removed:
- ----- Method: PNGReadWriter class>>createAFormFrom: (in category 'as yet unclassified') -----
- createAFormFrom: data
- 
- 	| error f |
- 
- 	error := ''.
- 	f := [
- 		self formFromStream: (RWBinaryOrTextStream with: data)
- 	] ifError: [ :a :b |
- 		error := a printString,'  ',b printString.
- 		(StringMorph contents: error) color: Color red; imageForm
- 	].
- 	^{f. error}!

Item was removed:
- ----- Method: Form>>asMorph (in category 'converting') -----
- asMorph
- 	^ImageMorph new image: self!

Item was removed:
- ----- Method: PNMReadWriter class>>testFromSEFile: (in category 'testing') -----
- testFromSEFile: filename
- 	"read SE file, check origin
- 		PNMReadWriter testFromSEFile: 'Tools:Squeak3.4:eliseSE.pbm'.
- 	"
- 	| prw f |
- 	prw := self new.
- 	prw stream: (FileStream readOnlyFileNamed: filename).
- 	f := prw nextImage.
- 	f morphEdit.
- 	prw inspect!

Item was removed:
- ----- Method: PNMReadWriter class>>testMultiFile: (in category 'testing') -----
- testMultiFile: filename
- 	"write two files from user, then read
- 		PNMReadWriter testMultiFile: 'Tools:Squeak3.6:outMulti.pbm'.
- 	"
- 	| prw f |
- 	prw := self new.
- 	prw stream: ((FileStream newFileNamed: filename) binary).
- 	prw pragma: '#Squeak test', String lf.
- 	f := Form fromUser. prw nextPutImage: f. 
- 	f := Form fromUser.prw nextPutImage: f.	
- 	prw close.
- 	prw stream: (StandardFileStream readOnlyFileNamed: filename).
- 	f := prw nextImage. (SketchMorph withForm: f) openInWorld.
- 	f := prw nextImage. (SketchMorph withForm: f) openInWorld.
- !

Item was removed:
- ----- Method: Pen>>arrowHeadFrom:to:forPlayer: (in category 'operations') -----
- arrowHeadFrom: prevPt to: newPt forPlayer: aPlayer
- 	"Put an arrowhead on the pen stroke from oldPt to newPt"
- 	
- 	| aSpec |
- 	(aPlayer notNil and: [(aSpec := aPlayer costume renderedMorph valueOfProperty: #arrowSpec) notNil]) 
- 		ifFalse:
- 			[aSpec := Preferences parameterAt: #arrowSpec "may well be nil"].
- 	self arrowHeadFrom: prevPt to: newPt arrowSpec: aSpec!

Item was removed:
- ----- Method: Pen>>arrowHead (in category 'operations') -----
- arrowHead
- 	"Put an arrowhead on the previous pen stroke"
- 	" | pen | pen := Pen new. 20 timesRepeat: [pen turn: 360//20; go: 20; arrowHead]."
- 
- 	penDown ifTrue:
- 		[self arrowHeadFrom: (direction degreeCos @ direction degreeSin) * -40 + location 
- 			to: location
- 			arrowSpec: (Preferences parameterAt: #arrowSpec ifAbsent: [5 @ 4])]!

Item was removed:
- ----- Method: PNGReadWriter class>>test1 (in category 'as yet unclassified') -----
- test1
- "PNGReadWriter test1"
- 	| d0 d1 fileInfo book d2 f |
- 
- 	Debugging := true.
- 	1 = 1 ifTrue: [
- 		book := BookMorph new.
- 		book setProperty: #transitionSpec toValue: {'silence'. #none. #none}.
- 	].
- 	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 := {
- 		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 := ''.
- 			MessageTally spyOn: [
- 				t := [ | result |
- 					result := self createAFormFrom: data.
- 					f_ result first.
- 					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.!

Item was removed:
- ----- Method: Form>>morphEdit (in category 'editing') -----
- morphEdit
- 
-         ^ FatBitsPaint new openWith: self!




More information about the Squeak-dev mailing list