[squeak-dev] The Trunk: Morphic-ul.474.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 16 04:22:05 UTC 2010


Levente Uzonyi uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-ul.474.mcz

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

Name: Morphic-ul.474
Author: ul
Time: 16 November 2010, 5:20:28.527 am
UUID: 9107f23b-5888-804b-ba2f-4685283d31c5
Ancestors: Morphic-ul.473

- use #= for integer comparison instead of #== (http://bugs.squeak.org/view.php?id=2788 )

=============== Diff against Morphic-ul.473 ===============

Item was changed:
  ----- Method: BalloonCanvas>>line:to:width:color: (in category 'drawing') -----
  line: pt1 to: pt2 width: w color: c
  	"Draw a line from pt1 to: pt2"
  
+ 	(aaLevel = 1 and: [self ifNoTransformWithIn:(pt1 rect: pt2)])
- 	(aaLevel == 1 and: [self ifNoTransformWithIn:(pt1 rect: pt2)])
  		ifTrue:[^super line: pt1 to: pt2 width: w color: c].
  	^self drawPolygon: (Array with: pt1 with: pt2)
  		color: c
  		borderWidth: w
  		borderColor: c!

Item was changed:
  ----- Method: BorderedMorph>>acquireBorderWidth: (in category 'geometry') -----
  acquireBorderWidth: aBorderWidth
  	"Gracefully acquire the new border width, keeping the interior area intact and not seeming to shift"
  
  	| delta |
+ 	(delta := aBorderWidth- self borderWidth) = 0 ifTrue: [^ self].
- 	(delta := aBorderWidth- self borderWidth) == 0 ifTrue: [^ self].
  	self bounds: ((self bounds origin - (delta @ delta)) corner: (self bounds corner + (delta @ delta))).
  	self borderWidth: aBorderWidth.
  	self layoutChanged!

Item was changed:
  ----- Method: ImageMorph>>color: (in category 'accessing') -----
  color: aColor
          super color: aColor.
