[Pkg] The Trunk: Nebraska-nice.28.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 23 21:26:23 UTC 2010


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

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

Name: Nebraska-nice.28
Author: nice
Time: 23 March 2010, 10:26:10.647 pm
UUID: 84be0f3b-1311-4bdc-b2cf-82f2e2133eec
Ancestors: Nebraska-nice.27

Fix underscores

=============== Diff against Nebraska-nice.27 ===============

Item was changed:
  ----- Method: StringSocket>>addToInBuf: (in category 'private-IO') -----
  addToInBuf: aString
  
  	| newAlloc |
+ 	newAlloc := aString size * 2 max: 80000.
- 	newAlloc _ aString size * 2 max: 80000.
  	inBuf ifNil: [
+ 		inBuf := String new: newAlloc.
+ 		inBufIndex := 1.
+ 		inBufLastIndex := 0.
- 		inBuf _ String new: newAlloc.
- 		inBufIndex _ 1.
- 		inBufLastIndex _ 0.
  	].
  	aString size > (inBuf size - inBufLastIndex) ifTrue: [
+ 		inBuf := inBuf , (String new: newAlloc)
- 		inBuf _ inBuf , (String new: newAlloc)
  	].
  	inBuf 
  		replaceFrom: inBufLastIndex + 1 
  		to: inBufLastIndex + aString size
  		with: aString 
  		startingAt: 1.
+ 	inBufLastIndex := inBufLastIndex + aString size.
- 	inBufLastIndex _ inBufLastIndex + aString size.
  !

Item was changed:
  ----- Method: CanvasDecoder classSide>>initialize (in category 'class initialization') -----
  initialize
  	"CanvasDecoder initialize"
  	"Set up my cache and decode table if necessary."
  	CachedForms ifNil: [CachedForms := Array new: 100].
  	DecodeTable ifNotNil: [ ^self ].
  
+ 	DecodeTable := Array new: 128.
- 	DecodeTable _ Array new: 128.
  	#((codeClip setClip:)
  	(codeTransform setTransform:)
  	(codeText drawText:)
  	(codeLine drawLine:)
  	(codeRect drawRect:)
  	(codeBalloonRect drawBalloonRect:)
  	(codeBalloonOval drawBalloonOval:)
  	(codeInfiniteFill drawInfiniteFill:)
  	(codeOval drawOval:)
  	(codeImage drawImage:)
  	(codeReleaseCache releaseImage:)
  	(codePoly drawPoly:)
  	(codeStencil drawStencil:)
  	(codeForce forceToScreen:)
  	(codeFont addFontToCache:)
  	(codeFontSet addFontSetToCache:)
  	(codeMultiText drawMultiText:) 
  	(codeTTCFont addTTCFontToCache:)
  	(codeExtentDepth extentDepth:)
  	(codeShadowColor shadowColor:))
  		do: [ :arr |
  			(DecodeTable at: ((CanvasEncoder perform: arr first) asciiValue + 1)) ifNotNil: [self error: 'duplicated code'].
  			DecodeTable
  				at: ((CanvasEncoder perform: arr first) asciiValue + 1)
  				put: arr second
  		].
  !

Item was changed:
  ----- Method: CanvasEncoder>>image:at:sourceRect:rule: (in category 'drawing') -----
  image: aForm at: aPoint sourceRect: sourceRect rule: argRule
  
  	| cacheID cacheNew cacheReply formToSend cacheEntry destRect visRect aFormArea d2 rule |
  
+ 	rule := argRule.
- 	rule _ argRule.
  
  	"first if we are only going to be able to draw a small part of the form,
  	it may be faster just to send the part of the form that will actually show up"
  
+ 	destRect := aPoint extent: sourceRect extent.
+ 	d2 := (lastTransform invertBoundsRect: destRect) expandBy: 1.
- 	destRect _ aPoint extent: sourceRect extent.
- 	d2 _ (lastTransform invertBoundsRect: destRect) expandBy: 1.
  	(d2 intersects: lastClipRect) ifFalse: [
  		^NebraskaDebug at: #bigImageSkipped add: {lastClipRect. d2}.
  	].
