VM Maker: VMMaker.oscog-eem.2307.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2307.mcz

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

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

Name: VMMaker.oscog-eem.2307
Author: eem
Time: 5 January 2018, 12:07:17.508019 am
UUID: bede75bd-3b6a-49d4-b6a8-14325d3573c7
Ancestors: VMMaker.oscog-eem.2306

Refactor preDeclareInterpreterProxyOn: to extract collecting the InterpreterProxy interface to its own method to simplify consistency checking.  To make the checking more correct use a concrete Sour class for the referenceObjectMemoryClass.

Fix several InterpreterProxy interface methods that don't specify a return type.

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

Item was changed:
  ----- Method: InterpreterProxy>>become:with: (in category 'other') -----
  become: array1 with: array2
+ <returnTypeC: #sqInt>
  array1 elementsExchangeIdentityWith: array2!

Item was changed:
  ----- Method: InterpreterProxy>>copyBits (in category 'BitBlt support') -----
  copyBits
+ <returnTypeC: #sqInt>
+ bb copyBits!
- bb copyBits.!

Item was changed:
  ----- Method: InterpreterProxy>>copyBitsFrom:to:at: (in category 'BitBlt support') -----
  copyBitsFrom: leftX to: rightX at: yValue
+ <returnTypeC: #sqInt>
  bb copyBitsFrom: leftX to: rightX at: yValue.!

Item was changed:
  ----- Method: InterpreterProxy>>fullDisplayUpdate (in category 'other') -----
  fullDisplayUpdate
+ <returnTypeC: #sqInt>
  Display display!

Item was changed:
  ----- Method: InterpreterProxy>>loadBitBltFrom: (in category 'BitBlt support') -----
  loadBitBltFrom: bbOop
+ <returnTypeC: #sqInt>
+ bb := bbOop!
- bb := bbOop.!

Item was changed:
  ----- Method: InterpreterProxy>>reestablishContextPriorToCallback: (in category 'callback support') -----
  reestablishContextPriorToCallback: callbackContext
  "callbackContext is an activation of invokeCallback:stack:registers:jmpbuf:.  Its sender
  is the interpreter's state prior to the callback.  Reestablish that state."
+ <returnTypeC: #sqInt>
  self notYetImplemented!

Item was changed:
  ----- Method: InterpreterProxy>>sendInvokeCallback:Stack:Registers:Jmpbuf: (in category 'callback support') -----
  sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr
  "Send the 4 argument callback message invokeCallback:stack:registers:jmpbuf:
  to Alien class with the supplied args.  The arguments are raw C addresses
  and are converted to integer objects on the way."
+ <returnTypeC: #sqInt>
  self notYetImplemented!

Item was changed:
  ----- Method: InterpreterProxy>>sendInvokeCallbackContext: (in category 'callback support') -----
  sendInvokeCallbackContext: vmCallbackContext
  <var: #vmCallbackContext type: #'VMCallbackContext *'>
  "Send the calllback message to Alien class with the supplied arg(s).  Use either the
  1 arg invokeCallbackContext: or the 4 arg invokeCallback:stack:registers:jmpbuf:
  message, depending on what selector is installed in the specialObjectsArray.
  Note that if invoking the legacy invokeCallback:stack:registers:jmpbuf: we pass the
  vmCallbackContext as the jmpbuf argument (see reestablishContextPriorToCallback:).
  The arguments are raw C addresses and are converted to integer objects on the way."
+ <returnTypeC: #sqInt>
  self notYetImplemented!

Item was changed:
  ----- Method: InterpreterProxy>>stringForCString: (in category 'testing') -----
  stringForCString: aCString
  "Answer a ByteString object containing the bytes (possibly UTF-8?) in the null-terminated C string aCString."
+ <returnTypeC: #sqInt>
  <var: #aCString type: #'char *'>
  self notYetImplemented!

