[Vm-dev] VM Maker: VMMaker-oscog-EstebanLorenzano.239.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jun 12 14:03:03 UTC 2013


Esteban Lorenzano uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-oscog-EstebanLorenzano.239.mcz

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

Name: VMMaker-oscog-EstebanLorenzano.239
Author: EstebanLorenzano
Time: 12 June 2013, 3:59:23.041 pm
UUID: 82137893-018c-467a-8b71-cfc71ef91f33
Ancestors: VMMaker-oscog-EstebanLorenzano.238, VMMaker.oscog-eem.298

- merged with Eliot's

=============== Diff against VMMaker-oscog-EstebanLorenzano.238 ===============

Item was changed:
  ----- Method: CCodeGenerator>>checkForGlobalUsage:in: (in category 'utilities') -----
  checkForGlobalUsage: vars in: aTMethod 
  	vars do:
  		[:var |
  		(variables includes: var) ifTrue: "find the set of method names using this global var"
  			[(globalVariableUsage at: var ifAbsentPut: [Set new])
  				add: aTMethod selector]].
+ 	aTMethod clearReferencesToGlobalStruct.
- 	aTMethod referencesGlobalStructMakeZero.
  	(aTMethod locals select: [:l| self reservedWords includes: l]) do:
  		[:l| | em |
  		em := aTMethod definingClass name, '>>', aTMethod selector, ' has variable that is a C reserved word: ', l.
  		self error: em.
  		self logger cr; nextPutAll: em; cr; flush]!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>checkForGlobalUsage:in: (in category 'utilities') -----
  checkForGlobalUsage: vars in: aTMethod 
  	"override to handle global struct needs"
  	super checkForGlobalUsage: vars in: aTMethod.
+ 
- 	"if localStructDef is false, we  don't ever need to include a reference to it in a function"
- 	localStructDef ifFalse:[^self].
  	vars asSet do:
  		[:var |
  		"if any var is global and in the global var struct 
+ 		tell the TMethod it may be refering to the  struct, depending upon the #defines"
- 		tell the TMethod it will be refering to the  struct"
  		 ((variables includes: var)
  		  and: [self placeInStructure: var]) ifTrue:
+ 			[aTMethod referencesGlobalStruct]]!
- 			[aTMethod referencesGlobalStructIncrementBy: (vars occurrencesOf: var)]]!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>emitCCodeOn:doInlining:doAssertions: (in category 'C code generator') -----
  emitCCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag
  	super emitCCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag.
  
+ 	"we add an initialiser for the pointer to the global struct; "
+ 	aStream 
+ 		cr;
+ 		nextPutAll: 'void initGlobalStructure(void) {';cr;
+ 		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT_REG';cr;
+ 		nextPutAll: 'foo = &fum;' ; cr;
+ 		nextPutAll: '#endif';  cr;
+ 		nextPutAll:'}';
+ 		cr!
- 	"if the machine needs the globals structure defined locally in the interp.c file, don't add the folowing function"
- 	localStructDef ifFalse:[self emitStructureInitFunctionOn: aStream]!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>emitCVariablesOn: (in category 'C code generator') -----
  emitCVariablesOn: aStream
  	"Store the global variable declarations on the given stream.
  	 Break logic into vars for structure and vars for non-structure."
  	| structure nonstruct |
  
  	structure := WriteStream on: (String new: 32768).
  	nonstruct := WriteStream on: (String new: 32768).
  	aStream nextPutAll: '/*** Variables ***/'; cr.
  	structure
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
  		nextPutAll: '# define _iss /* define in-struct static as void */'; cr;
  		nextPutAll: 'static struct foo {'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: '# define _iss static'; cr;
  		nextPutAll: '#endif'; cr.
  	self buildSortedVariablesCollection do:
  		[ :var | | decl varString inStruct target |
  		target := (inStruct := self placeInStructure: (varString := var asString)) 
  					ifTrue: [structure]
  					ifFalse: [nonstruct].
  		decl := variableDeclarations at: varString ifAbsent: ['sqInt ' , varString].
  		decl first == $# "support cgen var: #bytecodeSetSelector declareC: '#define bytecodeSetSelector 0' hack"
  			ifTrue:
  				[target nextPutAll: decl; cr]
  			ifFalse:
  				[self isGeneratingPluginCode
  					ifTrue:
  						[varString = 'interpreterProxy'
  							ifTrue: "quite special..."
  								[self preDeclareInterpreterProxyOn: target]
  							ifFalse: [target nextPutAll: 'static ']]
  					ifFalse:
  						[(vmClass mustBeGlobal: varString) ifFalse:
  							[target nextPutAll: (inStruct ifTrue: ['_iss '] ifFalse: ['static '])]].
  				target nextPutAll: decl; nextPut: $;; cr]].
  	structure
  		nextPutAll: '#undef _iss'; cr;
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
  		nextPutAll: ' } fum;'; cr;
+ 		nextPutAll: ' #if SQ_USE_GLOBAL_STRUCT_REG';cr;
+ 		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT /* using a global reg pointer */'; cr;
+ 		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT /* using a global reg pointer */'; cr;
+ 		nextPutAll:'#else';cr;
  		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT register struct foo * foo = &fum;'; cr;
  		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT volatile register struct foo * foo = &fum;'; cr;
+ 		nextPutAll: '#endif';cr;
  		nextPutAll: '# define GIV(interpreterInstVar) (foo->interpreterInstVar)'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT /* oh, no mr bill!! */'; cr;
  		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT /* oh no, mr bill!! */'; cr;
  		nextPutAll: '# define GIV(interpreterInstVar) interpreterInstVar'; cr;
  		nextPutAll: '#endif'; cr.
  
+ 	"if the machine needs the fum structure defining locally, do it now; global register users don't need that, but DO need some batshit insane C macro fudging in order to convert the define of USE_GLOBAL_STRUCT_REG into a simple string to use in the asm clause below. Sigh."
+ 	structure
+ 		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
+ 		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT_REG';cr;
+ 		nextPutAll: '#define fooxstr(s) foostr(s)'; cr;
+ 		nextPutAll: '#define foostr(s)  #s'; cr;
+ 		nextPutAll: 'register struct foo * foo asm(fooxstr(USE_GLOBAL_STRUCT_REG));'; cr;
+ 		nextPutAll: '#else'; cr;
+ 		nextPutAll: 'static struct foo * foo = &fum;'; cr;
+ 		nextPutAll: '#endif'; cr;
+ 		nextPutAll: '#endif'; cr.
- 	"if the machine needs the fum structure defining locally, do it now"
- 	localStructDef ifTrue:
- 		[structure
- 			nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
- 			nextPutAll: 'static struct foo * foo = &fum;'; cr;
- 			nextPutAll: '#endif'; cr].
  
  	aStream
  		nextPutAll: structure contents;
  		nextPutAll: nonstruct contents;
  		cr!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>emitGlobalStructFlagOn: (in category 'C code generator') -----
  emitGlobalStructFlagOn: aStream
