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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 14 20:42:29 UTC 2012


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

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

Name: VMMaker.oscog-eem.235
Author: eem
Time: 14 December 2012, 12:40:24.977 pm
UUID: 954df856-3f83-498c-9735-6cd3777ba9c7
Ancestors: VMMaker.oscog-eem.234

Fix doubling of include file declarations in plugins (now plugin
code is generated an exctra time to extract usedf functions we
must avoid adding headers twice in emitCHeaderOn:).

Provide a hook, InterpreterPlugin class>>exportBuildInfoOrNil, for
build info comments as in the UnixOSProcessPlugin.

Make constant generation look for method var and return types so
as not to nuke types introduced as #defines via
addConstantForBinding: (again a la UnixOSProcessPlugin).

EMit constants more carefully, not converting defs that contain a
comment into C literals, again so that UnixOSProcessPlugin can
declare FILEHANDLETYPE et al.

Add all headers through addHeaderFile[First]: so that warnings can
be issued aboud multiple defs etc.

Fix MNU handler for missing NullStream protocol as per trunk4.3.

Nuke a duplicate include in VMProfileMacSupportPlugin.

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

Item was changed:
  ----- Method: CCodeGenerator>>addHeaderFile: (in category 'public') -----
  addHeaderFile: aString
+ 	"Add a header file. As a hack we allow C preprocessor defs such as #ifdef"
+ 	self assert: (('"<#' includes: aString first) or: [(aString last: 2) = '_H']).
+ 	(aString first ~= $#
+ 	 and: [headerFiles includes: aString]) ifTrue:
+ 		[logger nextPutAll: 'warning, attempt to include ', aString, ' a second time'; cr; flush.
+ 		 ^self].
+ 	headerFiles addLast: aString!
- 	"Add a header file. The argument must be a quoted string!!"
- 	headerFiles addLast: aString.!

Item was added:
+ ----- Method: CCodeGenerator>>addHeaderFileFirst: (in category 'public') -----
+ addHeaderFileFirst: aString
+ 	"Add a header file to the front of the sequence."
+ 	self assert: (('"<' includes: aString first) and: ['">' includes: aString last]).
+ 	self assert: (headerFiles includes: aString) not.
+ 	headerFiles addFirst: aString!

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused constList |
  	unused := constants keys asSet.
  	"Don't generate any defines for the externally defined constants,
+ 	 STACKVM, COGVM, COGMTVM et al, unless they're actually used."
- 	 STACKVM, COGVM, COGMTVM et al, unless they're actuaslly used."
  	(VMClass class>>#initializeMiscConstantsWith:) literalsDo:
  		[:lit|
  		(lit isVariableBinding and: [lit key isString]) ifTrue:
  			[unused add: lit key]].
  	methods do:
  		[:meth|
+ 		meth declarations keysDo:
+ 			[:v|
+ 			(meth typeFor: v in: self) ifNotNil:
+ 				[:type| unused remove: type ifAbsent: []]].
+ 		unused remove: meth returnType ifAbsent: [].
  		meth parseTree nodesDo:
  			[:n| n isConstant ifTrue: [unused remove: n name ifAbsent: []]]].
  	unused copy do:
  		[:const|
  		(variableDeclarations anySatisfy: [:value| value includesSubString: const]) ifTrue:
  			[unused remove: const ifAbsent: []]].
  	unused remove: #BytesPerWord ifAbsent: []. "force inclusion of BytesPerWord declaration"
  	constList := constants keys reject: [:any| unused includes: any].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[:varName| | node default value |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
+ 			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
+ 			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
+ 			default := (node value isString and: [node value includesSubString: '/*'])
+ 							ifTrue: [node value]
+ 							ifFalse: [self cLiteralFor: node value name: varName].
- 			["Allow the class to provide an alternative definition, either of just the value or the whole shebang"
- 			default := self cLiteralFor: node value name: varName.
  			value := vmClass
  						ifNotNil:
  							[(vmClass specialValueForConstant: node name default: default)
  								ifNotNil: [:specialDef| specialDef]
  								ifNil: [default]]
  						ifNil: [default].
  			value first ~= $# ifTrue:
  				[aStream nextPutAll: '#define '; nextPutAll: node name; space].
  			aStream nextPutAll: value; cr]].
  	aStream cr!

Item was changed:
  ----- Method: CCodeGenerator>>emitCHeaderOn: (in category 'C code generator') -----
  emitCHeaderOn: aStream
  	"Emit the initial part of a source file on aStream, comprising the version stamp,
  	 the global struct usage flags, the header files and preamble code."
  
  	| headerClass |
  	headerClass := [vmClass coreInterpreterClass]
  						on: MessageNotUnderstood
  						do: [:ex| vmClass].
  	aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: headerClass); cr; cr.
  	self emitGlobalStructFlagOn: aStream.
  
