[squeak-dev] The Trunk: System-ul.757.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Aug 14 20:34:46 UTC 2015


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

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

Name: System-ul.757
Author: ul
Time: 14 August 2015, 7:19:00.474 pm
UUID: fca51b99-736e-4666-acac-e5c5b6a1d397
Ancestors: System-cmm.756

#includesSubString: -> #includesSubstring:
#subStrings -> #substrings

=============== Diff against System-cmm.756 ===============

Item was changed:
  ----- Method: ChangeRecord>>methodClass: (in category 'access') -----
  methodClass: anEnvironment
  	| methodClassName methodClass |
  	(#(method #classComment) includes: type) ifFalse: [ ^ nil ].
+ 	methodClassName := class substrings
- 	methodClassName := class subStrings
  		ifEmpty: [ ^ nil ]
  		ifNotEmptyDo:
  			[ : parts | parts first asSymbol ].
  	(anEnvironment includesKey: methodClassName) ifFalse: [ ^ nil ].
  	methodClass := anEnvironment at: methodClassName.
  	^ meta
  		ifTrue: [ methodClass class ]
  		ifFalse: [ methodClass ]!

Item was changed:
  ----- Method: ChangeSet class>>scanCategory: (in category 'scanning') -----
  scanCategory: file
  	"Scan anything that involves more than one chunk; method name is historical only"
  	| itemPosition item tokens stamp isComment anIndex |
  	itemPosition := file position.
  	item := file nextChunk.
  
+ 	isComment := (item includesSubstring: 'commentStamp:').
+ 	(isComment or: [item includesSubstring: 'methodsFor:']) ifFalse:
- 	isComment := (item includesSubString: 'commentStamp:').
- 	(isComment or: [item includesSubString: 'methodsFor:']) ifFalse:
  		["Maybe a preamble, but not one we recognize; bail out with the preamble trick"
  		^{(ChangeRecord new file: file position: itemPosition type: #preamble)}].
  
  	tokens := Scanner new scanTokens: item.
  	tokens size >= 3 ifTrue:
  		[stamp := ''.
  		anIndex := tokens indexOf: #stamp: ifAbsent: [nil].
  		anIndex ifNotNil: [stamp := tokens at: (anIndex + 1)].
  
  		tokens second == #methodsFor:
  			ifTrue: [^ self scanFile: file category: tokens third class: tokens first
  							meta: false stamp: stamp].
  		tokens third == #methodsFor:
  			ifTrue: [^ self scanFile: file category: tokens fourth class: tokens first
  							meta: true stamp: stamp]].
  
  		tokens second == #commentStamp:
  			ifTrue:
  				[stamp := tokens third.
  				item := (ChangeRecord new file: file position: file position type: #classComment
  										class: tokens first category: nil meta: false stamp: stamp).
  				file nextChunk.
  				file skipStyleChunk.
  				^Array with: item].
  	^#()!

Item was changed:
  ----- Method: FileDirectory class>>openSources:andChanges:forImage: (in category '*System-Files') -----
  openSources: sourcesName andChanges: changesName forImage: imageName 
  	"Open the changes and sources files and install them in SourceFiles. Inform the user of problems regarding write permissions or CR/CRLF mixups."
  	"Note: SourcesName and imageName are full paths; changesName is a  
  	local name."
  	| sources changes msg wmsg |
  	msg := 'Squeak cannot locate &fileRef.
  
  Please check that the file is named properly and is in the
  same directory as this image.'.
  	wmsg := 'Squeak cannot write to &fileRef.
  
  Please check that you have write permission for this file.
  
  You won''t be able to save this image correctly until you fix this.'.
  
  	sources := self openSources: sourcesName forImage: imageName.
  	changes := self openChanges: changesName forImage: imageName.
  
  	((sources == nil or: [sources atEnd])
  			and: [Preferences valueOfFlag: #warnIfNoSourcesFile])
  		ifTrue: [Smalltalk platformName = 'Mac OS'
  				ifTrue: [msg := msg , '
  Make sure the sources file is not an Alias.'].
  self inform: (msg copyReplaceAll: '&fileRef' with: 'the sources file named ' , sourcesName)].
  
  	(changes == nil
  			and: [Preferences valueOfFlag: #warnIfNoChangesFile])
  		ifTrue: [self inform: (msg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)].
  
  	((Preferences valueOfFlag: #warnIfNoChangesFile) and: [changes notNil])
  		ifTrue: [changes isReadOnly
  				ifTrue: [self inform: (wmsg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)].
  
  			((changes next: 200)
+ 					includesSubstring: String crlf)
- 					includesSubString: String crlf)
  				ifTrue: [self inform: 'The changes file named ' , changesName , '
  has been injured by an unpacking utility.  Crs were changed to CrLfs.
  Please set the preferences in your decompressing program to 
  "do not convert text files" and unpack the system again.']].
  
  	SourceFiles := Array with: sources with: changes!

Item was changed:
  ----- Method: ImageSegment>>findOwnerMap: (in category 'testing') -----
  findOwnerMap: morphs
  	| st |
  	"Construct a string that has a printout of the owner chain for every morph in the list.  Need it as a string so not hold onto them."
  
  st := ''.
  morphs do: [:mm |
+ 	(st includesSubstring: mm printString) ifFalse: [
- 	(st includesSubString: mm printString) ifFalse: [
  		st := st, '
  ', mm allOwners printString]].
  Smalltalk at: #Owners put: st.
  !

Item was changed:
  ----- Method: ResourceLocator class>>make:relativeTo: (in category 'utilities') -----
  make: newURLString relativeTo: oldURLString 
  	"Local file refs are not handled well, so work around here"
+ 	^((oldURLString includesSubstring: '://') not
+ 		and: [(newURLString includesSubstring: '://') not])
- 	^((oldURLString includesSubString: '://') not
- 		and: [(newURLString includesSubString: '://') not])
  		ifTrue: [oldURLString , (UnixFileDirectory localNameFor: newURLString)]
  		ifFalse: [(newURLString asUrlRelativeTo: oldURLString asUrl) asString]!

Item was changed:
  ----- Method: SystemVersion>>isPharo (in category 'testing') -----
  isPharo
+ 	^ version includesSubstring: 'Pharo'!
- 	^ version includesSubString: 'Pharo'!

Item was changed:
  ----- Method: SystemVersion>>isSqueak (in category 'testing') -----
  isSqueak
+ 	^ version includesSubstring: 'Squeak'!
- 	^ version includesSubString: 'Squeak'!



More information about the Squeak-dev mailing list