[squeak-dev] The Trunk: ST80-ul.120.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 16 04:03:34 UTC 2010


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

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

Name: ST80-ul.120
Author: ul
Time: 16 November 2010, 5:03:09.258 am
UUID: 2c431b8b-bddd-be44-a25d-35d98a0fd08c
Ancestors: ST80-ul.119

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

=============== Diff against ST80-ul.119 ===============

Item was changed:
  ----- Method: ControlManager>>findWindowSatisfying: (in category 'scheduling') -----
  findWindowSatisfying: aBlock
  	"Present a menu of window titles, and activate the one that gets chosen"
  
  	| sortAlphabetically controllers listToUse labels index |
  	sortAlphabetically := Sensor shiftPressed.
  	controllers := OrderedCollection new.
  	scheduledControllers do: [:controller |
  		controller == screenController ifFalse:
  			[(aBlock value: controller) ifTrue: [controllers addLast: controller]]].
+ 	controllers size = 0 ifTrue: [^ self].
- 	controllers size == 0 ifTrue: [^ self].
  	listToUse := sortAlphabetically
  		ifTrue: [controllers asSortedCollection: [:a :b | a view label < b view label]]
  		ifFalse: [controllers].
  	labels := String streamContents:
  		[:strm | 
  			listToUse do: [:controller | strm nextPutAll: (controller view label contractTo: 40); cr].
  		strm skip: -1  "drop last cr"].
  	index := (UIManager default chooseFrom: labels lines).
  	index > 0 ifTrue:
  		[self activateController: (listToUse at: index)].
  !

Item was changed:
  ----- Method: FormInspectView>>displayView (in category 'as yet unclassified') -----
  displayView 
  	"Display the form as a value in an inspector.  8/11/96 sw"
  	"Defeated form scaling for HS FormInspector.  8/20/96 di"
  	| scale |
  	Display fill: self insetDisplayBox fillColor: Color white.
+ 	model selectionIndex = 0 ifTrue: [^ self].
- 	model selectionIndex == 0 ifTrue: [^ self].
  	scale := self insetDisplayBox extent / model selection extent.
  	scale := (scale x min: scale y) min: 1.
  	model selection
  		displayOn: Display
  		transformation: (WindowingTransformation
  			scale: scale asPoint
  			translation: self insetDisplayBox topLeft - model selection offset)
  		clippingBox: self insetDisplayBox
  		rule: self rule
  		fillColor: self fillColor!

Item was changed:
  ----- Method: ListController>>markerDelta (in category 'marker adjustment') -----
  markerDelta
  
  	| viewList |
  	viewList := view list.
