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

commits at source.squeak.org commits at source.squeak.org
Sun Jun 24 23:44:27 UTC 2012


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

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

Name: VMMaker.oscog-eem.169
Author: eem
Time: 24 June 2012, 4:41:55.493 pm
UUID: 932f0574-1b33-407c-8eb7-130fac92ab8d
Ancestors: VMMaker.oscog-eem.168

Add support for in-line literal array constants (currently ByteArray
only).  gen code of form
	 { static type aLiteralArray = { .... };
		var = aLiteralArray;
	 };
for e.g.
	var = self cCoerce: #[...] to: 'unsigned char *'
Add a cutesy development-time MNU for redirecting to cogit
and objectMemory if in a doit only.

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

Item was added:
+ ----- Method: ByteArray>>coerceTo:sim: (in category '*VMMaker-coercing') -----
+ coerceTo: cTypeString sim: interpreterSimulator
+ 	^CLiteralArray on: self!

Item was added:
+ ----- Method: CCodeGenerator>>staticArrayInitializerCalled:for:type: (in category 'utilities') -----
+ staticArrayInitializerCalled: varName for: array type: cType
+ 	"array is a literal array or a CArray on some array."
+ 	| sequence lastLine |
+ 	sequence := array isCollection ifTrue: [array] ifFalse: [array object].
+ 	lastLine := 0.
+ 	^String streamContents:
+ 		[:s|
+ 		s	nextPutAll: 'static ';
+ 			nextPutAll: cType;
+ 			space;
+ 			nextPutAll: varName;
+ 			nextPutAll: '[] = {'; crtab: 2.
+ 		sequence
+ 			do: [:element| s nextPutAll: (self cLiteralFor: element)]
+ 			separatedBy:
+ 				[s nextPut: $,.
+ 				 (s position - lastLine) > 76
+ 					ifTrue: [s crtab: 2. lastLine := s position]
+ 					ifFalse: [s space]].
+ 		s crtab; nextPut: $}; cr]!

Item was added:
+ Object subclass: #CLiteralArray
+ 	instanceVariableNames: 'object'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-InterpreterSimulation'!

Item was added:
+ ----- Method: CLiteralArray class>>on: (in category 'instance creation') -----
+ on: anArrayLiteral
+ 	^self new setObject: anArrayLiteral; yourself!

Item was added:
+ ----- Method: CLiteralArray>>at: (in category 'accessing') -----
+ at: offset
+ 	^object at: offset + 1!

Item was added:
+ ----- Method: CLiteralArray>>at:put: (in category 'accessing') -----
+ at: offset put: val
+ 	^object at: offset + 1 put: val!

Item was added:
+ ----- Method: CLiteralArray>>setObject: (in category 'accessing') -----
+ setObject: anArrayLiteral
+ 	object := anArrayLiteral!

Item was changed:
  ----- Method: CoInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Override to avoid repeating StackInterpreter's declarations and add our own extensions"
  	| threaded |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	threaded := aCCodeGenerator vmClass isThreadedVM.
  	aCCodeGenerator
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile: (threaded ifTrue: ['"cointerpmt.h"'] ifFalse: ['"cointerp.h"']);
  		addHeaderFile:'"cogit.h"'.
  	self declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: (threaded ifTrue: ['Cog MT'] ifFalse: ['Cog']).
  	aCCodeGenerator
  		var: #heapBase
  		declareC: 'static usqInt heapBase';
  		var: #maxLiteralCountForCompile
  		declareC: 'sqInt maxLiteralCountForCompile = MaxLiteralCountForCompile /* ', MaxLiteralCountForCompile printString, ' */';
  		var: #minBackwardJumpCountForCompile
  		declareC: 'sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* ', MinBackwardJumpCountForCompile printString, ' */'.
  	aCCodeGenerator
  		var: #reenterInterpreter
  		declareC: 'jmp_buf reenterInterpreter; /* private export */'.
  	aCCodeGenerator
  		var: #statCodeCompactionUsecs
  		type: #usqLong.
  	aCCodeGenerator
  		var: #primTraceLogIndex type: #'unsigned char';
  		var: #primTraceLog declareC: 'sqInt primTraceLog[256]';
  		var: #traceLog
  		declareC: 'sqInt traceLog[TraceBufferSize /* ', TraceBufferSize printString, ' */]';
  		var: #traceSources
+ 		declareC: (aCCodeGenerator
+ 					staticArrayInitializerCalled: 'traceSources'
+ 					for: TraceSources
+ 					type: 'char *')!
- 		declareC: (String streamContents:
- 					[:s|
- 					s nextPutAll: 'static char *traceSources[] = {'; crtab: 2.
- 					TraceSources object
- 						do: [:string| s nextPut: $"; nextPutAll: string; nextPut: $"]
- 						separatedBy: [ s crtab: 2; nextPut: $,].
- 					s crtab; nextPut: $}; cr])!