+ 	"Depending upon the value of structDefDefine (See also #structDefDefine:), define SQ_USE_GLOBAL_STRUCT before including the header. Also derive the flag for using the global register; define USE_GLOBAL_STRUCT_REG to do so"
- 	"Define SQ_USE_GLOBAL_STRUCT before including the header."
  
  	aStream
  		nextPutAll: '#if ';
  		nextPutAll: structDefDefine; cr;
  		nextPutAll: '# define SQ_USE_GLOBAL_STRUCT 1'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: '# define SQ_USE_GLOBAL_STRUCT 0'; cr;
  		nextPutAll: '#endif'; cr;
+ 		nextPutAll: '#if USE_GLOBAL_STRUCT_REG '; cr;
+ 		nextPutAll: '# define SQ_USE_GLOBAL_STRUCT_REG 1'; cr;
+ 		nextPutAll: '#else'; cr;
+ 		nextPutAll: '# define SQ_USE_GLOBAL_STRUCT_REG 0'; cr;
+ 		nextPutAll: '#endif'; cr;
  		cr!

Item was removed:
- ----- Method: CCodeGeneratorGlobalStructure>>emitStructureInitFunctionOn: (in category 'C code generator') -----
- emitStructureInitFunctionOn: aStream 
- 	"For the VM using a global struct for most of the global vars (useful for ARM and PPC so far), append the initGlobalStructure() function"
- 	aStream 
- 		cr;
- 		nextPutAll: 'void initGlobalStructure(void) {foo = &fum;}';
- 		cr!

Item was removed:
- ----- Method: CCodeGeneratorGlobalStructure>>globalStructDefined: (in category 'C code generator') -----
- globalStructDefined: aBool
- 	localStructDef := aBool!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>initialize (in category 'C code generator') -----
  initialize
  	super initialize.
+ 	localStructDef := nil. "ignored ivar - no longer used"
- 	localStructDef := false.
  	structDefDefine := '1'!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>structDefDefine: (in category 'initialize-release') -----
  structDefDefine: aString
+ "set the string that will appear in the C file to define whether or not to use the global struct; reasonable values would be:
+ 'USE_GLOBAL_STRUCT' - which would be defined in a header or makefile
+ '0' - which would mean never do it
+ '1' - which would mean always do it"
  	structDefDefine := aString!

Item was added:
+ ----- Method: CoInterpreter>>interpreterAllocationReserveBytes (in category 'stack pages') -----
+ interpreterAllocationReserveBytes
+ 	"At a rough approximation we may need to allocate up to a couple
+ 	 of page's worth of contexts when switching stack pages, assigning
+ 	 to senders, etc.  But the snapshot primitive voids all stack pages.
+ 	 So a safe margin is the size of a large context times the maximum
+ 	 number of frames per page times the number of pages."
+ 	| maxUsedBytesPerPage maxFramesPerPage |
+ 	maxUsedBytesPerPage := self stackPageFrameBytes + self stackLimitOffset.
+ 	maxFramesPerPage := maxUsedBytesPerPage / BytesPerWord // MFrameSlots.
+ 	^maxFramesPerPage * LargeContextSize * numStackPages!

Item was added:
+ ----- Method: CogVMSimulator>>ioLocalSecondsOffset (in category 'I/O primitives support') -----
+ ioLocalSecondsOffset
+ 	^DateAndTime localOffset asSeconds!

Item was changed:
  ----- Method: CrossPlatformVMMaker>>createCodeGenerator (in category 'initialize') -----
  createCodeGenerator
  	"Set up a CCodeGenerator for this VMMaker - A cross platform tree leaves it up to the makefiles to decide whether to use the global struct or not."
  	^CCodeGeneratorGlobalStructure new initialize;
- 		globalStructDefined: true;
  		structDefDefine: 'USE_GLOBAL_STRUCT';
  		logger: logger;
  		options: optionsDictionary;
  		yourself!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveUtcWithOffset (in category 'system control primitives') -----
  primitiveUtcWithOffset
  	"Answer an array with UTC microseconds since the Posix epoch and
  	the current seconds offset from GMT in the local time zone.
  	This is a named (not numbered) primitive in the null module (ie the VM)"
+ 	| resultArray |
- 	| offset resultArray |
- 
  	<export: true>
+ 	"2177452800000000 = '1/1/1970' asDate asSeconds - '1/1/1901' asDate asSeconds * 1,000,000"
+ 	objectMemory pushRemappableOop: (self positive64BitIntegerFor: self ioUTCMicroseconds - 2177452800000000).
- 	<var: #clock type: 'sqLong'>
- 	offset := self ioUTCMicroseconds - self ioLocalMicroseconds.
- 	objectMemory pushRemappableOop: (self positive64BitIntegerFor: self ioUTCMicroseconds).
  	resultArray := objectMemory instantiateClass: objectMemory classArray indexableSize: 2.
+ 	self storePointer: 0 ofObject: resultArray withValue: objectMemory popRemappableOop.
+ 	self storePointerUnchecked: 1 ofObject: resultArray withValue: (objectMemory integerObjectOf: self ioLocalSecondsOffset).
- 	self stObject: resultArray at: 1 put: objectMemory popRemappableOop.
- 	self stObject: resultArray at: 2 put: (objectMemory integerObjectOf: offset).
  	self pop: 1 thenPush: resultArray
  !

Item was changed:
  ----- Method: MacOSPowerPCOS9VMMaker>>createCodeGenerator (in category 'initialize') -----
  createCodeGenerator
  	"Set up a CCodeGenerator for this VMMaker - Mac OS uses the global struct and local def of the
  	 structure.  The global struct/loca def regime appears to be about 10% faster than the default
  	 regime for Smalltalk-intensive macro benchmarks for both the Intel and gcc 4.0 compiler on x86.
  	 eem 12/10/2008 14:34 2.16 GHz Intel Core Duo MacBook Pro Mac OS X 10.4.11"
  	^CCodeGeneratorGlobalStructure new initialize;
- 		globalStructDefined: true;
  		structDefDefine: '1';
  		"structDefDefine: 'defined(PPC) || defined(_POWER) || defined(__powerpc__) || defined(__ppc__)';"
  		logger: logger;
  		yourself!

