[Vm-dev] VM Maker: VMMaker.oscog-eem.1388.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jun 27 04:17:12 UTC 2015


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

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

Name: VMMaker.oscog-eem.1388
Author: eem
Time: 26 June 2015, 9:13:40.945 pm
UUID: 5946eb20-1cae-4cba-98b5-467aa146ffab
Ancestors: VMMaker.oscog-eem.1387

Newspeak:
Declare EnforceAccessControl so it can be
overridden at compile time.  Modify Slang to
provide const:declareC: for this purpose.

Add inline decls to the access modifier accessors
and use the is[Pulic|Protected|Private]Method:
forms.  Use the class vars for the access codes.

=============== Diff against VMMaker.oscog-eem.1387 ===============

Item was added:
+ ----- Method: CCodeGenerator>>const:declareC: (in category 'public') -----
+ const: constName declareC: declarationString
+ 	"Record the given C declaration for a constant."
+ 
+ 	constants
+ 		at: constName asString
+ 		put: (TDefineNode new
+ 				setName: constName asString
+ 				value: declarationString)!

Item was changed:
  ----- Method: CoInterpreter>>lookupLexicalNoMNU:from:rule: (in category 'message sending') -----
  lookupLexicalNoMNU: selector from: mixin rule: rule
  	"A shared part of the lookup for implicit receiver sends that found a lexically visible
  	method, and self and outer sends."
  	| receiverClass mixinApplication dictionary found |
  	receiverClass := objectMemory fetchClassOf: localAbsentReceiver.
  	mixinApplication := self findApplicationOfTargetMixin: mixin startingAtBehavior: receiverClass.
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: mixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
+ 	(found and: [(self isPrivateMethod: newMethod)]) ifTrue:
+ 		[^0].
+ 	^self lookupProtectedNoMNU: selector startingAt: receiverClass rule: rule!
- 	(found and: [(self accessModifierOfMethod: newMethod) = AccessModifierPrivate])
- 		ifTrue: [^0].
- 	^self lookupProtectedNoMNU: selector startingAt: receiverClass rule: rule
- !

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: 'unsigned long'.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
  	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit stackMemory breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
+ 	NewspeakVM
+ 		ifTrue:
+ 			[aCCodeGenerator
+ 				const: #EnforceAccessControl
+ 				declareC: ('#if !!defined(EnforceAccessControl) /* Allow EnforceAccessControl to be overridden on the compiler command line */\# define EnforceAccessControl ', (aCCodeGenerator cLiteralFor: EnforceAccessControl),'\#endif') withCRs]
+ 		ifFalse:
+ 			[aCCodeGenerator
+ 				removeVariable: 'localAbsentReceiver';
+ 				removeVariable: 'localAbsentReceiverOrZero';
+ 				removeVariable: 'nsMethodCache'].
- 	NewspeakVM ifFalse:
- 		[aCCodeGenerator
- 			removeVariable: 'localAbsentReceiver';
- 			removeVariable: 'localAbsentReceiverOrZero';
- 			removeVariable: 'nsMethodCache'].
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB';
  			removeVariable: 'bytecodeSetSelector'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #nsMethodCache
  		declareC: 'long nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #atCache
  		declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  		declareC: 'void (*primitiveFunctionPointer)()'.
  	aCCodeGenerator
  		var: #externalPrimitiveTable
  		declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'.
  	aCCodeGenerator var: #showSurfaceFn type: #'void *'.
  	aCCodeGenerator
  		var: #jmpBuf
  		declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedCallbacks
  		declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedMethods
  		declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #interruptCheckChain
  		declareC: 'void (*interruptCheckChain)(void) = 0'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was changed:
  ----- Method: StackInterpreter>>accessModifierOfMethod: (in category 'compiled methods') -----
  accessModifierOfMethod: methodObj
  	<option: #NewspeakVM>
+ 	<inline: true>
  	^self accessModifierOfMethodHeader: (objectMemory methodHeaderOf: methodObj)!

Item was changed:
  ----- Method: StackInterpreter>>accessModifierOfMethodHeader: (in category 'compiled methods') -----
  accessModifierOfMethodHeader: header
  	<option: #NewspeakVM>
