[Vm-dev] VM Maker: CogTools-sk.82.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 11 14:16:36 UTC 2017


Sophie Kaleba uploaded a new version of CogTools to project VM Maker:
http://source.squeak.org/VMMaker/CogTools-sk.82.mcz

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

Name: CogTools-sk.82
Author: sk
Time: 11 July 2017, 4:16:16.801546 pm
UUID: 48900e89-c6c5-4b29-a586-3d7322342e57
Ancestors: CogTools-sk.81

* change the name of the class variable VMFileSystem to CompatibilityClass
* remove the tempDirectory methods inherited from VMProfilerSymbolsManager

=============== Diff against CogTools-sk.81 ===============

Item was changed:
  ----- Method: PharoVMProfiler>>initialize (in category 'initialization') -----
  initialize
  
+ 	self initializeMost.
- 	super initializeMost.
  	self withDetails: false.
  	CompatibilityClass := PharoVMMethodConverter new.
  	expressionTextMorph := PluggableTextMorph new.
  	self initializeSymbols.!

Item was changed:
  ----- Method: SqueakVMProfiler>>initialize (in category 'initialization') -----
  initialize
+ 	self initializeMost.
- 	super initializeMost.
  	self withDetails: false.
  	CompatibilityClass := SqueakVMMethodConverter new.
  	expressionTextMorph := PluggableTextMorph new.
  	super initializeSymbols.
  	self toggleShowing: #module.!

Item was changed:
  ----- Method: VMProfilerLinuxSymbolsManager class>>shutDown: (in category 'shut down') -----
  shutDown: quitting
  	(quitting
  	 and: [#('Mac OS' 'unix') includes: Smalltalk platformName]) ifTrue:
  		[| tempDir |
  		(tempDir := self tempDirectory) notNil ifTrue:
  			 [tempDir exists ifTrue:
+ 				[CompatibilityClass deleteContentsOf: tempDir]]]!
- 				[VMFileSystem deleteContentsOf: tempDir]]]!

Item was removed:
- ----- Method: VMProfilerLinuxSymbolsManager class>>tempDirectory (in category 'accessing') -----
- tempDirectory
- 
- 	^ VMFileSystem ifNotNil: [VMFileSystem nameFordirPath:'/tmp/vmsyms'  plus:OSProcess thisOSProcess pid printString] 
- !

Item was changed:
  ----- Method: VMProfilerLinuxSymbolsManager>>initializeMost (in category 'initialize-release') -----
  initializeMost
  	| shortNames |
  	initialized := false.
  	maxAddressMask := (2 raisedToInteger: 32) - 1.
  	modulesByName := Dictionary new.
  	symbolsByModule := Dictionary new.
  	shortNames := Set new.
  	tempDir := self class tempDirectory.
+ 	CompatibilityClass ensureExistenceOfDirectory:  tempDir. 
- 	VMFileSystem ensureExistenceOfDirectory:  tempDir. 
  	modules := self primitiveExecutableModules.
  	modules := (1 to: modules size by: 2) collect:
  					[:i| | fileName shortName counter longName |
  					fileName := modules at: i.
  					(fileName beginsWith: '/dgagent') ifTrue:
  						[fileName := fileName allButFirst: 8].
+ 					shortName := CompatibilityClass nameOfFile: fileName in: tempDir.  
- 					shortName := VMFileSystem nameOfFile: fileName in: tempDir.  
  					counter := 0.
  					[shortNames includes: shortName] whileTrue:
  						[counter := counter + 1.
+ 						 shortName := (CompatibilityClass nameOfFile: fileName  in: tempDir), counter printString].
- 						 shortName := (VMFileSystem nameOfFile: fileName  in: tempDir), counter printString].
  					shortNames add: shortName.
  					longName := (modules at: i + 1)
  									ifNil: [fileName]
  									ifNotNil:
  										[:symlink|
  										symlink first = $/
  											ifTrue: [symlink]
+ 											ifFalse: [( CompatibilityClass parentPathOfFile: fileName ), '/', symlink]].
- 											ifFalse: [( VMFileSystem parentPathOfFile: fileName ), '/', symlink]].
  					"some files are off limits (e.g. /dgagent/lib/preload.so)"