Item was changed:
  ----- Method: NewObjectMemory>>allocate:headerSize:h1:h2:h3:doFill:format: (in category 'allocation') -----
  allocate: byteSize headerSize: hdrSize h1: baseHeader h2: classOopArg h3: extendedSize doFill: doFill format: format
  	"Allocate a new object of the given size and number of header words. (Note: byteSize already includes space for the base header word.) Initialize the header fields of the new object and fill the remainder of the object with a value appropriate for the format.
  	May cause a GC"
  
  	| newObj classOop |
  	<inline: true>
+ 	<var: #i type: #usqInt>
+ 	<var: #end type: #usqInt>
- 	<var: #i type: 'usqInt'>
- 	<var: #end type: 'usqInt'>
  	newObj := self allocateChunk: byteSize + (hdrSize - 1 * BytesPerWord).
  	newObj = 0
  		ifTrue:
  			["remap classOop because GC may move the classOop"
  			hdrSize > 1 ifTrue: [self pushRemappableOop: classOopArg].
  			newObj := self allocateChunkAfterGC: byteSize + (hdrSize - 1 * BytesPerWord).
  			hdrSize > 1 ifTrue: [classOop := self popRemappableOop].
  			newObj = 0 ifTrue: [^newObj]]
  		ifFalse: [classOop := classOopArg].
  
  	hdrSize = 3 ifTrue:
  		[self longAt: newObj put: (extendedSize bitOr: HeaderTypeSizeAndClass).
  		 self longAt: newObj + BytesPerWord put: (classOop bitOr: HeaderTypeSizeAndClass).
  		 self longAt: newObj + (BytesPerWord*2) put: (baseHeader bitOr: HeaderTypeSizeAndClass).
  		 newObj := newObj + (BytesPerWord*2)].
  
  	hdrSize = 2 ifTrue:
  		[self longAt: newObj put: (classOop bitOr: HeaderTypeClass).
  		 self longAt: newObj + BytesPerWord put: (baseHeader bitOr: HeaderTypeClass).
  		 newObj := newObj + BytesPerWord].
  
  	hdrSize = 1 ifTrue:
  		[self longAt: newObj put: (baseHeader bitOr: HeaderTypeShort)].
  
  	"clear new object"
  	doFill ifTrue:
  		[| fillWord end i |
  		 fillWord := format <= 4
+ 						ifTrue: [nilObj] "if pointers, fill with nil oop"
+ 						ifFalse: [0].
- 					ifTrue: [nilObj] "if pointers, fill with nil oop"
- 					ifFalse: [0].
  		 end := newObj + byteSize.
+ 		 i := newObj + BytesPerWord. "skip header"
- 		 i := newObj + BytesPerWord.
  		 [i < end] whileTrue:
  			[self longAt: i put: fillWord.
+ 			 i := i + BytesPerWord].
+ 		 self assert: i = freeStart.].
- 			 i := i + BytesPerWord]].
  	DoExpensiveAssertionChecks ifTrue:
  		[self okayOop: newObj.
  		 self oopHasOkayClass: newObj.
  		 (self safeObjectAfter: newObj) = freeStart ifFalse:
  			[self error: 'allocate bug: did not set header of new oop correctly']].
  
  	^newObj!

Item was changed:
  ----- Method: NewObjectMemory>>allocateChunkAfterGC: (in category 'allocation') -----
  allocateChunkAfterGC: byteSize 
+ 	"Garbage collect and then allocate a chunk of the given size. Sender must be sure
- 	"Garbage colect and then allocate a chunk of the given size. Sender must be sure
  	 that the requested size includes enough space for the header word(s)."
  	| newChunk enoughSpace |
  	<inline: true>
  	<var: #newChunk type: #usqInt>
  	enoughSpace := self sufficientSpaceToAllocate: byteSize.
  	enoughSpace ifFalse:
  		["signal that space is running low, but proceed with allocation if possible"
  		 self setSignalLowSpaceFlagAndSaveProcess].
  	(self oop: freeStart + byteSize isGreaterThan: reserveStart) ifTrue:
  		[^0 "Allocation failed.  Client should e.g. fail the primtive"].
  
+ 	"if we get here, there is enough space for allocation to succeed "
- 	"if we get here, there is enough space for allocation to  succeed "
  	newChunk := freeStart.
  	freeStart := freeStart + byteSize.
  	^self oopForPointer: newChunk!

Item was changed:
  ----- Method: NewObjectMemory>>eeAllocate:headerSize:h1:h2:h3: (in category 'allocation') -----
  eeAllocate: byteSize headerSize: hdrSize h1: baseHeader h2: classOop h3: extendedSize
  	"Allocate a new object of the given size and number of header words. (Note: byteSize already includes
+ 	 space for the base header word.) Initialize the header fields of the new object.
+ 	 Does *not* initialize the objects' fields. Will *not* cause a GC.  This version is for the execution engine's use only."
- 	 space for the base header word.) Initialize the header fields of the new object and fill the remainder of
- 	 the object with the given value.  Will not cause a GC.  This version is for the execution engine"
  
  	| newObj |
  	<inline: true>
  	<asmLabel: false>
+ 	<var: #i type: #usqInt>
+ 	<var: #end type: #usqInt>
- 	<var: #i type: 'usqInt'>
- 	<var: #end type: 'usqInt'>
  	newObj := self allocateInterpreterChunk: byteSize + (hdrSize - 1 * BytesPerWord).
  	newObj = 0 ifTrue: [^newObj].
  	hdrSize = 3 ifTrue:
  		[self longAt: newObj put: (extendedSize bitOr: HeaderTypeSizeAndClass).
  		 self longAt: newObj + BytesPerWord put: (classOop bitOr: HeaderTypeSizeAndClass).
  		 self longAt: newObj + (BytesPerWord*2) put: (baseHeader bitOr: HeaderTypeSizeAndClass).
  		 newObj := newObj + (BytesPerWord*2)].
  
  	 hdrSize = 2 ifTrue:
  		[self longAt: newObj put: (classOop bitOr: HeaderTypeClass).
  		 self longAt: newObj + BytesPerWord put: (baseHeader bitOr: HeaderTypeClass).
  		 newObj := newObj + BytesPerWord].
  
  	 hdrSize = 1 ifTrue:
  		[self longAt: newObj put: (baseHeader bitOr: HeaderTypeShort)].
  
  	DoExpensiveAssertionChecks ifTrue:
  		[self okayOop: newObj.
  		 self oopHasOkayClass: newObj.
  		 (self safeObjectAfter: newObj) = freeStart ifFalse:
  			[self error: 'allocate bug: did not set header of new oop correctly']].
  
  	^newObj!

