[commit] r2236 - OSCogVM source as per VMMaker-oscog.23. Take alloca from stddef.h; malloc.h is

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

[commit] r2236 - OSCogVM source as per VMMaker-oscog.23. Take alloca from stddef.h; malloc.h is

commits-3
 
Author: eliot
Date: 2010-07-16 08:22:23 -0700 (Fri, 16 Jul 2010)
New Revision: 2236

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
Log:
OSCogVM source as per VMMaker-oscog.23.  Take alloca from stddef.h; malloc.h is
an anachronism.  Safer long-running primitive method code.  FreeBSD-friendly
mutex initialization in the unix heartbeat (I hope).


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-16 14:57:02 UTC (rev 2235)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-16 15:22:23 UTC (rev 2236)
@@ -120674,4 +120674,304 @@
  excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin
  FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin)!
 
-----QUIT----{13 July 2010 . 5:53:45 pm} VMMaker-Squeak4.1.image priorSource: 4893204!
\ No newline at end of file
+----QUIT----{13 July 2010 . 5:53:45 pm} VMMaker-Squeak4.1.image priorSource: 4893204!
+
+----STARTUP----{15 July 2010 . 4:36:32 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!StackInterpreter class methodsFor: 'translation' stamp: 'eem 7/15/2010 16:29' prior: 37654127!
+declareCVarsIn: aCCodeGenerator
+ aCCodeGenerator
+ addHeaderFile:'#if defined(WIN32)\# include <malloc.h> /* for alloca under MSVC */\#endif' withCRs;
+ addHeaderFile:'<setjmp.h>';
+ addHeaderFile:'"sqMemoryFence.h"';
+ addHeaderFile:'"dispdbg.h"'.
+ aCCodeGenerator
+ var: #interpreterVersion
+ declareC: 'const char *interpreterVersion = "Croquet Closure Stack VM [',
+ (aCCodeGenerator shortMonticelloDescriptionForClass: self),']"'.
+ 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)
+ as: #'char *'
+ in: aCCodeGenerator.
+ self declareC: #(stackPage overflowedPage)
+ as: #'StackPage *'
+ in: aCCodeGenerator.
+ aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
+ aCCodeGenerator
+ var: #methodCache
+ declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 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) = ', self primitiveTableString.
+ self primitiveTable do:
+ [:symbolOrNot|
+ (symbolOrNot isSymbol
+ and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
+ [(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
+ [:tMethod| tMethod returnType: #void]]].
+ 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'.
+ aCCodeGenerator
+ var: #breakSelector type: #'char *';
+ var: #breakSelectorLength
+ declareC: 'sqInt breakSelectorLength = -1'.
+
+ self declareC: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
+ longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs)
+ as: #usqLong
+ in: aCCodeGenerator.
+ aCCodeGenerator var: #nextProfileTick type: #sqLong! !
+!VMClass methodsFor: 'simulation support' stamp: 'eem 7/7/2010 12:04'!
+sqLowLevelMFence
+ <doNotGenerate>
+ "A no-op in the simulator"! !
+!StackInterpreter methodsFor: 'primitive support' stamp: 'eem 7/8/2010 10:58' prior: 37429536!
+checkForLongRunningPrimitive
+ "Called from forceInterruptCheckFromHeartbeat.  If the system has been running
+ the same primitive on two successive heartbeats then signal profileMethod."
+ <inline: true>
+ longRunningPrimitiveCheckSemaphore isNil ifTrue:
+ [^nil].
+ (longRunningPrimitiveStartUsecs > 0
+ and: [longRunningPrimitiveCheckMethod = newMethod
+ and: [longRunningPrimitiveCheckSequenceNumber = statCheckForEvents]]) ifTrue:
+ [longRunningPrimitiveStopUsecs := self ioUTCMicroseconds.
+ self assert: longRunningPrimitiveStopUsecs > longRunningPrimitiveStartUsecs.
+ ^nil].
+ "See traceProfileState & mapProfileState."
+ longRunningPrimitiveStopUsecs = 0 ifTrue:
+ [longRunningPrimitiveCheckSequenceNumber := statCheckForEvents.
+ longRunningPrimitiveCheckMethod := newMethod.
+ longRunningPrimitiveStartUsecs := self ioUTCMicroseconds.
+ self sqLowLevelMFence]! !
+!StackInterpreter methodsFor: 'object memory support' stamp: 'eem 7/8/2010 10:54' prior: 37415469!
+mapProfileState
+ profileProcess := self remap: profileProcess.
+ profileMethod := self remap: profileMethod.
+ profileSemaphore := self remap: profileSemaphore.
+ "The longRunningPrimitiveCheckMethod (LRPCM) is sampled in an interrupt.  Be very careful with it.
+  If longRunningPrimitiveCheckSequenceNumber (LRPCSN) = statCheckForEvents then LRPCM has
+  been recenty sampled and could be mapped or not, but it must be newMethod and we can simply
+  copy newMethod.  If LRPCSN ~= statCheckForEvents then LRPCM must be some extant object and
+  needs to be remapped."
+ self sqLowLevelMFence.
+ longRunningPrimitiveCheckMethod ~= nil ifTrue:
+ [longRunningPrimitiveCheckMethod :=
+ longRunningPrimitiveCheckSequenceNumber = statCheckForEvents
+ ifTrue: [newMethod]
+ ifFalse: [self remap: longRunningPrimitiveCheckMethod].
+ self sqLowLevelMFence].
+ longRunningPrimitiveCheckSemaphore ~= nil ifTrue:
+ [longRunningPrimitiveCheckSemaphore := self remap: longRunningPrimitiveCheckSemaphore]! !
+!StackInterpreter methodsFor: 'process primitives' stamp: 'eem 7/7/2010 12:00' prior: 37627131!
+primitiveLongRunningPrimitive
+ "Primitive. Answer an Array with the current long-running primitive method identified by
+ the heartbeat, the minimum number of milliseconds it was active for, and the milliseconds
+ of GC activity there-in, or nil if none.  Since the longRunningPrimitiveCheckMethod is
+ sampled at interrupt time be careful to validate it before returning it."
+ <export: true>
+ | lrpcm result primms gcms |
+ self methodArgumentCount = 0 ifFalse:
+ [^self primitiveFail].
+ self sqLowLevelMFence.
+ (longRunningPrimitiveStopUsecs > longRunningPrimitiveStartUsecs "a hit"
+ and: [(lrpcm := longRunningPrimitiveCheckMethod) ~= nil "there is a method"
+ and: [(self addressCouldBeObj: lrpcm) "method looks valid"
+ and: [(self isFreeObject: lrpcm) not
+ and: [(self isCompiledMethod: lrpcm)]]]])
+ ifTrue: [result := self instantiateClass: (self splObj: ClassArray) indexableSize: 3.
+ primms := (longRunningPrimitiveStopUsecs - longRunningPrimitiveStartUsecs) + 500 // 1000.
+
+ gcms := longRunningPrimitiveGCUsecs + 500 // 1000.
+ self storePointer: 0 ofObject: result withValue: lrpcm.
+ self storePointerUnchecked: 1 ofObject: result withValue: (self integerObjectOf: primms).
+ self storePointerUnchecked: 2 ofObject: result withValue: (self integerObjectOf: gcms)]
+ ifFalse: [result := nilObj].
+ self pop: 1 thenPush: result.
+ self voidLongRunningPrimitive: 'get'! !
+!StackInterpreter methodsFor: 'object memory support' stamp: 'eem 7/8/2010 10:57' prior: 37427924!
+traceProfileState
+ self markAndTrace: profileProcess.
+ self markAndTrace: profileMethod.
+ self markAndTrace: profileSemaphore.
+
+ "The longRunningPrimitiveCheckMethod (LRPCM) is sampled in an interrupt.  Be very careful with it.
+  If longRunningPrimitiveCheckSequenceNumber (LRPCSN) = statCheckForEvents then LRPCM has
+  been recenty sampled, but it must be newMethod and we don't need to trace it twice.  If LRPCSN
+  ~= statCheckForEvents then LRPCM must be some extant object and needs to be traced."
+ self sqLowLevelMFence.
+ (longRunningPrimitiveCheckMethod ~= nil
+ and: [longRunningPrimitiveCheckSequenceNumber ~= statCheckForEvents]) ifTrue:
+ [self markAndTrace: longRunningPrimitiveCheckMethod].
+ longRunningPrimitiveCheckSemaphore ~= nil ifTrue:
+ [self markAndTrace: longRunningPrimitiveCheckSemaphore]! !
+!StackInterpreter methodsFor: 'primitive support' stamp: 'eem 7/7/2010 12:19' prior: 37448462!
+voidLongRunningPrimitive: reason
+ "Void the state associated with the long-running primitive check.
+ This is done when a new semaphore is installed or when it appears
+ that is longRunningPrimitiveCheckMethod is invalid, e.g. because it
+ has eben sampled in the middle of a GC."
+ <var: #reason type: #'char *'>
+ <inline: false>
+ longRunningPrimitiveCheckMethod := nil.
+ longRunningPrimitiveCheckSequenceNumber = 0. "not strictly necessary but prevents this being inlined into checkForLongRunningPrimitive"
+ longRunningPrimitiveStartUsecs :=
+ longRunningPrimitiveStopUsecs := 0.
+ longRunningPrimitiveSignalUndelivered := true.
+ self sqLowLevelMFence! !
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+"VMMaker"!
+!StackInterpreter class methodsFor: 'translation' stamp: 'eem 7/15/2010 18:41' prior: 38469466!
+declareCVarsIn: aCCodeGenerator
+ aCCodeGenerator
+ addHeaderFile:'<stddef.h> /* for e.g. alloca */';
+ addHeaderFile:'<setjmp.h>';
+ addHeaderFile:'"sqMemoryFence.h"';
+ addHeaderFile:'"dispdbg.h"'.
+ aCCodeGenerator
+ var: #interpreterVersion
+ declareC: 'const char *interpreterVersion = "Croquet Closure Stack VM [',
+ (aCCodeGenerator shortMonticelloDescriptionForClass: self),']"'.
+ 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)
+ as: #'char *'
+ in: aCCodeGenerator.
+ self declareC: #(stackPage overflowedPage)
+ as: #'StackPage *'
+ in: aCCodeGenerator.
+ aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
+ aCCodeGenerator
+ var: #methodCache
+ declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 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) = ', self primitiveTableString.
+ self primitiveTable do:
+ [:symbolOrNot|
+ (symbolOrNot isSymbol
+ and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
+ [(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
+ [:tMethod| tMethod returnType: #void]]].
+ 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'.
+ aCCodeGenerator
+ var: #breakSelector type: #'char *';
+ var: #breakSelectorLength
+ declareC: 'sqInt breakSelectorLength = -1'.
+
+ self declareC: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
+ longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs)
+ as: #usqLong
+ in: aCCodeGenerator.
+ aCCodeGenerator var: #nextProfileTick type: #sqLong! !
+
+VMMaker
+ generate: CoInterpreter
+ to: (FileDirectory default / '../src') fullName
+ platformDir: (FileDirectory default / '../platforms') fullName
+ excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin
+ FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin)!
+
+----QUIT----{15 July 2010 . 6:44:15 pm} VMMaker-Squeak4.1.image priorSource: 4914731!
+
+----STARTUP----{15 July 2010 . 7:43:34 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+"VMMaker"!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+VMMaker
+ generate: CoInterpreter
+ to: (FileDirectory default / '../src') fullName
+ platformDir: (FileDirectory default / '../platforms') fullName
+ excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin
+ FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin)!
+
+VMMaker
+ generate: StackInterpreter
+ to: (FileDirectory default / '../stacksrc') fullName
+ platformDir: (FileDirectory default / '../platforms') fullName
+ excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
+
+----QUIT----{15 July 2010 . 8:09:58 pm} VMMaker-Squeak4.1.image priorSource: 4927113!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)

Reply | Threaded
Open this post in threaded view
|

Re: [commit] r2236 - OSCogVM source as per VMMaker-oscog.23. Take alloca from stddef.h; malloc.h is

Frank Shearar
 
On 2010/07/16 17:22, [hidden email] wrote:

>
> Author: eliot
> Date: 2010-07-16 08:22:23 -0700 (Fri, 16 Jul 2010)
> New Revision: 2236
>
> Modified:
>     branches/Cog/image/VMMaker-Squeak4.1.changes
>     branches/Cog/image/VMMaker-Squeak4.1.image
> Log:
> OSCogVM source as per VMMaker-oscog.23.  Take alloca from stddef.h; malloc.h is
> an anachronism.  Safer long-running primitive method code.  FreeBSD-friendly
> mutex initialization in the unix heartbeat (I hope).

Thanks Eliot! I was trying to figure out how to do the legwork for you.

OK, with the new changes we find the next error. As usual, configure
works just fine, and the error's when compiling:

gcc -g -O2 -msse2 -D_GNU_SOURCE -DNDEBUG -DITIMER_HEARTBEAT=1
-DNO_VM_PROFILE=1 -DCOGMTVM=0 -msse -DLSB_FIRST=1  -DHAVE_CONFIG_H
-DSQUEAK_BUILTIN_PLUGIN  -I/usr/home/frank/temp/unixbuild/bld
-I/usr/home/frank/temp/unixbuild/bld
-I/usr/home/frank/temp/platforms/unix/vm
-I/usr/home/frank/temp/platforms/Cross/vm -I/usr/home/frank/temp/src/vm
-I/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin   -c -o
sqFilePluginBasicPrims.o
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:
In function 'sqFileAtEnd':
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:136:
warning: dereferencing 'void *' pointer
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:136:
error: request for member '_flags' in something not a structure or union
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:
In function 'sqFileTruncate':
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:407:
warning: dereferencing 'void *' pointer
/usr/home/frank/temp/platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c:407:
error: request for member '_file' in something not a structure or union
*** Error code 1