+         (image depth = 1 and: [aColor isColor]) ifTrue: [
-         (image depth == 1 and: [aColor isColor]) ifTrue: [
                  image colors: {Color transparent. aColor}.
                  self changed]!

Item was changed:
  ----- Method: ImageMorph>>wantsRecolorHandle (in category 'as yet unclassified') -----
  wantsRecolorHandle
  	^ image isNil not
+ 		and: [image depth = 1]!
- 		and: [image depth == 1]!

Item was changed:
  ----- Method: MenuMorph class>>fromArray: (in category 'instance creation') -----
  fromArray: anArray 
  	"Construct a menu from anArray. The elements of anArray  
  	must be either:  
  	* A pair of the form: <label> <selector>  
  	or	* The 'dash' (or 'minus sign') symbol  
  	 
  	Refer to the example at the bottom of the method"
  	| menu |
  
  	menu := self new.
  
  	anArray
  		do: [:anElement |
+ 			anElement size = 1
- 			anElement size == 1
  				ifTrue: [
  					anElement == #- ifFalse: [^ self error: 'badly-formed menu constructor'].
  					menu addLine.
  				]
  				ifFalse: [
+ 					anElement size = 2 ifFalse: [^ self error: 'badly-formed menu constructor'].
- 					anElement size == 2 ifFalse: [^ self error: 'badly-formed menu constructor'].
  					menu add: anElement first action: anElement second.
  				]
  		].
  
  	^ menu!

Item was changed:
  ----- Method: MenuMorph>>wantsToBeDroppedInto: (in category 'control') -----
  wantsToBeDroppedInto: aMorph
  	"Return true if it's okay to drop the receiver into aMorph.  A single-item MenuMorph is in effect a button rather than a menu, and as such should not be reluctant to be dropped into another object."
  
+ 	^ (aMorph isWorldMorph or: [submorphs size = 1]) or:
- 	^ (aMorph isWorldMorph or: [submorphs size == 1]) or:
  		[Preferences systemWindowEmbedOK]!

Item was changed:
  ----- Method: Morph>>addStandardHaloMenuItemsTo:hand: (in category 'menus') -----
  addStandardHaloMenuItemsTo: aMenu hand: aHandMorph
  	"Add standard halo items to the menu"
  
  	| unlockables |
  
  	self isWorldMorph ifTrue:
  		[^ self addWorldHaloMenuItemsTo: aMenu hand: aHandMorph].
  
  	self mustBeBackmost ifFalse:
  		[aMenu add: 'send to back' translated action: #goBehind.
  		aMenu add: 'bring to front' translated action: #comeToFront.
  		self addEmbeddingMenuItemsTo: aMenu hand: aHandMorph.
  		aMenu addLine].
  
  	self addFillStyleMenuItems: aMenu hand: aHandMorph.
  	self addBorderStyleMenuItems: aMenu hand: aHandMorph.
  	self addDropShadowMenuItems: aMenu hand: aHandMorph.
  	self addLayoutMenuItems: aMenu hand: aHandMorph.
  	self addHaloActionsTo: aMenu.
  	owner isTextMorph ifTrue:[self addTextAnchorMenuItems: aMenu hand: aHandMorph].
  	aMenu addLine.
  	self addToggleItemsToHaloMenu: aMenu.
  	aMenu addLine.
  	self addCopyItemsTo: aMenu.
  	self addPlayerItemsTo: aMenu.
  	self addExportMenuItems: aMenu hand: aHandMorph.
  	self addStackItemsTo: aMenu.
  	self addMiscExtrasTo: aMenu.
  	Preferences noviceMode ifFalse:
  		[self addDebuggingItemsTo: aMenu hand: aHandMorph].
  
  	aMenu addLine.
  	aMenu defaultTarget: self.
  
  	aMenu addLine.
  
  	unlockables := self submorphs select:
  		[:m | m isLocked].
+ 	unlockables size = 1 ifTrue:
- 	unlockables size == 1 ifTrue:
  		[aMenu
  			add: ('unlock "{1}"' translated format: unlockables first externalName)
  			action: #unlockContents].
  	unlockables size > 1 ifTrue:
  		[aMenu add: 'unlock all contents' translated action: #unlockContents.
  		aMenu add: 'unlock...' translated action: #unlockOneSubpart].
  
  	aMenu defaultTarget: aHandMorph.
  !

Item was changed:
  ----- Method: MorphicAlarmQueue>>add: (in category 'adding') -----
  add: aMorphicAlarm
+ 	(sequenceNumber := sequenceNumber + 1) = 16r3FFFFFFF ifTrue: [
- 	(sequenceNumber := sequenceNumber + 1) == 16r3FFFFFFF ifTrue: [
  		"Sequence number overflow... reassign sequence numbers starting at 0."
  		| alarmList |
  		alarmList := self asArray sort: [:msg1 :msg2 |
  			 msg1 sequenceNumber < msg2 sequenceNumber
  		].
  		alarmList withIndexDo: [:msg :ind | msg sequenceNumber: ind-1].
  		"The #bitAnd: for the unlikely event that we have > 16r3FFFFFF messages in the queue."
  		sequenceNumber := alarmList last sequenceNumber + 1 bitAnd: 16r3FFFFFFF.
  	].
  	aMorphicAlarm sequenceNumber: sequenceNumber.
  	super add: aMorphicAlarm.
  	
  	"If we doubt our sanity..."
  	false ifTrue: [
  		self isValidHeap ifFalse: [self error: 'not a valid heap!!!!!!'].
  	].
  	^aMorphicAlarm!

Item was changed:
  ----- Method: PasteUpMorph>>addWorldHaloMenuItemsTo:hand: (in category 'menu & halo') -----
  addWorldHaloMenuItemsTo: aMenu hand: aHandMorph
  	"Add standard halo items to the menu, given that the receiver is a World"
  
  	| unlockables |
  	self addFillStyleMenuItems: aMenu hand: aHandMorph.
  	self addLayoutMenuItems: aMenu hand: aHandMorph.
  
  	aMenu addLine.
  	self addWorldToggleItemsToHaloMenu: aMenu.
  	aMenu addLine.
  	self addCopyItemsTo: aMenu.
  	self addPlayerItemsTo: aMenu.
  	self addExportMenuItems: aMenu hand: aHandMorph.
  	self addStackItemsTo: aMenu.
  	self addMiscExtrasTo: aMenu.
  
  	Preferences noviceMode ifFalse:
  		[self addDebuggingItemsTo: aMenu hand: aHandMorph].
  
  	aMenu addLine.
  	aMenu defaultTarget: self.
  
  	aMenu addLine.
  
  	unlockables := self submorphs select:
  		[:m | m isLocked].
+ 	unlockables size = 1 ifTrue:
- 	unlockables size == 1 ifTrue:
  		[aMenu add: ('unlock "{1}"' translated format:{unlockables first externalName})action: #unlockContents].
  	unlockables size > 1 ifTrue:
  		[aMenu add: 'unlock all contents' translated action: #unlockContents.
  		aMenu add: 'unlock...' translated action: #unlockOneSubpart].
  
  	aMenu defaultTarget: aHandMorph.
  !

Item was changed:
  ----- Method: PluggableButtonMorph>>performAction (in category 'accessing') -----
  performAction
  	"Inform the model that this button has been pressed. Sent by the controller when this button is pressed. If the button's actionSelector takes any arguments, they are obtained dynamically by sending the argumentSelector to the argumentsProvider"
  
  	askBeforeChanging ifTrue: [model okToChange ifFalse: [^ self]].
  	actionSelector ifNotNil:
+ 		[actionSelector numArgs = 0
- 		[actionSelector numArgs == 0
  			ifTrue:
  				[model perform: actionSelector]
  			ifFalse:
  				[argumentsProvider ifNotNil:
  					[arguments := argumentsProvider perform: argumentsSelector].
  					model perform: actionSelector withArguments: arguments]]!

Item was changed:
  ----- Method: PluggableListMorph>>mouseUp: (in category 'events') -----
  mouseUp: event 
  	"The mouse came up within the list; take appropriate action"
  	| row |
  	row := self rowAtLocation: event position.
  	"aMorph ifNotNil: [aMorph highlightForMouseDown: false]."
  	model okToChange
  		ifFalse: [^ self].
  	"No change if model is locked"
+ 	row = self selectionIndex
+ 		ifTrue: [(autoDeselect ifNil: [true]) ifTrue:[row = 0 ifFalse: [self changeModelSelection: 0] ]]
- 	row == self selectionIndex
- 		ifTrue: [(autoDeselect ifNil: [true]) ifTrue:[row == 0 ifFalse: [self changeModelSelection: 0] ]]
  		ifFalse: [self changeModelSelection: row].
  	Cursor normal show!

Item was changed:
  ----- Method: PolygonMorph>>unrotatedLength (in category 'menu') -----
  unrotatedLength
  	"If the receiver bears rotation without a transformation morph, answer what its length in the direction it is headed is"
  
+ 	vertices size = 2 ifTrue:
- 	vertices size == 2 ifTrue:
  		[^ (vertices second - vertices first) r].
  
  	^ ((PolygonMorph new setVertices: vertices) rotationDegrees: self rotationDegrees negated) height!

Item was changed:
  ----- Method: PolygonMorph>>unrotatedLength: (in category 'menu') -----
  unrotatedLength: aLength
  	"If the receiver bears rotation without a transformation morph, answer what its length in the direction it is headed is"
  
+ 	vertices size = 2 ifTrue: [^ self arrowLength: aLength].
- 	vertices size == 2 ifTrue: [^ self arrowLength: aLength].
  
  	self setVertices: ((((PolygonMorph new setVertices: vertices) rotationDegrees: self rotationDegrees negated) height: aLength) rotationDegrees: 0) vertices!

Item was changed:
  ----- Method: PolygonMorph>>unrotatedWidth (in category 'menu') -----
  unrotatedWidth
  	"If the receiver bears rotation without a transformation morph, answer what its length in the direction it is headed is"
  	
+ 	vertices size = 2 ifTrue: [^ self borderWidth].
- 	vertices size == 2 ifTrue: [^ self borderWidth].
  	^ ((PolygonMorph new setVertices: vertices) rotationDegrees: self rotationDegrees negated) width!

Item was changed:
  ----- Method: ScrollPane>>hideOrShowScrollBars (in category 'scrolling') -----
  hideOrShowScrollBars
  
  	| wasHShowing wasVShowing |
  
  	wasVShowing := self vIsScrollbarShowing.
  	wasHShowing := self hIsScrollbarShowing.
  
  	self 
  		vHideOrShowScrollBar; 
  		hHideOrShowScrollBar; 
  		resizeScrollBars.
  
  	(wasVShowing and: [self vIsScrollbarShowing not]) ifTrue:
  		["Make sure the delta is 0"
+ 		(scroller offset y = 0) 
- 		(scroller offset y == 0) 
  				ifFalse:[ scroller offset: (scroller offset x at 0) ]].
  			
  	(wasHShowing and: [self hIsScrollbarShowing not]) ifTrue:
  		[(scroller offset x <= 0)
  				ifFalse:[ scroller offset: (self hMargin negated at scroller offset y)]].
  !

Item was changed:
  ----- Method: SimpleHierarchicalListMorph>>arrowKey: (in category 'keyboard navigation') -----
  arrowKey: aChar
  	"Handle a keyboard navigation character. Answer true if handled, false if not."
  	| keyEvent |
  	keyEvent := aChar asciiValue.
+      keyEvent = 31 ifTrue:["down"
-      keyEvent == 31 ifTrue:["down"
  		self setSelectionIndex: self getSelectionIndex+1.
  		^true].
+      keyEvent = 30 ifTrue:["up"
-      keyEvent == 30 ifTrue:["up"
  		self setSelectionIndex: (self getSelectionIndex-1 max: 1).
  		^true].
+      keyEvent = 1  ifTrue: ["home"
-      keyEvent == 1  ifTrue: ["home"
  		self setSelectionIndex: 1.
  		^true].
+      keyEvent = 4  ifTrue: ["end"
-      keyEvent == 4  ifTrue: ["end"
  		self setSelectionIndex: scroller submorphs size.
  		^true].
+       keyEvent = 11 ifTrue: ["page up"
-       keyEvent == 11 ifTrue: ["page up"
  		self setSelectionIndex: (self getSelectionIndex - self numSelectionsInView max: 1).
  		^true].
+      keyEvent = 12  ifTrue: ["page down"
-      keyEvent == 12  ifTrue: ["page down"
  		self setSelectionIndex: self getSelectionIndex + self numSelectionsInView.
  		^true].
+ 	keyEvent = 29 ifTrue:["right"
- 	keyEvent == 29 ifTrue:["right"
  		selectedMorph ifNotNil:[
  			(selectedMorph canExpand and:[selectedMorph isExpanded not])
  				ifTrue:[self toggleExpandedState: selectedMorph]
  				ifFalse:[self setSelectionIndex: self getSelectionIndex+1].
  		].
  		^true].
+ 	keyEvent = 28 ifTrue:["left"
- 	keyEvent == 28 ifTrue:["left"
  		selectedMorph ifNotNil:[
  			(selectedMorph isExpanded)
  				ifTrue:[self toggleExpandedState: selectedMorph]
  				ifFalse:[self setSelectionIndex: (self getSelectionIndex-1 max: 1)].
  		].
  		^true].
  	^false!

Item was changed:
  ----- Method: SystemWindow>>holdsTranscript (in category 'panes') -----
  holdsTranscript
  	"ugh"
  	| plug |
+ 	^ paneMorphs size = 1 and: [((plug := paneMorphs first) isKindOf: PluggableTextMorph) and: [plug model isKindOf: TranscriptStream]]!
- 	^ paneMorphs size == 1 and: [((plug := paneMorphs first) isKindOf: PluggableTextMorph) and: [plug model isKindOf: TranscriptStream]]!

Item was changed:
  ----- Method: SystemWindow>>takeOutOfWindow (in category 'menu') -----
  takeOutOfWindow
  	"Take the receiver's pane morph out the window and place it, naked, where once the window was"
  	| aMorph |
+ 	paneMorphs size = 1 ifFalse: [^ Beeper beep].
- 	paneMorphs size == 1 ifFalse: [^ Beeper beep].
  	aMorph := paneMorphs first.
  	owner addMorphFront: aMorph.
  	self delete!

Item was changed:
  ----- Method: SystemWindow>>titleAndPaneText (in category 'panes') -----
  titleAndPaneText
  	"If the receiver represents a workspace, return an Association between the title and that text, else return nil"
+ 	(paneMorphs size ~= 1 or: [(paneMorphs first isKindOf: PluggableTextMorph) not])
- 	(paneMorphs size ~~ 1 or: [(paneMorphs first isKindOf: PluggableTextMorph) not])
  		ifTrue: [^ nil].
  	^ labelString -> paneMorphs first text
  
  !

Item was changed:
  ----- Method: UpdatingMenuItemMorph>>updateContents (in category 'world') -----
  updateContents
  	"Update the receiver's contents"
  
  	| newString enablement nArgs |
  	((wordingProvider isNil) or: [wordingSelector isNil]) ifTrue: [^ self].
  	nArgs := wordingSelector numArgs.
+ 	newString := nArgs = 0
- 	newString := nArgs == 0
  		ifTrue:
  			[wordingProvider perform: wordingSelector]
  		ifFalse:
+ 			[(nArgs = 1 and: [wordingArgument notNil])
- 			[(nArgs == 1 and: [wordingArgument notNil])
  				ifTrue:
  					[wordingProvider perform: wordingSelector with: wordingArgument]
  				ifFalse:
  					[nArgs == arguments size ifTrue:
  						[wordingProvider perform: wordingSelector withArguments: arguments]]].
  	newString = (self contentString ifNil: [ contents ])
  		ifFalse: [self contents: newString.
  			MenuIcons decorateMenu: owner ].
  	enablementSelector ifNotNil:
  		[(enablement := self enablement) == isEnabled 
  			ifFalse:	[self isEnabled: enablement]]!




More information about the Squeak-dev mailing list