Item was changed:
  ----- Method: NewObjectMemory>>freeStart (in category 'accessing') -----
  freeStart
+ 	"This is a horrible hack and only works because C macros are generated after Interpreter variables."
+ 	<cmacro: '() GIV(freeStart)'>
- 	"This is a horribe hack and only works because C macros are generated after Interpreter variables."
- 	<cmacro: '() freeStart'>
  	^freeStart!

Item was changed:
  ----- Method: NewObjectMemory>>loadImageSegmentFrom:outPointers: (in category 'image segment in/out') -----
  loadImageSegmentFrom: segmentWordArray outPointers: outPointerArray
  	"This primitive is called from Squeak as...
  		<imageSegment> loadSegmentFrom: aWordArray outPointers: anArray."
  
  "This primitive will load a binary image segment created by primitiveStoreImageSegment.  It expects the outPointer array to be of the proper size, and the wordArray to be well formed.  It will return as its value the original array of roots, and the erstwhile segmentWordArray will have been truncated to a size of zero.  If this primitive should fail, the segmentWordArray will, sadly, have been reduced to an unrecognizable and unusable jumble.  But what more could you have done with it anyway?"
  
  	| endSeg segOop fieldPtr fieldOop doingClass lastPtr extraSize mapOop lastOut outPtr hdrTypeBits header data |
  	<inline: false>
  	<var: #endSeg type: #usqInt>
  	<var: #segOop type: #usqInt>
  	<var: #fieldPtr type: #usqInt>
  	<var: #lastOut type: #usqInt>
  	<var: #outPtr type: #usqInt>
  	<var: #lastPtr type: #usqInt>
  
  	DoAssertionChecks ifTrue: [self verifyCleanHeaders].
  	lastOut := outPointerArray + (self lastPointerOf: outPointerArray).
  	endSeg := segmentWordArray + (self sizeBitsOf: segmentWordArray) - BaseHeaderSize.
  
  	"Version check.  Byte order of the WordArray now"
  	data := self longAt: segmentWordArray + BaseHeaderSize.
+ 	(coInterpreter readableFormat: (data bitAnd: 16rFFFF "low 2 bytes")) ifFalse:
- 	(self readableFormat: (data bitAnd: 16rFFFF "low 2 bytes")) ifFalse:
  		"Not readable -- try again with reversed bytes..."
  		[self reverseBytesFrom: segmentWordArray + BaseHeaderSize to: endSeg + BytesPerWord.
  		data := self longAt: segmentWordArray + BaseHeaderSize.
+ 		(coInterpreter readableFormat: (data bitAnd: 16rFFFF "low 2 bytes")) ifFalse:
- 		(self readableFormat: (data bitAnd: 16rFFFF "low 2 bytes")) ifFalse:
  			"Still NG -- put things back and fail"
  			[self reverseBytesFrom: segmentWordArray + BaseHeaderSize to: endSeg + BytesPerWord.
  			DoAssertionChecks ifTrue: [self verifyCleanHeaders].
  			^0]].
  	"Reverse the Byte type objects if the data is from opposite endian machine.
  	 Revese the words in Floats if from an earlier version with different Float order.
  	 Test top byte.  $d on the Mac or $s on the PC.  Rest of word is equal."
  	(data >> 16) = (self imageSegmentVersion >> 16)
  		ifTrue:
  			"Need to swap floats if the segment is being loaded into a little-endian VM from a version
  			 that keeps Floats in big-endian word order as was the case prior to the 6505 image format."
  			[(self isPlatformFloatOrderVersion: (data bitAnd: 16rFFFF "low 2 bytes")) ifFalse:
  				[self vmEndianness ~= 1 "~= 1 => little-endian" ifTrue:
  					[segOop := self oopFromChunk: segmentWordArray + BaseHeaderSize + BytesPerWord.
  					 self wordSwapFloatsFrom: segOop to: endSeg + BytesPerWord]]]
  		ifFalse: "Reverse the byte-type objects once"
  			[segOop := self oopFromChunk: segmentWordArray + BaseHeaderSize + BytesPerWord.
  				 "Oop of first embedded object"
  			self byteSwapByteObjectsFrom: segOop
  				to: endSeg + BytesPerWord
  				flipFloatsIf: (self isPlatformFloatOrderVersion: (data bitAnd: 16rFFFF "low 2 bytes"))].
  
  	"Proceed through the segment, remapping pointers..."
  	segOop := self oopFromChunk: segmentWordArray + BaseHeaderSize + BytesPerWord.
  	[segOop <= endSeg] whileTrue:
  		[(self headerType: segOop) <= 1
  			ifTrue: ["This object has a class field (type = 0 or 1) -- start with that."
  					fieldPtr := segOop - BytesPerWord.  doingClass := true]
  			ifFalse: ["No class field -- start with first data field"
  					fieldPtr := segOop + BaseHeaderSize.  doingClass := false].
  		lastPtr := segOop + (self lastPointerOf: segOop).	"last field"
  		lastPtr > endSeg ifTrue:
  			[DoAssertionChecks ifTrue: [self verifyCleanHeaders].
  			^0 "out of bounds"].
  
  		"Go through all oops, remapping them..."
  		[fieldPtr > lastPtr] whileFalse:
  			["Examine each pointer field"
  			fieldOop := self longAt: fieldPtr.
  			doingClass ifTrue:
  				[hdrTypeBits := self headerType: fieldPtr.
  				fieldOop := fieldOop - hdrTypeBits].
  			(self isIntegerObject: fieldOop)
  				ifTrue:
  					["Integer -- nothing to do"
  					fieldPtr := fieldPtr + BytesPerWord]
  				ifFalse:
  					[(fieldOop bitAnd: 3) = 0 ifFalse:
  						[^0 "bad oop"].
  					(fieldOop bitAnd: 16r80000000) = 0
  						ifTrue: ["Internal pointer -- add segment offset"
  								mapOop := fieldOop + segmentWordArray]
  						ifFalse: ["External pointer -- look it up in outPointers"
  								outPtr := outPointerArray + (fieldOop bitAnd: 16r7FFFFFFF).
  								outPtr > lastOut ifTrue:
  									[^0 "out of bounds"].
  								mapOop := self longAt: outPtr].
  					doingClass
  						ifTrue: [self longAt: fieldPtr put: mapOop + hdrTypeBits.
  								fieldPtr := fieldPtr + 8.
  								doingClass := false]
  						ifFalse: [self longAt: fieldPtr put: mapOop.
  								fieldPtr := fieldPtr + BytesPerWord].
  					segOop < youngStart ifTrue:
  						[self possibleRootStoreInto: segOop value: mapOop]]].
  		segOop := self objectAfter: segOop].
  
  	"Again, proceed through the segment checking consistency..."
  	segOop := self oopFromChunk: segmentWordArray + BaseHeaderSize + BytesPerWord.
  	[segOop <= endSeg] whileTrue:
  		[(self oopHasAcceptableClass: segOop) ifFalse:
  			[^0 "inconsistency"].
  		fieldPtr := segOop + BaseHeaderSize.		"first field"
  		lastPtr := segOop + (self lastPointerOf: segOop).	"last field"
  		"Go through all oops, remapping them..."
  		[fieldPtr > lastPtr] whileFalse:
  			["Examine each pointer field"
  			fieldOop := self longAt: fieldPtr.
  			(self oopHasAcceptableClass: fieldOop) ifFalse:
  				[^0 "inconsistency"].
  			fieldPtr := fieldPtr + BytesPerWord].
  		segOop := self objectAfter: segOop].
  
  	"Truncate the segment word array to size = BytesPerWord (vers stamp only)"
  	extraSize := self extraHeaderBytes: segmentWordArray.
  	hdrTypeBits := self headerType: segmentWordArray.
  	extraSize = 8
  		ifTrue: [self longAt: segmentWordArray-extraSize put: BaseHeaderSize + BytesPerWord + hdrTypeBits]
  		ifFalse: [header := self longAt: segmentWordArray.
  				self longAt: segmentWordArray
  					put: header - (header bitAnd: SizeMask) + BaseHeaderSize + BytesPerWord].	
  	"and return the roots array which was first in the segment"
  	DoAssertionChecks ifTrue: [self verifyCleanHeaders].
  	^self oopFromChunk: segmentWordArray + BaseHeaderSize + BytesPerWord!