+ 	aFormArea := aForm boundingBox area.
- 	aFormArea _ aForm boundingBox area.
  	(aFormArea > 20000 and: [aForm isStatic not and: [lastTransform isPureTranslation]]) ifTrue: [
+ 		visRect := destRect intersect: lastClipRect.
- 		visRect _ destRect intersect: lastClipRect.
  		visRect area < (aFormArea // 20) ifTrue: [
  			"NebraskaDebug 
  				at: #bigImageReduced 
  				add: {lastClipRect. aPoint. sourceRect extent. lastTransform}."
+ 			formToSend := aForm copy: (visRect translateBy: sourceRect origin - aPoint).
+ 			formToSend depth = 32 ifTrue: [formToSend := formToSend asFormOfDepth: 16. rule = 24 ifTrue: [rule := 25]].
- 			formToSend _ aForm copy: (visRect translateBy: sourceRect origin - aPoint).
- 			formToSend depth = 32 ifTrue: [formToSend _ formToSend asFormOfDepth: 16. rule = 24 ifTrue: [rule _ 25]].
  			^self 
  				image: formToSend 
  				at: visRect origin 
  				sourceRect: formToSend boundingBox
  				rule: rule
  				cacheID: 0 		"no point in trying to cache this - it's a one-timer"
  				newToCache: false.
  		].
  	].
  