Item was changed:
  ----- Method: VMMaker class>>generateVMPlugins (in category 'configurations') -----
  generateVMPlugins
  ^VMMaker
  generatePluginsTo: (FileDirectory default pathFromURI: self sourceTree, '/src')
  options: #()
  platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  including:#( ADPCMCodecPlugin AsynchFilePlugin
  BalloonEnginePlugin B3DAcceleratorPlugin B3DEnginePlugin BMPReadWriterPlugin BitBltSimulation
  BochsIA32Plugin BochsX64Plugin
+ CameraPlugin CroquetPlugin DeflatePlugin DropPlugin
+ "Cryptography Plugins:" DESPlugin DSAPlugin MD5Plugin SHA256Plugin
+ "FT2Plugin" FFTPlugin FileCopyPlugin FilePlugin FileAttributesPlugin FloatArrayPlugin FloatMathPlugin
- CameraPlugin CroquetPlugin DSAPlugin DeflatePlugin DropPlugin
- "FT2Plugin" FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
  GeniePlugin GdbARMPlugin HostWindowPlugin IA32ABIPlugin ImmX11Plugin InternetConfigPlugin
  JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin
  ScratchPlugin SecurityPlugin SerialPlugin SocketPlugin
  SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
  ThreadedFFIPlugin ThreadedARMFFIPlugin ThreadedIA32FFIPlugin ThreadedX64SysVFFIPlugin ThreadedX64Win64FFIPlugin
  UnicodePlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
  Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin WeDoPlugin
  XDisplayControlPlugin)!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>collectAndCheckInterpreterProxyInterfaceFor:verbose: (in category 'utilities') -----