Item was changed:
  ----- Method: NewObjectMemory>>maybeFillWithAllocationCheckFillerFrom:to: (in category 'allocation') -----
  maybeFillWithAllocationCheckFillerFrom: start to: end
+ 	"Fill free memory with a bit pattern for checking if the last object has been overwritten."
- 	"Fill free memory with a bit pattern for chekcing if the last object has been overwritten."
  	<inline: true>
+ 	<var: 'start' type: #usqInt>
+ 	<var: 'end' type: #usqInt>
+ 	<var: 'i' type: #usqInt>
  	AllocationCheckFiller ~= 0 ifTrue:
  		[start to: end by: BytesPerWord do:
  			[:i|
  			self longAt: i put: (AllocationCheckFiller = 16rADD4E55
  									ifTrue: [i]
  									ifFalse: [AllocationCheckFiller])]]!

Item was changed:
  ----- Method: NewObjectMemory>>oopHasAcceptableClass: (in category 'image segment in/out') -----
  oopHasAcceptableClass: signedOop
  	"Similar to oopHasOkayClass:, except that it only returns true or false."
  
  	| oopClass formatMask behaviorFormatBits oopFormatBits oop |
  	<var: #oop type: #usqInt>
  	<var: #oopClass type: #usqInt>
  
  	(self isIntegerObject: signedOop) ifTrue: [^ true].
  
  	oop := self cCoerce: signedOop to: #usqInt.
+ 	(self addressCouldBeObj: oop) ifFalse: [^ false].
  
- 	oop < freeStart ifFalse: [^ false].
- 	((oop \\ BytesPerWord) = 0) ifFalse: [^ false].
- 	(oop + (self sizeBitsOf: oop)) <= freeStart ifFalse: [^ false].
  	oopClass := self cCoerce: (self fetchClassOfNonInt: oop) to: #usqInt.
+ 	(self addressCouldBeObj: oopClass) ifFalse: [^ false].
- 
- 	(self isIntegerObject: oopClass) ifTrue: [^ false].
- 	(oopClass < freeStart) ifFalse: [^ false].
- 	((oopClass \\ BytesPerWord) = 0) ifFalse: [^ false].
  	(oopClass + (self sizeBitsOf: oopClass)) <= freeStart ifFalse: [^ false].
+ 
  	((self isPointersNonInt: oopClass) and: [(self lengthOf: oopClass) >= 3]) ifFalse: [^ false].
+ 
  	formatMask := (self isBytesNonInt: oop)
  						ifTrue: [16rC00]  "ignore extra bytes size bits"
  						ifFalse: [16rF00].
  
  	behaviorFormatBits := (self formatOfClass: oopClass) bitAnd: formatMask.
  	oopFormatBits := (self baseHeader: oop) bitAnd: formatMask.
  	behaviorFormatBits = oopFormatBits ifFalse: [^ false].
  	^ true!

Item was changed:
  ----- Method: NewObjectMemory>>safeObjectAfter: (in category 'object enumeration') -----
  safeObjectAfter: oop 
  	"Return the object or start of free space immediately following the 
  	 given object or free chunk in memory. Return freeStart when
  	 enumeration is complete.  This is for assertion checking only."
  	| sz |
+ 	<asmLabel: false>
  	(self isFreeObject: oop)
  		ifTrue: [sz := self sizeOfFree: oop]
  		ifFalse: [sz := self sizeBitsOf: oop].
  	^oop + sz >= freeStart
  		ifTrue: [freeStart]
  		ifFalse: [self oopFromChunk: oop + sz]!

Item was changed:
  ----- Method: ObjectMemory>>oopHasAcceptableClass: (in category 'image segment in/out') -----
  oopHasAcceptableClass: signedOop
  	"Similar to oopHasOkayClass:, except that it only returns true or false."
  
  	| oopClass formatMask behaviorFormatBits oopFormatBits oop |
  	<var: #oop type: #usqInt>
  	<var: #oopClass type: #usqInt>
  
  	(self isIntegerObject: signedOop) ifTrue: [^ true].
  
  	oop := self cCoerce: signedOop to: #usqInt.
+ 	(self addressCouldBeObj: oop) ifFalse: [^ false].
  
- 	oop < freeBlock ifFalse: [^ false].
- 	((oop \\ BytesPerWord) = 0) ifFalse: [^ false].
- 	(oop + (self sizeBitsOf: oop)) < freeBlock ifFalse: [^ false].
  	oopClass := self cCoerce: (self fetchClassOfNonInt: oop) to: #usqInt.
+ 	(self addressCouldBeObj: oopClass) ifFalse: [^ false].
- 
- 	(self isIntegerObject: oopClass) ifTrue: [^ false].
- 	(oopClass < freeBlock) ifFalse: [^ false].
- 	((oopClass \\ BytesPerWord) = 0) ifFalse: [^ false].
  	(oopClass + (self sizeBitsOf: oopClass)) < freeBlock ifFalse: [^ false].