+ 	cacheID := 0.
+ 	cacheNew := false.
+ 	formToSend := aForm.
+ 	(aFormArea > 1000 and: [(cacheReply := self testCache: aForm) notNil]) ifTrue: [
+ 		cacheID := cacheReply first.
+ 		cacheEntry := cacheReply third.
+ 		(cacheNew := cacheReply second) ifFalse: [
+ 			formToSend := aForm isStatic 
- 	cacheID _ 0.
- 	cacheNew _ false.
- 	formToSend _ aForm.
- 	(aFormArea > 1000 and: [(cacheReply _ self testCache: aForm) notNil]) ifTrue: [
- 		cacheID _ cacheReply first.
- 		cacheEntry _ cacheReply third.
- 		(cacheNew _ cacheReply second) ifFalse: [
- 			formToSend _ aForm isStatic 
  				ifTrue: [nil] 
  				ifFalse: [aForm depth <= 8 ifTrue: [aForm] ifFalse: [aForm deltaFrom: cacheEntry fourth]].
  		].
  		cacheEntry at: 4 put: (aForm isStatic ifTrue: [aForm] ifFalse: [aForm deepCopy]).
  	].
+ 	(formToSend notNil and: [formToSend depth = 32]) ifTrue: [formToSend := formToSend asFormOfDepth: 16. rule = 24 ifTrue: [rule := 25]].
- 	(formToSend notNil and: [formToSend depth = 32]) ifTrue: [formToSend _ formToSend asFormOfDepth: 16. rule = 24 ifTrue: [rule _ 25]].
  	self
  		image: formToSend 
  		at: aPoint 
  		sourceRect: sourceRect 
  		rule: rule 
  		cacheID: cacheID 
  		newToCache: cacheNew.
  
  !

Item was changed:
  ----- Method: StringSocket>>readBuffer (in category 'as yet unclassified') -----
  readBuffer
  
+ 	^ readBuffer ifNil: [readBuffer := String new: 20000].
- 	^ readBuffer ifNil: [readBuffer _ String new: 20000].
  !

Item was changed:
  ----- Method: StringSocket>>processInput (in category 'private-IO') -----
  processInput
  	| totalReceived chunkOfData |
  	"do as much input as possible"
  
  	self flag: #XXX.  "should have resource limits here--no more than X objects and Y bytes"
  
+ 	chunkOfData := socket receiveAvailableDataIntoBuffer: self readBuffer.
- 	chunkOfData _ socket receiveAvailableDataIntoBuffer: self readBuffer.
  	self addToInBuf: chunkOfData.
+ 	totalReceived := chunkOfData size.
- 	totalReceived _ chunkOfData size.
  
  	totalReceived > 0 ifTrue: [
  		NebraskaDebug at: #SendReceiveStats add: {'GET'. totalReceived}.
  	].
  
  	[ self gotSomething ] whileTrue: [].		"decode as many string arrays as possible"
  
  	self shrinkInBuf.!

Item was changed:
  ----- Method: NebraskaServerMorph classSide>>serveWorldButton (in category 'as yet unclassified') -----
  serveWorldButton
  
  	| button |
+ 	button := ScriptableButton new.
- 	button _ ScriptableButton new.
  	button target: NebraskaServerMorph.
  	button actionSelector: #serveWorld.
  	button arguments: #().
  	button label: 'Share'.
  	button color: Color yellow.
  	^ button.
  !

Item was changed:
  ----- Method: RemoteCanvas>>fillRectangle:fillStyle: (in category 'drawing-rectangles') -----
  fillRectangle: aRectangle fillStyle: aFillStyle
  	"Fill the given rectangle."
  	| pattern |
  	(self isShadowDrawing not and: [self shadowColor notNil]) ifTrue:
  		[^self fillRectangle: aRectangle color: self shadowColor].
  
  	(aFillStyle isKindOf: InfiniteForm) ifTrue: [
  		^self infiniteFillRectangle: aRectangle fillStyle: aFillStyle
  	].
  
  	(aFillStyle isSolidFill) 
  		ifTrue:[^self fillRectangle: aRectangle color: aFillStyle asColor].
  	"We have a very special case for filling with infinite forms"
  	(aFillStyle isBitmapFill and:[aFillStyle origin = (0 at 0)]) ifTrue:[
+ 		pattern := aFillStyle form.
- 		pattern _ aFillStyle form.
  		(aFillStyle direction = (pattern width @ 0) 
  			and:[aFillStyle normal = (0 at pattern height)]) ifTrue:[
  				"Can use an InfiniteForm"
  				^self fillRectangle: aRectangle color: (InfiniteForm with: pattern)].
  	].
  	"Use a BalloonCanvas instead"
  	self balloonFillRectangle: aRectangle fillStyle: aFillStyle.!

Item was changed:
  ----- Method: CanvasEncoder>>drawString:from:to:in:font:color: (in category 'drawing') -----
  drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c
  	| fontIndex str |
  	fontIndex := self establishFont: (fontOrNil ifNil: [ TextStyle defaultFont ]).
+ 	str := s asString copyFrom: firstIndex to: lastIndex.
- 	str _ s asString copyFrom: firstIndex to: lastIndex.
  	str isWideString ifTrue: [
  		self sendCommand: {
  			String with: CanvasEncoder codeMultiText.
  			str asByteArray asString.
  			self class encodeRectangle: boundsRect.
  			self class encodeInteger: fontIndex.
  			self class encodeColor: c
  		}
  	] ifFalse: [
  		self sendCommand: {
  			String with: CanvasEncoder codeText.
  			str.
  			self class encodeRectangle: boundsRect.
  			self class encodeInteger: fontIndex.
  			self class encodeColor: c
  		}
  	].
  !

Item was changed:
  ----- Method: StrikeFont class>>decodedFromRemoteCanvas: (in category '*nebraska-instance creation') -----
  decodedFromRemoteCanvas: aString
  
  	| array style base |
+ 	array := aString findTokens: #($ ).
+ 	style := TextStyle named: (array at: 1) asSymbol.
- 	array _ aString findTokens: #($ ).
- 	style _ TextStyle named: (array at: 1) asSymbol.
  	style ifNil: [^ TextStyle defaultFont].
  	(style fontArray first name = style fontArray first name withoutTrailingDigits) ifTrue: [
  			^ self familyName: (array at: 1) size: (array at: 3) asNumber emphasized: (array at: 4) asNumber].
+ 	base := style fontArray detect: [:f | (array at: 2) beginsWith: f name].
- 	base _ style fontArray detect: [:f | (array at: 2) beginsWith: f name].
  	^ base emphasized: (array at: 4) asNumber.
  
  	"^ self familyName: (array at: 1) size: (array at: 2) asNumber emphasized: (array at: 3) asNumber."
  !



More information about the Packages mailing list