+ collectAndCheckInterpreterProxyInterfaceFor: selectors verbose: beVerbose
+ "self new
+ collectAndCheckInterpreterProxyInterfaceFor: (InterpreterProxy selectors reject: [:s| #(initialize private) includes: (InterpreterProxy whichCategoryIncludesSelector: s)])
+ verbose: true"
+ | interpreterClass objectMemoryClass |
+ interpreterClass := self referenceInterpreterClass.
+ objectMemoryClass := self referenceObjectMemoryClass.
+ ^selectors collect:
+ [:selector| | reference actual |
+ reference := self compileToTMethodSelector: selector
+ in: ((interpreterClass whichClassIncludesSelector: selector) ifNil:
+ [(objectMemoryClass whichClassIncludesSelector: selector) ifNil:
+ [InterpreterProxy]]).
+ actual := self compileToTMethodSelector: selector in: InterpreterProxy.
+ { actual. reference } do:
+ [:tMethod|
+ tMethod recordDeclarationsIn: self.
+ tMethod returnType ifNil:
+ [tMethod inferReturnTypeIn: self.
+ tMethod returnType ifNil:
+ [tMethod returnType: #sqInt]]].
+ (reference returnType ~= actual returnType
+ or: [(1 to: reference args size) anySatisfy:
+ [:i| (reference typeFor: (reference args at: i) in: self)
+  ~= (actual typeFor: (actual args at: i) in: self)]]) ifTrue:
+ [self logger
+ nextPutAll: 'warning, signature of InterpreterProxy>>';
+ nextPutAll: selector;
+ nextPutAll: ' does not match reference implementation.';
+ cr.
+ beVerbose ifTrue:
+ [self logger nextPutAll: 'reference:'; tab.
+ reference emitCFunctionPrototype: self logger generator: self.
+ self logger nextPutAll: 'actual:'; tab; tab.
+ actual emitCFunctionPrototype: self logger generator: self].
+ self logger flush"; halt: selector"].
+ actual]!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>preDeclareInterpreterProxyOn: (in category 'C code generator') -----
  preDeclareInterpreterProxyOn: aStream
  "Put the necessary #defines needed before interpreterProxy.  Basically
  internal plugins use the VM's interpreterProxy variable and external plugins
  use their own.  Override to keep local copies of all functions in external
  prims, and link directly in internal plugins."
  "| pcc |
  pcc := self new.
  (InterpreterProxy selectors reject: [:s| #(initialize private) includes: (InterpreterProxy whichCategoryIncludesSelector: s)]) do:
  [:s| pcc noteUsedPluginFunction: s].
  pcc preDeclareInterpreterProxyOn: Transcript.
  Transcript flush"
+ | pluginFuncs |
- | pluginFuncs interpreterClass objectMemoryClass |
  self notePluginFunctionsUsedByMacros.
  (pluginFuncs := self pluginFunctionsToClone) isEmpty ifTrue:
  [^super preDeclareInterpreterProxyOn: aStream].
  (pluginFuncs includesAnyOf: self selectorsThatAreGeneratedAsMacros) ifTrue:
  [self preDeclareMacrosForFastClassCheckingOn: aStream].
  pluginFuncs := pluginFuncs copyWithoutAll: self selectorsThatAreGeneratedAsMacros.
  pluginFuncs isEmpty ifTrue:
  [^self].
+ pluginFuncs := self collectAndCheckInterpreterProxyInterfaceFor: pluginFuncs verbose: false.
- interpreterClass := self referenceInterpreterClass.
- objectMemoryClass := self referenceObjectMemoryClass.
- pluginFuncs := pluginFuncs collect:
- [:selector| | reference actual |
- reference := self compileToTMethodSelector: selector
- in: ((interpreterClass whichClassIncludesSelector: selector) ifNil:
- [(objectMemoryClass whichClassIncludesSelector: selector) ifNil:
- [InterpreterProxy]]).
- actual := self compileToTMethodSelector: selector in: InterpreterProxy.
- { actual. reference } do:
- [:tMethod|
- tMethod recordDeclarationsIn: self.
- tMethod returnType ifNil:
- [tMethod inferReturnTypeIn: self]].
- (reference returnType ~= actual returnType
- or: [(1 to: reference args size) anySatisfy:
- [:i| (reference typeFor: (reference args at: i) in: self)
-  ~= (actual typeFor: (actual args at: i) in: self)]]) ifTrue:
- [self logger
- nextPutAll: 'warning, signature of InterpreterProxy>>';
- nextPutAll: selector;
- nextPutAll: ' does not match reference implementation.';
- cr].
- actual].
  aStream cr; nextPutAll: '#if !!defined(SQUEAK_BUILTIN_PLUGIN)'; cr.
  pluginFuncs do:
  [:tMethod| | functionName |
  functionName := self cFunctionNameFor: tMethod selector.
  aStream nextPutAll:
  ((String streamContents:
  [:s|
  tMethod
  static: true;
  emitCFunctionPrototype: s generator: self])
  copyReplaceAll: functionName
  with: '(*', functionName, ')'
  tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]])].
  aStream nextPutAll: '#else /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'; cr.
  pluginFuncs do:
  [:tMethod|
  self withGuardAgainstDefinitionOf: tMethod selector on: aStream do:
  [self withOptionalVerbiageFor: tMethod selector
  on: aStream
  do: [tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self]
  ifOptionalDo:
  [aStream nextPutAll: '# define '.
  (TSendNode new
  setSelector: tMethod selector
  receiver: (TVariableNode new setName: 'interpreterProxy')
  arguments: (tMethod args collect: [:a| TVariableNode new setName: a]))
  emitCCodeAsArgumentOn: aStream
  level: 0
  generator: self.
  aStream nextPutAll: ' 0'; cr]]].
  aStream nextPutAll: 'extern'; cr; nextPutAll: '#endif'; cr!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>referenceObjectMemoryClass (in category 'C code generator') -----
  referenceObjectMemoryClass
  "Define the class from which to take methods to define the interpreter proxy imports."
+ ^(Smalltalk classNamed: #Spur32BitMemoryManager) ifNil:
- ^(Smalltalk classNamed: #SpurMemoryManager) ifNil:
  [(Smalltalk classNamed: #NewObjectMemory) ifNil:
  [ObjectMemory]]!