+ 
  	((self isPointersNonInt: oopClass) and: [(self lengthOf: oopClass) >= 3]) ifFalse: [^ false].
- 	(self isBytesNonInt: oop)
- 		ifTrue: [ formatMask := 16rC00 ]  "ignore extra bytes size bits"
- 		ifFalse: [ formatMask := 16rF00 ].
  
+ 	formatMask := (self isBytesNonInt: oop)
+ 						ifTrue: [16rC00]  "ignore extra bytes size bits"
+ 						ifFalse: [16rF00].
+ 
  	behaviorFormatBits := (self formatOfClass: oopClass) bitAnd: formatMask.
  	oopFormatBits := (self baseHeader: oop) bitAnd: formatMask.
  	behaviorFormatBits = oopFormatBits ifFalse: [^ false].
  	^ true!

Item was changed:
  ----- Method: RiscOSVMMaker>>createCodeGenerator (in category 'initialize') -----
  createCodeGenerator
  "set up a CCodeGenerator for this VMMaker - RiscOS uses the global struct and no local def of the structure because of the global register trickery"
  	^CCodeGeneratorGlobalStructure new initialize;
- 		globalStructDefined: false;
  		logger: logger;
  		yourself!

Item was changed:
  ----- Method: StackInterpreter>>floatValueOf: (in category 'utilities') -----
  floatValueOf: oop
  	"Answer the C double precision floating point value of the argument,
  	 or fail if it is not a Float, and answer 0.
  	 Note: May be called by translated primitive code."
  
  	| isFloat result |
+ 	<asmLabel: false>
  	<returnTypeC: #double>
  	<var: #result type: #double>
  	isFloat := self isInstanceOfClassFloat: oop.
  	isFloat ifTrue:
  		[self cCode: '' inSmalltalk: [result := Float new: 2].
  		 objectMemory fetchFloatAt: oop + BaseHeaderSize into: result.
  		 ^result].
  	self primitiveFail.
  	^0.0!

Item was changed:
  ----- Method: StackInterpreter>>interpreterAllocationReserveBytes (in category 'stack pages') -----
  interpreterAllocationReserveBytes
  	"At a rough approximation we may need to allocate up to a couple
  	 of page's worth of contexts when switching stack pages, assigning
  	 to senders, etc.  But the snapshot primitive voids all stack pages.
  	 So a safe margin is the size of a large context times the maximum
  	 number of frames per page times the number of pages."
  	| maxUsedBytesPerPage maxFramesPerPage |
  	maxUsedBytesPerPage := self stackPageFrameBytes + self stackLimitOffset.
+ 	maxFramesPerPage := maxUsedBytesPerPage / BytesPerWord // FrameSlots.
- 	maxFramesPerPage := maxUsedBytesPerPage / BytesPerWord // MFrameSlots.
  	^maxFramesPerPage * LargeContextSize * numStackPages!

Item was added:
+ ----- Method: StackInterpreterSimulator>>ioLocalSecondsOffset (in category 'I/O primitives support') -----
+ ioLocalSecondsOffset
+ 	^DateAndTime localOffset asSeconds!

Item was added:
+ ----- Method: TMethod>>clearReferencesToGlobalStruct (in category 'accessing') -----
+ clearReferencesToGlobalStruct
+ 	globalStructureBuildMethodHasFoo := false!

Item was changed:
  ----- Method: TMethod>>emitCLocalsOn:generator: (in category 'C code generation') -----
  emitCLocalsOn: aStream generator: aCodeGen
  	"Emit a C function header for this method onto the given stream."
  
  	| volatileVariables |
  	volatileVariables := properties includesKey: #volatile.
+ 	self refersToGlobalStruct ifTrue:
- 	self globalStructureBuildMethodHasFoo > 1 ifTrue:
  		[aStream
  			next: 3 put: Character space; "there's already an opening ${ on this line; see sender"
  			nextPutAll: (volatileVariables
  						ifTrue: ['DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT']
  						ifFalse: ['DECL_MAYBE_SQ_GLOBAL_STRUCT'])].
  	aStream cr.
  	locals isEmpty ifFalse:
  		[(aCodeGen sortStrings: locals) do:
  			[ :var |
  			aStream next: 4 put: Character space.
  			volatileVariables ifTrue:
  				[aStream nextPutAll: #volatile; space].
  			aStream
  				nextPutAll: (self declarationAt: var);
  				nextPut: $;;
  				cr].
  		 aStream cr]!

Item was removed:
- ----- Method: TMethod>>globalStructureBuildMethodHasFoo (in category 'accessing') -----
- globalStructureBuildMethodHasFoo
- 	^globalStructureBuildMethodHasFoo!

Item was added:
+ ----- Method: TMethod>>referencesGlobalStruct (in category 'accessing') -----
+ referencesGlobalStruct
+ 	globalStructureBuildMethodHasFoo := true!

Item was removed:
- ----- Method: TMethod>>referencesGlobalStructIncrementBy: (in category 'accessing') -----
- referencesGlobalStructIncrementBy: value
- 	globalStructureBuildMethodHasFoo := globalStructureBuildMethodHasFoo + value.!

Item was removed:
- ----- Method: TMethod>>referencesGlobalStructMakeZero (in category 'accessing') -----
- referencesGlobalStructMakeZero
- 	globalStructureBuildMethodHasFoo := 0!

Item was added:
+ ----- Method: TMethod>>refersToGlobalStruct (in category 'accessing') -----
+ refersToGlobalStruct
+ 	^globalStructureBuildMethodHasFoo!

Item was changed:
  ----- Method: TMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initialization') -----
  setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
  	"Initialize this method using the given information."
  
  	selector := sel.
  	definingClass := class.
  	returnType := #sqInt. 	 "assume return type is long for now"
  	args := argList asOrderedCollection collect: [:arg | arg key].
  	locals := (localList collect: [:arg | arg key]) asSet.
  	declarations := Dictionary new.
  	self addTypeForSelf.
  	primitive := aNumber.
  	properties := methodProperties.
  	comment := aComment.
  	parseTree := aBlockNode. "hack; allows nodes to find their parent, etc"
  	parseTree := aBlockNode asTranslatorNodeIn: self.
  	labels := OrderedCollection new.
  	complete := false.  "set to true when all possible inlining has been done"
  	export := self extractExportDirective.
  	static := self extractStaticDirective.
  	canAsmLabel := self extractLabelDirective.
  	self extractSharedCase.
  	self removeFinalSelfReturn.	"must preceed recordDeclarations because this may set returnType"
  	self recordDeclarations.
+ 	globalStructureBuildMethodHasFoo := false!
- 	globalStructureBuildMethodHasFoo := 0!

Item was changed:
  ----- Method: UnixVMMaker>>createCodeGenerator (in category 'initialisation') -----
  createCodeGenerator
  
  	^CCodeGeneratorGlobalStructure new initialize;
- 		globalStructDefined: true;
  		logger: logger;
  		yourself!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakCogVM (in category 'configurations') -----
  generateNewspeakCogVM
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit"Cogit chooseCogitClass"
  		with: #(	NewspeakVM true
  				MULTIPLEBYTECODESETS true)
  		to: (FileDirectory default pathFromURI: 'oscogvm/nscogsrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
  					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
  					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
  					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin ThreadedIA32FFIPlugin
+ 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!
- 					UUIDPlugin UnixOSProcessPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakInterpreterVM (in category 'configurations') -----
  generateNewspeakInterpreterVM
  	^VMMaker
  		generate: NewspeakInterpreter
  		to: (FileDirectory default pathFromURI: 'oscogvm/nssrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
  					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
  					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
  					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
+ 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!
- 					UUIDPlugin UnixOSProcessPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakStackVM (in category 'configurations') -----
  generateNewspeakStackVM
  	^VMMaker
  		generate: StackInterpreter
  		with: #(NewspeakVM true MULTIPLEBYTECODESETS true)
  		to: (FileDirectory default pathFromURI: 'oscogvm/nsstacksrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
  					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
  					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
  					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin SqueakSSLPlugin ThreadedIA32FFIPlugin
+ 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!
- 					UUIDPlugin UnixOSProcessPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogVM (in category 'configurations') -----
  generateSqueakCogVM
  	^VMMaker
  		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
  									value: #(CoInterpreter CoInterpreterMT)))
  		and: StackToRegisterMappingCogit
  		with: #(	MULTIPLEBYTECODESETS false
  				NewspeakVM false)
  		to: (FileDirectory default pathFromURI: 'oscogvm/src')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#(	ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
  					BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin CroquetPlugin DSAPlugin
  					DeflatePlugin DropPlugin FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin
  					FloatMathPlugin GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
  					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin SecurityPlugin SerialPlugin
  					SocketPlugin SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
  					ThreadedIA32FFIPlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
+ 					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin)!
- 					Win32OSProcessPlugin VMProfileMacSupportPlugin)!