+ 					(CompatibilityClass exists: longName) ifTrue:
- 					(VMFileSystem exists: longName) ifTrue:
  						[(modulesByName
  							at: longName
  							put: VMPExecutableModuleSymbol new)
  								name: longName;
  								shortName: shortName]].
  	"The primitive always answers the VM info in the first entry."
  	vmModule := modules first.
  	"now filter out the files we can't read..."
  	modules := modules select: [:m| m notNil and: [modulesByName includesKey: m name]]!

Item was changed:
  ----- Method: VMProfilerLinuxSymbolsManager>>parseSymbolsFor: (in category 'parsing') -----
  parseSymbolsFor: module
  	| proc symtab symStream |
+ 	(CompatibilityClass exists: tempDir fullName, '/', module shortName)  ifFalse:
- 	(VMFileSystem exists: tempDir fullName, '/', module shortName)  ifFalse:
  		[proc := OSProcess thisOSProcess command:
  						'objdump -j .text -tT "', module name, '" | fgrep .text | sort >"', tempDir fullName, '/', module shortName, '"'].
  	symStream := (Array new: 1000) writeStream.
  	symStream nextPut: module.
  	proc ifNotNil:
  		[[proc isComplete] whileFalse: [(Delay forMilliseconds: 25) wait]].
  	symtab := [StandardFileStream readOnlyFileNamed: (tempDir fullName,'/',module shortName) ]
  					on: Error
  					do: [:ex| "Handle flaky OSProcess stuff by reporting error and failing to parse"
  						Transcript print: ex; flush.
  						^nil].
  	[| prev |
  	 prev := self parseSymbolsFrom: symtab to: symStream.
  	 symbolsByModule
  		at: module
  		put: (self relocateSymbols: symStream contents allButFirst inModule: module).
  	 (prev notNil
  	  and: [prev limit isNil]) ifTrue: [prev limit: module limit]]
  		ensure: [symtab close]!

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager class>>shutDown: (in category 'shut down') -----
  shutDown: quitting
  	(quitting
  	 and: [#('Mac OS' 'unix') includes: Smalltalk platformName]) ifTrue:
  		[| tempDir |
  		(tempDir := self tempDirectory) notNil ifTrue:
  			 [tempDir exists ifTrue:
+ 				[CompatibilityClass deleteContentsOf: tempDir]]]!
- 				[VMFileSystem deleteContentsOf: tempDir]]]!

Item was removed:
- ----- Method: VMProfilerMacSymbolsManager class>>tempDirectory (in category 'accessing') -----
- tempDirectory
- 
- 	^ VMFileSystem ifNotNil: [VMFileSystem nameFordirPath:'private/tmp/vmsyms'  plus:OSProcess thisOSProcess pid printString] 
- !

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager>>computeLimitFor:initialShift: (in category 'parsing') -----
  computeLimitFor: module initialShift: initialShift
  	"If we can't find a non-text symbol following the last text symbol, compute the ernd of text using the size command."
  	| sizeFileName proc text size |
  	sizeFileName := module shortName, '.size'.
+ 	(CompatibilityClass exists: tempDir fullName, '/', sizeFileName) ifFalse: 
- 	(VMFileSystem exists: tempDir fullName, '/', sizeFileName) ifFalse: 
  		["N.B. Don't use the -f option (which meant flat symbols) as in El Capitan it is misinterpreted to mean -format."
  		 proc := OSProcess thisOSProcess command:
  						'cd ', tempDir fullName,
  						';size -arch ', self archName, " -f" ' "', module name, '" >"', sizeFileName, '"'.
  		 [proc isComplete] whileFalse: [(Delay forMilliseconds: 25) wait]].
  	text := (StandardFileStream readOnlyFileNamed: (tempDir fullName, '/', sizeFileName)) contentsOfEntireFile.
  	size := Integer readFrom: (text copyAfter: Character lf) readStream.
  	^size + initialShift!

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager>>initializeMost (in category 'initialize-release') -----
  initializeMost
  	| shortNames |
  	initialized := false.
  	maxAddressMask := (2 raisedToInteger: Smalltalk wordSize * 8) - 1.
  	modulesByName := Dictionary new.
  	symbolsByModule := Dictionary new.
  	shortNames := Set new.
  	modules := self primitiveExecutableModulesAndOffsets.
  	tempDir := self class tempDirectory.
