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

commits at source.squeak.org commits at source.squeak.org
Sun Feb 21 04:28:22 UTC 2016


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

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

Name: VMMaker.oscog-eem.1689
Author: eem
Time: 20 February 2016, 8:26:37.272946 pm
UUID: 4c473a09-7e78-4c59-b779-f2ad17e318ed
Ancestors: VMMaker.oscog-eem.1688

ThreadedFFIPlugin:
Arrange that the plugin includes sqFFI.h, but defines ThreadedFFIPlugin as 1 before hand so as to prevent sqFFI.h from declaring the old API.  This allows the preambleCCode to eliminate its declarations of the surface functions, which (of course0 fall foul of using ints where longts must be used on 64-bits.  Since sqFFI.h declares these functions and is included everywhere relevant it is the gospel here.

StackInterpreter: Eliminate warnings from followForwardingPointersInStackZone: by following the approach taken by the CoInterpreter's version.

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

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become.
  
  	 Override to handle machine code frames"
  	| theIPPtr |
  	<inline: false>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage headFP.
+ 			 "Skip the instruction pointer on top of stack of inactive pages."
  			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 self assert: (objectMemory isForwarded: (self mframeHomeMethod: theFP) methodObject) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop |
  						 newOop := objectMemory followForwarded: oop.
  						 offset := newOop - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + offset].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + offset.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)]].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #theFP type: #'char *'>
+ 	<var: #theIPPtr type: #usqInt>
- 	<var: #theIPPtr type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
+ 			[theIPPtr := instructionPointer - method asVoidPointer.
- 			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
+ 		[:i| | thePage theFP callerFP offset oop |
- 		[:i| | thePage theFP callerFP ptr oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
+ 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
- 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP].
  			 [self assert: (thePage addressIsInPage: theFP).
+ 			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
- 			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
+ 			  offset := self frameStackedReceiverOffset: theFP.
+ 			  oop := stackPages longAt: theFP + offset.
- 			  ptr := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger.
- 			  oop := stackPages longAt: ptr.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
+ 					longAt: theFP + offset
- 					longAt: ptr
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
+ 				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
- 				[theIPPtr := (theFP + FoxCallerSavedIP) asInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: ThreadedFFIPlugin class>>preambleCCode (in category 'translation') -----
  preambleCCode
  	"For a source of builtin defines grep for builtin_define in a gcc release config directory."
  	^'
  #include "sqAssert.h" /* for assert */
+ #define ThreadedFFIPlugin 1 /* to filter-out unwanted declarations from sqFFI.h */
+ #include "sqFFI.h" /* for logging and surface functions */
  
  #ifdef _MSC_VER
  # define alloca _alloca
  #endif
  #if defined(__GNUC__) && (defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__))
  # define setsp(sp) asm volatile ("movl %0,%%esp" : : "m"(sp))
  # define getsp() ({ void *esp; asm volatile ("movl %%esp,%0" : "=r"(esp) : ); esp;})
  # elif defined(__GNUC__) && (defined(__arm__))
  # define setsp(sp) asm volatile ("ldr %%sp, %0" : : "m"(sp))
  # define getsp() ({ void *sp; asm volatile ("mov %0, %%sp" : "=r"(sp) : ); sp;})
  #endif
  #if !!defined(getsp)
  # define getsp() 0
  #endif 
  #if !!defined(setsp)
  # define setsp(ignored) 0
  #endif 
  
  #if !!defined(STACK_ALIGN_BYTES)
  # if __APPLE__ && __MACH__ && __i386__
  #  define STACK_ALIGN_BYTES 16
  # elif __linux__ && __i386__
  #  define STACK_ALIGN_BYTES 16
  # elif defined(__amd64__) || defined(__x86_64__) ||  defined(__amd64) || defined(__x86_64)
  #  define STACK_ALIGN_BYTES 16
  # elif defined(powerpc) || defined(__powerpc__) || defined(_POWER) || defined(__POWERPC__) || defined(__PPC__)
  #  define STACK_ALIGN_BYTES 16
  # elif defined(__sparc64__) || defined(__sparcv9__) || defined(__sparc_v9__) /* must precede 32-bit sparc defs */
  #  define STACK_ALIGN_BYTES 16
  # elif defined(sparc) || defined(__sparc__) || defined(__sparclite__)
  #  define STACK_ALIGN_BYTES 8
  # elif defined(__arm__) 
  #  define STACK_ALIGN_BYTES 8
  # else
  #  define STACK_ALIGN_BYTES 0
  # endif
  #endif /* !!defined(STACK_ALIGN_BYTES) */
  
  #if !!defined(STACK_OFFSET_BYTES)
  # define STACK_OFFSET_BYTES 0
  #endif
  
  #if defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__)
  /* Both Mac OS X x86 and Win32 x86 return structs of a power of two in size
   * less than or equal to eight bytes in length in registers. Linux never does so.
   */
  # if __linux__
  #	define WIN32_X86_STRUCT_RETURN 0
  # else
  #	define WIN32_X86_STRUCT_RETURN 1
  # endif
  # if WIN32
  #	define PLATFORM_API_USES_CALLEE_POPS_CONVENTION 1
  # endif
  #endif /* defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__) */
  
  #if !!defined(ALLOCA_LIES_SO_USE_GETSP)
  # if defined(__MINGW32__) && (__GNUC__ >= 3)
      /*
       * cygwin -mno-cygwin (MinGW) gcc 3.4.x''s alloca is a library routine that answers
       * %esp + 4, so the outgoing stack is offset by one word if uncorrected.
       * Grab the actual stack pointer to correct.
       */
  #	define ALLOCA_LIES_SO_USE_GETSP 1
  # else
  #	define ALLOCA_LIES_SO_USE_GETSP 0
  # endif
  #endif /* !!defined(ALLOCA_LIES_SO_USE_GETSP) */
  
  #if !!defined(PLATFORM_API_USES_CALLEE_POPS_CONVENTION)
  # define PLATFORM_API_USES_CALLEE_POPS_CONVENTION 0
  #endif
  
  /* The dispatchOn:in:with:with: generates an unwanted call on error.  Just squash it. */
  #define error(foo) 0
  #ifndef SQUEAK_BUILTIN_PLUGIN
  /* but print assert failures. */
  void
  warning(char *s) { /* Print an error message but don''t exit. */
  	printf("\n%s\n", s);
  }
  #endif
  
  /* sanitize */
  #ifdef SQUEAK_BUILTIN_PLUGIN
  # define EXTERN 
  #else
  # define EXTERN extern
  #endif
- int ffiLogCallOfLength(void *, int);               			/* sqFFIPlugin.c */
- int ffiLogFileNameOfLength(void *, int);             		/* sqFFIPlugin.c */
- EXTERN void initSurfacePluginFunctionPointers();				/* sqManualSurface.c */
- EXTERN int createManualSurface(int, int, int, int, int); 	/* sqManualSurface.c */
- EXTERN int destroyManualSurface(int);							/* sqManualSurface.c */
- EXTERN int setManualSurfacePointer(int, void*);				/* sqManualSurface.c */
  '!



More information about the Vm-dev mailing list