Item was added:
+ InterpreterPlugin subclass: #VMProfileLinuxSupportPlugin
+ 	instanceVariableNames: 'numModules primErr'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins'!
+ 
+ !VMProfileLinuxSupportPlugin commentStamp: 'eem 6/5/2013 12:10' prior: 0!
+ This class provides support for the VMProfiler on Linux (at least linux versions that provide dl_iterate_phdr).  This support is for reading symbols from the executable.  We can use the OS's nm command to list symbols in the VM executable and loaded libraries.  To do this we need to know what libraries are loaded, not simply which libraries are linked against, since some libraries are loaded dynamically, and for each loaded library what the vm address relocation, if any, is for the loaded library.  
+ 
+ Further, we need to know the actual addresses in memory of symbols in the program and in memory.  Since the OS may be using address randomization we cannot assume that the addresses answered by nm for symbols in the program and/or libraries match the addresses of the same symbols in memory.  Instead we must correlate.  dlsym can be used to look up symbols in loaded dynamic load libraries, but it does _not_ answer the addresses of symbols in the main program.  Back in the day nlist could be used to do this, but it is no more.  Instead this module contains a reference to interpret and answers its address ia a primitive (alas this means the plugin must be internal, but it's extremely small, and the VM links against libdl.so anyway).  Any address space shift will therefore be the difference between nm's output for interpret and the primitive's value.  We can similarly compute the address shift for libraries by using dlsym to lookup a symbol in a library and comparing it to nm's output for the library.
+ 
+ 
+ The primitive primitiveExecutableModules returns the names of the executable and the loaded libraries.!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin class>>declareHeaderFilesIn: (in category 'translation') -----
+ declareHeaderFilesIn: cg
+ 
+ 	cg
+ 		addHeaderFile: '<limits.h>';
+ 		addHeaderFile: '#ifndef _GNU_SOURCE\# define _GNU_SOURCE\#endif\#include <link.h>' withCRs!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>count:num:modules: (in category 'iteration callbacks') -----
+ count: info num: size modules: ignored
+ 	<var: #info type: #'struct dl_phdr_info *'>
+ 	<var: #size type: #'size_t'>
+ 	<var: #ignored type: #'void *'>
+ 	numModules := numModules + 1.
+ 	^0!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>primitiveDLSymInLibrary (in category 'primitives') -----
+ primitiveDLSymInLibrary
+ 	"Answer the address of the symbol whose name is the first argument
+ 	 in the library whose name is the second argument, or nil if none."
+ 	| nameObj symName libName lib sz addr ok |
+ 	<export: true>
+ 	<var: #symName type: #'char *'>
+ 	<var: #libName type: #'char *'>
+ 	<var: #lib type: #'void *'>
+ 	<var: #addr type: #'void *'>
+ 	nameObj := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isBytes: nameObj) ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 	sz := interpreterProxy byteSizeOf: nameObj.
+ 	libName := self malloc: sz+1.
+ 	self st: libName rn: (interpreterProxy firstIndexableField: nameObj) cpy: sz.
+ 	libName at: sz put: 0.
+ 	nameObj := interpreterProxy stackValue: 1.
+ 	(interpreterProxy isBytes: nameObj) ifFalse:
+ 		[self free: libName.
+ 		 ^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 	sz := interpreterProxy byteSizeOf: nameObj.
+ 	symName := self malloc: sz+1.
+ 	self st: symName rn: (interpreterProxy firstIndexableField: nameObj) cpy: sz.
+ 	symName at: sz put: 0.
+ 	lib := self dl: libName open: (#'RTLD_LAZY' bitOr: #'RTLD_NODELETE').
+ 	lib ifNil:
+ 		[self free: libName; free: symName.
+ 		 ^interpreterProxy primitiveFailFor: PrimErrInappropriate].
+ 	self dlerror. "clear dlerror"
+ 	addr := self dl: lib sym: symName.
+ 	ok := self dlerror isNil.
+ 	self free: symName.
+ 	self free: libName.
+ 	self dlclose: lib.
+ 	ok ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNotFound].
+ 	^interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: addr asUnsignedLong)!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>primitiveExecutableModules (in category 'primitives') -----
+ primitiveExecutableModules
+ 	"Answer an Array of pairs of strings for executable modules (the VM executable and loaded libraries).
+ 	 The first element in each pair is the filename of the module.  The second element is either nil or
+ 	 the symlink's target, if the filename is a symlink."
+ 	<export: true>
+ 	<var: #name type: 'const char *'>
+ 	<var: #nameObjData type: #'char *'>
+ 	| resultObj |
+ 	numModules := 0.
+ 	self cCode: 'dl_iterate_phdr(countnummodules,0)' inSmalltalk: [0].
+ 	resultObj := interpreterProxy
+ 					instantiateClass: interpreterProxy classArray
+ 					indexableSize: numModules - 1 * 2. "skip the fake linux-gate.so.1"
+ 	resultObj = 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 	interpreterProxy pushRemappableOop: resultObj.
+ 	primErr := numModules := 0.
+ 	self cCode: 'dl_iterate_phdr(reapmodulesymlinks,0)' inSmalltalk: [0].
+ 	resultObj := interpreterProxy popRemappableOop.
+ 	primErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: primErr].
+ 	^interpreterProxy methodReturnValue: resultObj!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>primitiveInterpretAddress (in category 'primitives') -----
+ primitiveInterpretAddress
+ 	"Answer the address of the interpret routine."
+ 	<export: true>
+ 	| interpret |
+ 	<var: #interpret declareC: 'extern void interpret()'>
+ 	self touch: interpret.
+ 	^interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: interpret asUnsignedLong)!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>reap:module:names: (in category 'iteration callbacks') -----
+ reap: info module: size names: ignored
+ 	| elfModuleName len moduleNameObj GetAttributeString |
+ 	<var: #info type: #'struct dl_phdr_info *'>
+ 	<var: 'elfModuleName' type: #'const char *'>
+ 	<var: #GetAttributeString declareC: 'extern char *GetAttributeString(sqInt)'>
+ 	<var: #size type: #'size_t'>
+ 	<var: #ignored type: #'void *'>
+ 	self touch: GetAttributeString.
+ 	elfModuleName := self cCode: 'numModules ? info->dlpi_name : GetAttributeString(0)'.
+ 	(elfModuleName isNil
+ 	 or: [(len := self strlen: elfModuleName) = 0]) ifTrue:
+ 		[^0]. "skip the fake linux-gate.so.1"
+ 	moduleNameObj := interpreterProxy
+ 							instantiateClass: interpreterProxy classString
+ 							indexableSize: len.
+ 	moduleNameObj = 0 ifTrue:
+ 		[primErr := PrimErrNoMemory.
+ 		 ^1]. "stop iteration"
+ 	self st: (interpreterProxy arrayValueOf: moduleNameObj)
+ 		rn: elfModuleName
+ 		cpy: len. "(char *)strncpy()"
+ 	interpreterProxy
+ 		storePointer: numModules
+ 		ofObject: interpreterProxy topRemappableOop
+ 		withValue: moduleNameObj.
+ 	numModules := numModules + 1.
+ 	^0!