+ 	CompatibilityClass ensureExistenceOfDirectory:  tempDir. 
- 	VMFileSystem ensureExistenceOfDirectory:  tempDir. 
  	modules := (1 to: modules size by: 4) collect:
  					[:i| | shortName counter |
+ 					shortName := CompatibilityClass nameOfFile: (modules at: i) in: tempDir. 
- 					shortName := VMFileSystem nameOfFile: (modules at: i) in: tempDir. 
  					counter := 0.
  					[shortNames includes: shortName] whileTrue:
  						[counter := counter + 1.
+ 						shortName := (CompatibilityClass nameOfFile: (modules at: i) in: tempDir), counter printString].  
- 						shortName := (VMFileSystem nameOfFile: (modules at: i) in: tempDir), counter printString].  
  					shortNames add: shortName.
  					(modulesByName
  						at: (modules at: i)
  						put: VMPExecutableModuleSymbol new)
  								name: (modules at: i);
  								shortName: shortName;
  								vmshift: (modules at: i + 1);
  								address: (maxAddressMask bitAnd: (modules at: i + 2) + (modules at: i + 1));
  								size: (modules at: i + 3)].
  	modules := self filter: modules.
  	"The primitive always answers the VM info in the first entry."
  	vmModule := modules first.
  	modules := modules asSortedCollection: [:m1 :m2| m1 address <= m2 address]!

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager>>parseSymbolsFor: (in category 'parsing') -----
  parseSymbolsFor: module
  	| proc symtab symStream |
+ 	(CompatibilityClass exists: tempDir fullName, '/', module shortName) ifFalse: 
- 	(VMFileSystem exists: tempDir fullName, '/', module shortName) ifFalse: 
  		["N.B. Don't use the -f option (which meant flat symbols) as in El Capitan it is misinterpreted to mean -format."
  		 proc := OSProcess thisOSProcess command:
  						'cd ', tempDir fullName,
  						';nm -n -arch ', self archName, " -f" ' "', module name, '" | grep -v " [aAU] " >"', module shortName, '"'].
  	symStream := (Array new: 1000) writeStream.
  	symStream nextPut: module.
  	proc ifNotNil: [[proc isComplete] whileFalse: [(Delay forMilliseconds: 25) wait]].
  	symtab := [StandardFileStream readOnlyFileNamed: (tempDir fullName, '/', module shortName)]
  					on: Error
  					do: [:ex| "Handle flaky OSProcess stuff by reporting error and failing to parse"
  						Transcript print: ex; flush.
  						^nil].
  	"Have caller eliminate modules with no text."
  	symtab size = 0 ifTrue:
  		[^nil].
  	module shortName = 'HIToolbox' ifTrue: [self halt].
  	[| prev |
  	 prev := self parseSymbolsFrom: symtab to: symStream.
  	"CoreAUC has a huge chunk of data at the end of its text segment that causes the profiler to spend ages
  	 counting zeros.  Hack fix by setting the end of the last symbol in the text segment to a little less than 1Mb." 
  	"00000000000f1922    retq" "Mavericks 13.4"
  	"00000000000f3b21    retq" "Yosemite 14.5"
  	module shortName = 'CoreAUC' ifTrue: [prev limit: 16rf8000].
  	 symbolsByModule
  		at: module
  		put: (self relocateSymbols: symStream contents allButFirst inModule: module).
  	 (prev notNil
  	  and: [prev limit isNil]) ifTrue: [prev limit: module limit]]
  		ensure: [symtab close]!

Item was changed:
  Object subclass: #VMProfilerSymbolsManager
  	instanceVariableNames: 'modules symbolsByModule modulesByName vmModule cogModule'
+ 	classVariableNames: 'CompatibilityClass'
- 	classVariableNames: 'VMFileSystem'
  	poolDictionaries: ''
  	category: 'CogTools-VMProfiler'!

Item was changed:
  ----- Method: VMProfilerSymbolsManager class>>tempDirectory (in category 'as yet unclassified') -----
  tempDirectory
  
+ 	^ CompatibilityClass ifNotNil: [CompatibilityClass nameFordirPath:'/tmp/vmsyms'  plus:OSProcess thisOSProcess pid printString] 
- 	^ VMFileSystem ifNotNil: [VMFileSystem nameFordirPath:'/tmp/vmsyms'  plus:OSProcess thisOSProcess pid printString] 
  !

Item was changed:
  ----- Method: VMProfilerSymbolsManager class>>using: (in category 'as yet unclassified') -----
+ using: aCompatibilityClass
- using: aFileSystem
  
+ 	CompatibilityClass := aCompatibilityClass.
- 	VMFileSystem := aFileSystem.
  	^ self new 
  	!



More information about the Vm-dev mailing list