+ 	viewList compositionRectangle height = 0 ifTrue: [
- 	viewList compositionRectangle height == 0 ifTrue: [
  		^ (marker top - scrollBar inside top) - scrollBar inside height
  	].
  	^ (marker top - scrollBar inside top) -
  		((viewList clippingRectangle top -
  				viewList compositionRectangle top) asFloat /
  			viewList compositionRectangle height asFloat *
  			scrollBar inside height asFloat) rounded
  !

Item was changed:
  ----- Method: ListController>>processKeyboard (in category 'menu messages') -----
  processKeyboard
  	"Derived from a Martin Pammer submission, 02/98"
  
       | keyEvent oldSelection nextSelection max min howMany |
  	sensor keyboardPressed ifFalse: [^ self].
  
       keyEvent := sensor keyboard asciiValue.
       oldSelection := view selection.
       nextSelection := oldSelection.
       max := view maximumSelection.
       min := view minimumSelection.
       howMany := view clippingBox height // view list lineGrid.
  
+      keyEvent = 31 ifTrue:
-      keyEvent == 31 ifTrue:
  		["down-arrow; move down one, wrapping to top if needed"
  		nextSelection := oldSelection + 1.
  		nextSelection > max ifTrue: [nextSelection := 1]].
  
+      keyEvent = 30 ifTrue:
-      keyEvent == 30 ifTrue:
  		["up arrow; move up one, wrapping to bottom if needed"
  		nextSelection := oldSelection - 1.
  		nextSelection < 1 ifTrue: [nextSelection := max]].
  
+      keyEvent = 1  ifTrue: [nextSelection := 1].  "home"
+      keyEvent = 4  ifTrue: [nextSelection := max].   "end"
+      keyEvent = 11 ifTrue: [nextSelection := min max: (oldSelection -
-      keyEvent == 1  ifTrue: [nextSelection := 1].  "home"
-      keyEvent == 4  ifTrue: [nextSelection := max].   "end"
-      keyEvent == 11 ifTrue: [nextSelection := min max: (oldSelection -
  howMany)].  "page up"
+      keyEvent = 12  ifTrue: [nextSelection := (oldSelection + howMany)
-      keyEvent == 12  ifTrue: [nextSelection := (oldSelection + howMany)
  min: max].  "page down"
       nextSelection = oldSelection  ifFalse:
  		[model okToChange
  			ifTrue:
  				[self changeModelSelection: nextSelection.
  				self moveMarker]]
  			!

Item was changed:
  ----- Method: ParagraphEditor>>find (in category 'menu messages') -----
  find
  	"Prompt the user for a string to search for, and search the receiver from the current selection onward for it.  1/26/96 sw"
  
  	| reply |
  	reply := UIManager default request: 'Find what? ' translated initialAnswer: ''.
+ 	reply size = 0 ifTrue: [^ self].
- 	reply size == 0 ifTrue: [^ self].
  	self setSearch: reply.
  	ChangeText := FindText.  "Implies no replacement to againOnce: method"
  	self againOrSame: true
  	
  !

Item was changed:
  ----- Method: ParagraphEditor>>saveContentsInFile (in category 'menu messages') -----
  saveContentsInFile
  	"Save the receiver's contents string to a file, prompting the user for a file-name.  Suggest a reasonable file-name."
  
  	| fileName stringToSave parentWindow labelToUse suggestedName |
  	stringToSave := paragraph text string.
+ 	stringToSave size = 0 ifTrue: [^ self inform: 'nothing to save.'].
- 	stringToSave size == 0 ifTrue: [^ self inform: 'nothing to save.'].
  	parentWindow := self model dependents
  						detect: [:dep | dep isKindOf: SystemWindow orOf: StandardSystemView]
  						ifNone: [nil].
  	labelToUse := parentWindow
  		ifNil: 		['Untitled']
  		ifNotNil: 	[parentWindow label].
  	suggestedName := nil.
  	#(('Decompressed contents of: '		'.gz')) do:  "can add more here..."
  		[:leaderTrailer | | lastIndex |
  			(labelToUse beginsWith: leaderTrailer first) ifTrue:
  				[suggestedName := labelToUse copyFrom: leaderTrailer first size + 1 to: labelToUse size.
  				(labelToUse endsWith: leaderTrailer last)
  					ifTrue:
  						[suggestedName := suggestedName copyFrom: 1 to: suggestedName size - leaderTrailer last size]
  					ifFalse:
  						[lastIndex := suggestedName lastIndexOf: $. ifAbsent: [0].
  						(lastIndex = 0 or: [lastIndex = 1]) ifFalse:
  							[suggestedName := suggestedName copyFrom: 1 to: lastIndex - 1]]]].
  
  	suggestedName ifNil:
  		[suggestedName := labelToUse, '.text'].
  			
  	fileName := UIManager default request: 'File name?' translated
  			initialAnswer: suggestedName.
  	fileName isEmptyOrNil ifFalse:
  		[(FileStream newFileNamed: fileName) nextPutAll: stringToSave; close]!

Item was changed:
  ----- Method: ParagraphEditor>>selectedSymbol (in category 'menu messages') -----
  selectedSymbol
  	"Return the currently selected symbol, or nil if none.  Spaces, tabs and returns are ignored"
  
  	| aString |
  	self hasCaret ifTrue: [^ nil].
  	aString := self selection string.
  	aString isOctetString ifTrue: [aString := aString asOctetString].
  	aString := self selection string copyWithoutAll: CharacterSet separators.
+ 	aString size = 0 ifTrue: [^ nil].
- 	aString size == 0 ifTrue: [^ nil].
  	Symbol hasInterned: aString  ifTrue: [:sym | ^ sym].
  
  	^ nil!

Item was changed:
  ----- Method: ParagraphEditor>>sendContentsToPrinter (in category 'menu messages') -----
  sendContentsToPrinter
  	| textToPrint printer parentWindow |
  	textToPrint := paragraph text.
+ 	textToPrint size = 0 ifTrue: [^self inform: 'nothing to print.'].
- 	textToPrint size == 0 ifTrue: [^self inform: 'nothing to print.'].
  	printer := TextPrinter defaultTextPrinter.
  	parentWindow := self model dependents 
  				detect: [:dep | dep isSystemWindow]
  				ifNone: [nil].
  	parentWindow isNil 
  		ifTrue: [printer documentTitle: 'Untitled']
  		ifFalse: [printer documentTitle: parentWindow label].
  	printer printText: textToPrint!

Item was changed:
  ----- Method: ParagraphEditor>>setSearchString: (in category 'nonediting/nontyping keys') -----
  setSearchString: characterStream
  	"Establish the current selection as the current search string."
  
  	| aString |
  	self closeTypeIn: characterStream.
  	sensor keyboard.
  	self lineSelectAndEmptyCheck: [^ true].
  	aString :=  self selection string.
+ 	aString size = 0
- 	aString size == 0
  		ifTrue:
  			[self flash]
  		ifFalse:
  			[self setSearch: aString].
  	^ true!

Item was changed:
  ----- Method: ParagraphEditor>>swapChars: (in category 'editing keys') -----
  swapChars: characterStream 
  	"Triggered byCmd-Y;.  Swap two characters, either those straddling the insertion point, or the two that comprise the selection.  Suggested by Ted Kaehler.  "
  
  	| currentSelection aString chars |
  	sensor keyboard.		"flush the triggering cmd-key character"
+ 	(chars := self selection) size = 0
- 	(chars := self selection) size == 0
  		ifTrue:
  			[currentSelection := self pointIndex.
  			self selectMark: currentSelection - 1 point: currentSelection]
  		ifFalse:
+ 			[chars size = 2
- 			[chars size == 2
  				ifFalse:
  					[view flash.  ^ true]
  				ifTrue:
  					[currentSelection := self pointIndex - 1]].
  	aString := self selection string.
  	self replaceSelectionWith: (Text string: aString reversed emphasis: emphasisHere).
  	self selectAt: currentSelection + 1.
  	^ true!

Item was changed:
  ----- Method: PluggableListView>>specialKeyPressed: (in category 'model access') -----
  specialKeyPressed: keyEvent
  	"Process the up and down arrows in a list pane."
       | oldSelection nextSelection max min howMany |
  
  	(#(1 4 11 12 30 31) includes: keyEvent) ifFalse: [ ^ false ].
  
       oldSelection := self getCurrentSelectionIndex.
       nextSelection := oldSelection.
       max := self maximumSelection.
       min := self minimumSelection.
       howMany := self numSelectionsInView.	"get this exactly??"
  
+      keyEvent = 31 ifTrue:
-      keyEvent == 31 ifTrue:
  		["down-arrow; move down one, wrapping to top if needed"
  		nextSelection := oldSelection + 1.
  		nextSelection > max ifTrue: [nextSelection := 1]].
  
+      keyEvent = 30 ifTrue:
-      keyEvent == 30 ifTrue:
  		["up arrow; move up one, wrapping to bottom if needed"
  		nextSelection := oldSelection - 1.
  		nextSelection < 1 ifTrue: [nextSelection := max]].
  
+      keyEvent = 1  ifTrue: [nextSelection := 1].  "home"
+      keyEvent = 4  ifTrue: [nextSelection := max].   "end"
+      keyEvent = 11 ifTrue: [nextSelection := min max: (oldSelection - howMany)].  "page up"
+      keyEvent = 12  ifTrue: [nextSelection := (oldSelection + howMany) min: max].  "page down"
-      keyEvent == 1  ifTrue: [nextSelection := 1].  "home"
-      keyEvent == 4  ifTrue: [nextSelection := max].   "end"
-      keyEvent == 11 ifTrue: [nextSelection := min max: (oldSelection - howMany)].  "page up"
-      keyEvent == 12  ifTrue: [nextSelection := (oldSelection + howMany) min: max].  "page down"
       nextSelection = oldSelection  ifFalse:
  		[model okToChange
  			ifTrue:
  				[self changeModelSelection: nextSelection.
  				"self controller moveMarker"]].
  	
  	^true
  			!




More information about the Squeak-dev mailing list