Item was added:
+ ----- Method: VMProfileLinuxSupportPlugin>>reap:module:symlinks: (in category 'iteration callbacks') -----
+ reap: info module: size symlinks: ignored
+ 	"like reap:module:names:, but follows symlinks"
+ 	| elfModuleName len moduleNameObj GetAttributeString symLinkBuf |
+ 	<var: #info type: #'struct dl_phdr_info *'>
+ 	<var: 'elfModuleName' type: #'const char *'>
+ 	<var: #GetAttributeString declareC: 'extern char *GetAttributeString(sqInt)'>
+ 	<var: #symLinkBuf declareC: 'char symLinkBuf[PATH_MAX]'>
+ 	<var: #size type: #'size_t'>
+ 	<var: #ignored type: #'void *'>
+ 	self touch: GetAttributeString.
+ 	elfModuleName := self cCode: 'numModules ? info->dlpi_name : GetAttributeString(0)'.
+ 	(elfModuleName isNil
+ 	 or: [(len := self strlen: elfModuleName) = 0]) ifTrue:
+ 		[^0]. "skip the fake linux-gate.so.1"
+ 	moduleNameObj := interpreterProxy
+ 							instantiateClass: interpreterProxy classString
+ 							indexableSize: len.
+ 	moduleNameObj = 0 ifTrue:
+ 		[primErr := PrimErrNoMemory.
+ 		 ^1]. "stop iteration"
+ 	self st: (interpreterProxy arrayValueOf: moduleNameObj)
+ 		rn: elfModuleName
+ 		cpy: len. "(char *)strncpy()"
+ 	interpreterProxy
+ 		storePointer: numModules
+ 		ofObject: interpreterProxy topRemappableOop
+ 		withValue: moduleNameObj.
+ 	"now dereference the symlink, if it exists"
+ 	self str: symLinkBuf cpy: elfModuleName.
+ 	(len := self read: elfModuleName li: symLinkBuf nk: #'PATH_MAX') > 0
+ 		ifTrue:
+ 			[moduleNameObj := interpreterProxy
+ 									instantiateClass: interpreterProxy classString
+ 									indexableSize: len.
+ 			 moduleNameObj = 0 ifTrue:
+ 				[primErr := PrimErrNoMemory.
+ 				 ^1]. "stop iteration"
+ 			 self st: (interpreterProxy arrayValueOf: moduleNameObj)
+ 				rn: symLinkBuf
+ 				cpy: len. "(char *)strncpy()"
+ 			 interpreterProxy
+ 				storePointer: numModules + 1
+ 				ofObject: interpreterProxy topRemappableOop
+ 				withValue: moduleNameObj]
+ 		ifFalse:
+ 			[interpreterProxy
+ 				storePointer: numModules + 1
+ 				ofObject: interpreterProxy topRemappableOop
+ 				withValue: interpreterProxy nilObject].
+ 	numModules := numModules + 2.
+ 	^0!

Item was changed:
  ----- Method: Win32VMMaker>>createCodeGenerator (in category 'initialize') -----
  createCodeGenerator
  	"Set up a CCodeGenerator for this VMMaker - On Windows we use the gcc 2.95.x compiler
  	 which does better without the global struct."
  	^CCodeGeneratorGlobalStructure new initialize;
- 		globalStructDefined: true;
  		structDefDefine: '0';
  		"structDefDefine: 'defined(PPC) || defined(_POWER) || defined(__powerpc__) || defined(__ppc__)';"
  		logger: logger;
  		yourself!



More information about the Vm-dev mailing list