Item was added:
+ ----- Method: CogVMSimulator>>doesNotUnderstand: (in category 'error handling') -----
+ doesNotUnderstand: aMessage
+ 	"If this is a doit and the objectMemory understands, pass it on."
+ 	(thisContext findContextSuchThat: [:ctxt| ctxt selector == #evaluate:in:to:notifying:ifFail:logged:]) ifNotNil:
+ 		[((objectMemory class whichClassIncludesSelector: aMessage selector) inheritsFrom: Object) ifTrue: "i.e. VMClass and below"
+ 			[Transcript nextPutAll: 'warning: redirecting to objectMemory'; cr; flush.
+ 			 aMessage lookupClass: nil.
+ 			^aMessage sentTo: objectMemory].
+ 		((cogit class whichClassIncludesSelector: aMessage selector) inheritsFrom: Object) ifTrue: "i.e. VMClass and below"
+ 			[Transcript nextPutAll: 'warning: redirecting to cogit'; cr; flush.
+ 			 aMessage lookupClass: nil.
+ 			^aMessage sentTo: cogit]].
+ 	^super doesNotUnderstand: aMessage!

Item was added:
+ ----- Method: StackInterpreterSimulator>>doesNotUnderstand: (in category 'error handling') -----
+ doesNotUnderstand: aMessage
+ 	"If this is a doit and the objectMemory understands, pass it on."
+ 	(thisContext findContextSuchThat: [:ctxt| ctxt selector == #evaluate:in:to:notifying:ifFail:logged:]) ifNotNil:
+ 		[((objectMemory class whichClassIncludesSelector: aMessage selector) inheritsFrom: Object) ifTrue: "i.e. VMClass and below"
+ 			[Transcript nextPutAll: 'warning: redirecting to objectMemory'; cr; flush.
+ 			 aMessage lookupClass: nil.
+ 			^aMessage sentTo: objectMemory]].
+ 	^super doesNotUnderstand: aMessage!

Item was changed:
  ----- Method: TAssignmentNode>>emitCCodeOn:level:generator: (in category 'C code generation') -----
  emitCCodeOn: aStream level: level generator: aCodeGen
  	expression isSwitch ifTrue:
  		[^expression emitCCodeOn: aStream addToEndOfCases: self level: level generator: aCodeGen].
+ 	expression isLiteralArrayDeclaration ifTrue:
+ 		[^self emitLiteralArrayDeclarationOn: aStream level: level generator: aCodeGen].
  	variable emitCCodeOn: aStream level: level generator: aCodeGen.
  	self isVariableUpdatingAssignment
  		ifTrue:
  			[aStream
  				space;
  				nextPutAll: expression selector;	"+ or -"
  				nextPut: $=;
  				space.
  			expression args first emitCCodeAsArgumentOn: aStream level: level generator: aCodeGen]
  		ifFalse:
  			[aStream space; nextPut: $=; space.
  			 expression emitCCodeAsArgumentOn: aStream level: level generator: aCodeGen]!

Item was added:
+ ----- Method: TAssignmentNode>>emitLiteralArrayDeclarationOn:level:generator: (in category 'C code generation') -----
+ emitLiteralArrayDeclarationOn: aStream level: level generator: aCCodeGen
+ 	| type |
+ 	type := expression args last value.
+ 	self assert: type last = $*.
+ 	aStream
+ 		crtab: level;
+ 		nextPutAll: '{ ';
+ 		nextPutAll: (aCCodeGen staticArrayInitializerCalled: 'aLiteralArray' for: expression args first value type: type allButLast);
+ 		nextPut: $;;
+ 		crtab: level + 1;
+ 		nextPutAll: variable name;
+ 		nextPutAll: ' = aLiteralArray;';
+ 		crtab: level;
+ 		nextPut: $};
+ 		cr!

Item was added:
+ ----- Method: TParseNode>>isLiteralArrayDeclaration (in category 'testing') -----
+ isLiteralArrayDeclaration
+ 	^false!

Item was added:
+ ----- Method: TSendNode>>isLiteralArrayDeclaration (in category 'testing') -----
+ isLiteralArrayDeclaration
+ 	^selector == #cCoerce:to:
+ 	  and: [arguments first isConstant
+ 	  and: [arguments first value isLiteral
+ 	  and: [arguments first value isCollection]]]!



More information about the Vm-dev mailing list