+ 	<inline: true>
  	"accessModifier bits:
  		 00 public
  		 01 private
  		 10 protected
  		 11 undefined"
+ 	^EnforceAccessControl
- 	^self cppIf: EnforceAccessControl
  		ifTrue: [header >> MethodHeaderFlagBitPosition bitAnd: 3]
  		ifFalse: [AccessModifierPublic]!

Item was changed:
  ----- Method: StackInterpreter>>isPrivateMethod: (in category 'compiled methods') -----
  isPrivateMethod: methodObj
  	<option: #NewspeakVM>
+ 	<inline: true>
+ 	^(self accessModifierOfMethod: methodObj) = AccessModifierPrivate!
- 	^(self accessModifierOfMethod: methodObj) = 1!

Item was changed:
  ----- Method: StackInterpreter>>isProtectedMethod: (in category 'compiled methods') -----
  isProtectedMethod: methodObj
  	<option: #NewspeakVM>
+ 	<inline: true>
+ 	^(self accessModifierOfMethod: methodObj) = AccessModifierProtected!
- 	^(self accessModifierOfMethod: methodObj) = 2!

Item was changed:
  ----- Method: StackInterpreter>>isPublicMethod: (in category 'compiled methods') -----
  isPublicMethod: methodObj
  	<option: #NewspeakVM>
+ 	<inline: true>
+ 	^(self accessModifierOfMethod: methodObj) = AccessModifierPublic!
- 	^(self accessModifierOfMethod: methodObj) = 0!

Item was changed:
  ----- Method: StackInterpreter>>lookupLexical:from:rule: (in category 'message sending') -----
  lookupLexical: selector from: mixin rule: rule
  	"A shared part of the lookup for implicit receiver sends that found a lexically visible
  	method, and self and outer sends."
  	| receiverClass mixinApplication dictionary found |
  	receiverClass := objectMemory fetchClassOf: localAbsentReceiver.
  	lkupClass := receiverClass. "For use by MNU"
  	mixinApplication := self findApplicationOfTargetMixin: mixin startingAtBehavior: receiverClass.
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: mixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
+ 	(found and: [(self isPrivateMethod: newMethod)]) ifTrue:
+ 		[^rule].
- 	(found and: [(self accessModifierOfMethod: newMethod) = AccessModifierPrivate])
- 		ifTrue: [^rule].
  	^self lookupProtected: selector startingAt: receiverClass rule: rule
  !

Item was changed:
  ----- Method: StackInterpreter>>lookupMethodNoMNUEtcInClass: (in category 'message sending') -----
  lookupMethodNoMNUEtcInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
  	| currentClass dictionary found |
  	<inline: false>
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
+ 		 found := self lookupMethodInDictionary: dictionary.
+ 		 self cppIf: #NewspeakVM
- 		found := self lookupMethodInDictionary: dictionary.
- 		self cppIf: #NewspeakVM
  			ifTrue:
  				[found ifTrue:
+ 					[(self isPublicMethod: newMethod) ifTrue:
+ 						[self addNewMethodToCache: class. ^0].
+ 					(self isProtectedMethod: newMethod) ifTrue:
+ 						[^SelectorDoesNotUnderstand]]]
- 					[(self accessModifierOfMethod: newMethod) == AccessModifierPublic
- 						ifTrue: [self addNewMethodToCache: class. ^0].
- 					(self accessModifierOfMethod: newMethod) == AccessModifierProtected
- 						ifTrue: [^SelectorDoesNotUnderstand]]]
  			ifFalse:
