Update of /cvsroot/squeak/squeak/platforms/Mac OS/vm/specialChangeSets
In directory sc8-pr-cvs1:/tmp/cvs-serv5658/squeak/platforms/Mac OS/vm/specialChangeSets
Added Files:
VMGlobalsChanges.5.cs
Log Message:
3.5.0b5 Faster GC logic
--- NEW FILE: VMGlobalsChanges.5.cs ---
'From Squeak3.5alpha of ''7 January 2003'' [latest update: #5169] on 9 April 2003 at 4:33:07 pm'!
"Change Set: VMGlobalsChanges
Date: 5 April 2003
Author: ti...@su..., jo...@sm...
Seconds pass at combining all the changes needed to add the VM global structure support into a single filein.
This incorporates:-
MoreInterpAccessors-JMM
GlobalStructure-JMM
GlobalsRiscOS-tpr
GCMakeItFaster-JMM
GCCMakeItFasterGStruct-JMM
VMGlobalsCleanups-tpr
VMGLobalsReStructure-JMM
"!
Object subclass: #CCodeGenerator
instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations methods variablesSetCache headerFiles pluginName extraDefs postProcesses isCPP globalVariableUsage '
classVariableNames: 'UseRightShiftForDivide '
[...1618 lines suppressed...]
!TVariableNode methodsFor: 'as yet unclassified' stamp: 'JMM 4/5/2002 14:14'!
emitCCodeOn: aStream level: level generator: aCodeGen
name = 'nil'
ifTrue: [ aStream nextPutAll: (aCodeGen cLiteralFor: nil) ]
ifFalse: [ aStream nextPutAll: (aCodeGen returnPrefixFromVariable: name) ].! !
TMethod removeSelector: #referencesGlobalStruct:!
Interpreter removeSelector: #returnValue:to:!
Object subclass: #ObjectMemory
instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold statFullGCs statFullGCMSecs statIncrGCs statIncrGCMSecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes '
classVariableNames: 'AllButHashBits AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit AllButTypeMask BaseHeaderSize BlockContextProto CharacterTable ClassArray ClassBitmap ClassBlockContext ClassByteArray ClassCharacter ClassCompiledMethod ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassInteger ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassPoint ClassProcess ClassPseudoContext ClassSemaphore ClassString ClassTranslatedMethod CompactClassMask CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero CtxtTempFrameStart DoAssertionChecks DoBalanceChecks Done ExternalObjectsArray FalseObject FloatProto GCTopMarker HashBits HashBitsOffset HeaderTypeClass HeaderTypeFree HeaderTypeGC HeaderTypeShort HeaderTypeSizeAndClass LargeContextBit LargeContextSize MarkBit MethodContextProto NilContext NilObject RemapBufferSize RootBit RootTableSize SchedulerAssociation SelectorAboutToReturn SelectorCannotInterpret SelectorCannotReturn SelectorDoesNotUnderstand SelectorMustBeBoolean SizeMask SmallContextSize SpecialSelectors StackStart StartField StartObj TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject TypeMask Upward '
poolDictionaries: ''
category: 'VMConstruction-Interpreter'!
CCodeGeneratorGlobalStructure removeSelector: #globalVariables!
CCodeGenerator removeSelector: #generateCodeStringForPrimitives!
CCodeGenerator removeSelector: #pluginName!
CCodeGenerator removeSelector: #pluginName:!
|