+ 	self addHeaderFileFirst: '"sq.h"'.
- 	headerFiles addFirst: '"sq.h"'.
  	vmClass isInterpreterClass ifTrue:
+ 		[self addHeaderFile: '"sqMemoryAccess.h"'].
- 		[headerFiles addLast: '"sqMemoryAccess.h"'].
  	"Additional header files; include C library ones first."
  	self emitHeaderFiles: (headerFiles select: [:hdr| hdr includes: $<]) on: aStream.
  	"Additional header files; include squeak VM ones last"
  	self emitHeaderFiles: (headerFiles reject: [:hdr| hdr includes: $<]) on: aStream.
  
  	vmClass isInterpreterClass ifTrue:
  		[aStream cr; cr; nextPutAll: vmClass preambleCCode].
  
  	aStream cr!

Item was changed:
  ----- Method: CCodeGenerator>>fileHeaderVersionStampForSourceClass: (in category 'C code generator') -----
  fileHeaderVersionStampForSourceClass: sourceClass
  	"Answer a suitable versiomn stamp to include in the header."
  	| exportBuildInfo slangDescription sourceDescription |
  	[exportBuildInfo := sourceClass isInterpreterClass
  						ifTrue: ['char *__interpBuildInfo = __buildInfo;']
  						ifFalse:
  							[sourceClass isCogitClass
+ 								ifTrue: ['char *__cogitBuildInfo = __buildInfo;']
+ 								ifFalse:
+ 									[sourceClass isPluginClass ifTrue:
+ 										[sourceClass exportBuildInfoOrNil]]]]
- 								ifTrue: ['char *__cogitBuildInfo = __buildInfo;']]]
  		on: MessageNotUnderstood
  		do: [:ex| ex resume: false].
  	[slangDescription := self monticelloDescriptionFor: self class.
  	 sourceClass ifNotNil:
  		[sourceDescription := self monticelloDescriptionFor: sourceClass]]
  		on: Error
  		do: [:ex| | now |
  			now := Time dateAndTimeNow printString.
  			^String streamContents:
  				[:s|
  				s nextPutAll: '/* Automatically generated from Squeak on '.
  				s nextPutAll: now.
  				s nextPutAll: ' */'; cr; cr.
  				s nextPutAll: 'static char __buildInfo[] = "Generated on '.
  				s nextPutAll: now.
  				s nextPutAll: '. Compiled on "'.
  				s nextPutAll: '__DATE__ ;'; cr.
  				exportBuildInfo ifNotNil:
  					[s nextPutAll: exportBuildInfo; cr].
  				s cr]].
  	^String streamContents:
  		[:s|
  		s nextPutAll: '/* Automatically generated by'.
  		s crtab.
  		s nextPutAll: slangDescription.
  		sourceDescription ifNotNil:
  			[s cr; nextPutAll: '   from'; crtab; nextPutAll: sourceDescription].
  		s cr; nextPutAll: ' */'; cr.
  		sourceDescription ifNotNil:
  			[s nextPutAll: 'static char __buildInfo[] = "'.
  			 s nextPutAll: sourceDescription.
  			 s nextPutAll: ' " __DATE__ ;'; cr.
  			exportBuildInfo ifNotNil:
  				[s nextPutAll: exportBuildInfo; cr].
  			s cr]]!