+ 				[found ifTrue:
+ 					[self addNewMethodToCache: class. ^0]].
+ 		 currentClass := self superclassOf: currentClass].
- 				[found ifTrue: [self addNewMethodToCache: class. ^0]].
- 		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackInterpreter>>lookupOrdinaryNoMNUEtcInClass: (in category 'message sending') -----
  lookupOrdinaryNoMNUEtcInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
  	| currentClass dictionary found |
  	<inline: false>
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
  		found := self lookupMethodInDictionary: dictionary.
  		self cppIf: #NewspeakVM
  			ifTrue:
  				[found ifTrue:
+ 					[(self isPublicMethod: newMethod) ifTrue:
+ 						[self addNewMethodToCache: class. ^0].
+ 					(self isProtectedMethod: newMethod) ifTrue:
+ 						[lkupClass := class. ^SelectorDoesNotUnderstand]]]
- 					[(self accessModifierOfMethod: newMethod) == AccessModifierPublic
- 						ifTrue: [self addNewMethodToCache: class. ^0].
- 					(self accessModifierOfMethod: newMethod) == AccessModifierProtected
- 						ifTrue: [lkupClass := class. ^SelectorDoesNotUnderstand]]]
  			ifFalse:
+ 				[found ifTrue:
+ 					[self addNewMethodToCache: class. ^0]].
- 				[found ifTrue: [self addNewMethodToCache: class. ^0]].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackInterpreter>>lookupOrdinarySend (in category 'message sending') -----
  lookupOrdinarySend
  	"Do the full lookup for an ordinary send (i.e., a Newspeak or Smalltalk ordinary send or a Smalltalk super send).
  	IN: lkupClass
  	IN: messageSelector
  	IN: argumentCount
  	OUT: newMethod
  	OUT: primitiveIndex
  	RESULT: LookupOrdinary or LookupDNU"
  	<option: #NewspeakVM>
  	| currentClass dictionary found |
  	self assert: (self addressCouldBeClassObj: lkupClass).
  	currentClass := lkupClass.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		found := self lookupMethodInDictionary: dictionary.
  		found ifTrue:
+ 			[(self isPublicMethod: newMethod) ifTrue:
+ 				[^self].
+ 			(self isProtectedMethod: newMethod) ifTrue:
+ 				[^self lookupDnuPresent]].
- 			[(self accessModifierOfMethod: newMethod) == AccessModifierPublic
- 				ifTrue: [^self].
- 			(self accessModifierOfMethod: newMethod) == AccessModifierProtected
- 				ifTrue: [^self lookupDnuPresent]].
  		currentClass := self superclassOf: currentClass].
  	^self lookupDnuPresent!

Item was changed:
  ----- Method: StackInterpreter>>printMethodCacheFor: (in category 'debug printing') -----
  printMethodCacheFor: thing
  	<api>
  	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
  		[:i | | s c m p |
  		s := methodCache at: i + MethodCacheSelector.
  		c := methodCache at: i + MethodCacheClass.
  		m := methodCache at: i + MethodCacheMethod.
  		p := methodCache at: i + MethodCachePrimFunction.
  		((thing = -1 or: [s = thing or: [c = thing or: [p = thing or: [m = thing]]]])
  		 and: [(objectMemory addressCouldBeOop: s)
  		 and: [c ~= 0
  		 and: [(self addressCouldBeClassObj: c)
  			or: [self addressCouldBeClassObj: (objectMemory classForClassTag: c)]]]]) ifTrue:
  			[self cCode: [] inSmalltalk: [self transcript ensureCr].
  			 self printNum: i; cr; tab.
  			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: [self cCode: 'printf("%lx %.*s\n", s, numBytesOf(s), (char *)firstIndexableField(s))'
- 				ifTrue: [self cCode: 'printf("%x %.*s\n", s, numBytesOf(s), (char *)firstIndexableField(s))'
  						inSmalltalk: [self printHex: s; space; print: (self stringOf: s); cr]]
  				ifFalse: [self shortPrintOop: s].
  			 self tab.
  			 (self addressCouldBeClassObj: c)
  				ifTrue: [self shortPrintOop: c]
  				ifFalse: [self printNum: c; space; shortPrintOop: (objectMemory classForClassTag: c)].
  			self tab; shortPrintOop: m; tab.
  			self cCode:
  					[p > 1024
  						ifTrue: [self printHexnp: p]
  						ifFalse: [self printNum: p]]
  				inSmalltalk:
  					[p isSymbol ifTrue: [self print: p] ifFalse: [self printNum: p]].
  			self cr]]!



More information about the Vm-dev mailing list