[Vm-dev] VM Maker: Cog-eem.340.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 27 20:04:52 UTC 2017


Eliot Miranda uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-eem.340.mcz

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

Name: Cog-eem.340
Author: eem
Time: 27 April 2017, 1:04:43.977266 pm
UUID: 2455965e-28fe-46f4-a9e6-9ed84870ad1f
Ancestors: Cog-eem.339

includesSubString: is deprecated.

=============== Diff against Cog-eem.339 ===============

Item was changed:
  ----- Method: CrashReportsMailer>>addReportFor: (in category 'reporting') -----
  addReportFor: lines
  	rs	resetContents;
  		tab;
  		nextPutAll: ((lines detect: [:l| l beginsWith: 'Subject:']) ifNotNil:
  							[:l| l allButFirst: (l indexOfSubCollection: ' Teleplace Bug')]);
  		crtab: 2;
  		nextPutAll: (lines detect: [:l| l beginsWith: 'Date:']);
  		cr.
+ 	((lines anySatisfy: [:l| (l beginsWith: 'OS Version') and: [l includesSubstring: 'Mac OS X']])
- 	((lines anySatisfy: [:l| (l beginsWith: 'OS Version') and: [l includesSubString: 'Mac OS X']])
  		ifTrue: [self reportForMacOS: lines]
  		ifFalse: [(lines anySatisfy: [:l| l beginsWith: 'Module:'])
  					ifTrue: [self reportForOldWin32: lines]
  					ifFalse: [self reportForNewWin32: lines]]) ifNotNil:
  			[:cause|
  			(causes at: cause ifAbsentPut: [OrderedCollection new])
  				addLast: rs contents]!

Item was changed:
  ----- Method: CrashReportsMailer>>ifCrashReport:do: (in category 'parsing') -----
  ifCrashReport: fileName do: aBlock
  	"Answer the evaluation of aBlock with the lines for fileName if it is a crash report, or nil if not."
  	| file lines subject |
  	file := mailDirectory oldFileNamed: fileName.
  	lines := [file contentsOfEntireFile]
  				on: Error
  				do: [:ex|
  					file close.
  					Transcript nextPutAll: fileName; nextPutAll: ': '; nextPutAll: ex messageText; flush.
  					^nil].
  	lines := self breakIntoLines: lines.
  	subject := lines detect: [:l| l beginsWith: 'Subject:'] ifNone: [^nil].
+ 	(subject includesSubstring: 'Teleplace Bug Report: ') ifFalse: [^nil].
- 	(subject includesSubString: 'Teleplace Bug Report: ') ifFalse: [^nil].
  	#('@qwaq.com' '@teleplace.com' '@chonkaa.com' 'craig at netjam.org' 'skysound at mac.com') do:
  		[:localEmail| (subject includesSubstring: localEmail caseSensitive: false) ifTrue: [^nil]].
  	(lines anySatisfy:
  		[:l|
+ 		((l beginsWith: 'OS Version') and: [l includesSubstring: 'Mac OS X'])
- 		((l beginsWith: 'OS Version') and: [l includesSubString: 'Mac OS X'])
  		or: [l beginsWith: 'Operating System:']]) ifFalse: [^nil].
  	^aBlock value: lines!

Item was changed:
  ----- Method: CrashReportsMailer>>reportForMacOS: (in category 'reporting') -----
  reportForMacOS: lines
  	| thread dateAndTime cStackTop cstIdx |
  
  	thread := Integer readFrom: ((lines detect: [:l| l beginsWith: 'Crashed Thread: ']) allButFirst: 15) readStream skipSeparators.
  	thread := 'Thread ', thread printString, ' Crashed'.
  	lines withIndexDo:
  		[:l :i|
  		(l beginsWith: 'Date/Time:') ifTrue:
  			[dateAndTime := l allButFirst: 11].
  		((l beginsWith: thread)
  		and: [i < lines size]) ifTrue:
  			[cStackTop := lines at: (cstIdx := i + 1)]].
  	[cstIdx <= lines size
  	 and: [(lines at: cstIdx) notEmpty]] whileTrue:
+ 		[(((lines at: cstIdx) includesSubstring: ' _sigtramp ')
+ 		 and: [((lines at: cstIdx + 1) includesSubstring: ' ??? ')
+ 		 and: [((lines at: cstIdx + 1) includesSubstring: '0xffffffff 0 + 4294967295')]]) ifTrue:
- 		[(((lines at: cstIdx) includesSubString: ' _sigtramp ')
- 		 and: [((lines at: cstIdx + 1) includesSubString: ' ??? ')
- 		 and: [((lines at: cstIdx + 1) includesSubString: '0xffffffff 0 + 4294967295')]]) ifTrue:
  			[cStackTop := lines at: cstIdx + 2.
  			 cstIdx := lines size].
  		 cstIdx := cstIdx + 1].
  	dateAndTime := self macOSDateFor: dateAndTime.
  	(dateAndTime between: startDate and: endDate) ifFalse:
  		[^nil].
  	^'Mac:', (cStackTop allButFirst: (cStackTop indexOf: Character space))!

Item was changed:
  ----- Method: GdbARMAlien>>disassembleFrom:to:in:for:labels:on: (in category 'disassembly') -----
  disassembleFrom: startAddress to: endAddress in: memory for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
  	| address |
  	address := startAddress.
  	[address <= endAddress] whileTrue:
  		[[:sizeArg :stringArg| | size string index offset |
  		size := sizeArg.
  		string := stringArg.
  		(aSymbolManager labelForPC: address) ifNotNil:
  			[:label| aStream nextPutAll: label; nextPut: $:; cr].
  		(labelDictionary at: address ifAbsent: []) ifNotNil:
  			[:label|
  			self printLabel: label on: aStream at: address for: aSymbolManager.
  			label isArray ifTrue:
  				[string := nil.
  				 size := label third]].
  		string ifNotNil:
  			[aStream nextPutAll: (self decorateDisassembly: string for: aSymbolManager fromAddress: address).
+ 			 (string includesSubstring: ': ldr	') ifTrue:"i.e. colon space 'ldr' tab" 
- 			 (string includesSubString: ': ldr	') ifTrue:"i.e. colon space 'ldr' tab" 
  				[(index := string indexOfSubCollection: ' [pc, #' startingAt: 1) > 0
  					ifTrue:
  						[offset := Integer readFrom: (ReadStream on: string from: index + 7 to: (string indexOf: $] startingAt: index + 7) - 1)]
  					ifFalse:
  						[(string indexOfSubCollection: ' [pc]' startingAt: 1) > 0 ifTrue:
  							[offset := 0]].
  				 offset ifNotNil:
  					[offset := address + 8 + offset.
  					 labelDictionary
  						at: offset
  						ifPresent:
  							[:entry|
  							entry isString
  								ifTrue: [labelDictionary at: offset put: {#literal. offset. 4. entry}]
  								ifFalse: [self assert: (entry isArray and: [entry first == #literal])]]
  						ifAbsentPut: [{#literal. offset. 4}]]]].
  		aStream cr; flush.
  		address := address + size]
  			valueWithArguments: (self
  									primitiveDisassembleAt: address
  									inMemory: memory)].
  	(labelDictionary at: address ifAbsent: []) ifNotNil:
  		[:label| self printLabel: label on: aStream at: address for: aSymbolManager]!



More information about the Vm-dev mailing list