Item was added:
+ ----- Method: InterpreterPlugin class>>exportBuildInfoOrNil (in category 'translation') -----
+ exportBuildInfoOrNil
+ 	"A hook for classes to emit some descriptive build string.
+ 	 See CCodeGenerator>>fileHeaderVersionStampForSourceClass:"
+ 	^nil!

Item was added:
+ ----- Method: InterpreterPlugin class>>isPluginClass (in category 'translation') -----
+ isPluginClass
+ 	^true!

Item was added:
+ ----- Method: VMClass class>>isPluginClass (in category 'translation') -----
+ isPluginClass
+ 	"InterpreterPlugin class override this."
+ 	^false!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>emitCCodeOn:doInlining:doAssertions: (in category 'C code generator') -----
  emitCCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag
  	"Generate twice; the first time to collect the used functions, the second to output the used functions."
+ 	| savedHeaders |
+ 	savedHeaders := headerFiles copy.
  	[super emitCCodeOn: NullStream new doInlining: inlineFlag doAssertions: assertionFlag]
  		on: MessageNotUnderstood
  		do: [:ex|
+ 				(#(cr crtab: peekLast space tab tab:) includes: ex message selector) ifTrue:
- 				(#(peekLast tab: crtab:) includes: ex message selector) ifTrue:
  					[ex resume: nil].
  				ex pass].
+ 	headerFiles := savedHeaders.
  	super emitCCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>emitCHeaderOn: (in category 'C code generator') -----
  emitCHeaderOn: aStream
  	"Write a C file header onto the given stream."
  
  	aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: pluginClass).
  	aStream cr; cr.
  
  	#('<math.h>' '<stdio.h>' '<stdlib.h>' '<string.h>' '<time.h>') reverseDo:
+ 		[:hdr| self addHeaderFileFirst: hdr].
- 		[:hdr| headerFiles addFirst: hdr].
  
  	"Additional header files; include C library ones first."
  	self emitHeaderFiles: (headerFiles select: [:hdr| hdr includes: $<]) on: aStream.
  
  	aStream cr; nextPutAll:'/* Default EXPORT macro that does nothing (see comment in sq.h): */
  #define EXPORT(returnType) returnType
  
  /* Do not include the entire sq.h file but just those parts needed. */
  /*  The virtual machine proxy definition */
  #include "sqVirtualMachine.h"
  /* Configuration options */
  #include "sqConfig.h"
  /* Platform specific definitions */
  #include "sqPlatformSpecific.h"
  
  #define true 1
  #define false 0
  #define null 0  /* using ''null'' because nil is predefined in Think C */
  #ifdef SQUEAK_BUILTIN_PLUGIN
  #undef EXPORT
  // was #undef EXPORT(returnType) but screws NorCroft cc
  #define EXPORT(returnType) static returnType
  #endif'; cr; cr.
+ 	self addHeaderFile: '"sqMemoryAccess.h"'.
- 	headerFiles addLast: '"sqMemoryAccess.h"'.
  	"Additional header files; include squeak VM ones last"
  	self emitHeaderFiles: (headerFiles reject: [:hdr| hdr includes: $<]) on: aStream.
  	pluginClass preambleCCode ifNotNil:
  		[:preamble|
  		aStream cr; nextPutAll: preamble].
  	aStream cr.!

Item was changed:
  ----- Method: VMProfileMacSupportPlugin class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGen
  	aCCodeGen
- 		addHeaderFile: '<stdlib.h>';
  		addHeaderFile: '<dlfcn.h>';
  		addHeaderFile: '<mach-o/dyld.h>';
  		addHeaderFile: '<mach-o/getsect.h>'!



More information about the Vm-dev mailing list