'From Pharo3.0 of 18 March 2013 [Latest update: #30274] on 16 July 2013 at 5:05:36 pm'! !TBehavior methodsFor: '*Fuel' stamp: 'SebastianTleye 7/16/2013 17:02'! fuelIgnoredInstanceVariableNames "Indicates which variables have to be ignored during serialization." ^#()! ! !Behavior methodsFor: '*Compiler-Kernel' stamp: 'SebastianTleye 7/16/2013 17:05'! recompile: selector from: oldClass "Compile the method associated with selector in the receiver's method dictionary." | method newMethod | method := oldClass compiledMethodAt: selector. newMethod := self compiler source: (oldClass sourceCodeAt: selector); class: self; failBlock: [^ self]; compiledMethodTrailer: method trailer; compile. "Assume OK after proceed from SyntaxError" selector == newMethod selector ifFalse: [self error: 'selector changed!!']. self basicAddSelector: selector withMethod: newMethod.! ! !Behavior methodsFor: 'accessing' stamp: 'SebastianTleye 7/16/2013 17:04'! subclassDefinerClass "Answer an evaluator class appropriate for evaluating definitions of new subclasses of this class." ^self compilerClass! ! !Behavior methodsFor: '*Compiler-Kernel' stamp: 'SebastianTleye 7/16/2013 17:05'! recompile: selector from: oldClass "Compile the method associated with selector in the receiver's method dictionary." | method newMethod | method := oldClass compiledMethodAt: selector. newMethod := self compiler source: (oldClass sourceCodeAt: selector); class: self; failBlock: [^ self]; compiledMethodTrailer: method trailer; compile. "Assume OK after proceed from SyntaxError" selector == newMethod selector ifFalse: [self error: 'selector changed!!']. self basicAddSelector: selector withMethod: newMethod.! ! !Behavior methodsFor: 'testing' stamp: 'SebastianTleye 7/16/2013 17:04'! instSize "Answer the number of named instance variables (as opposed to indexed variables) of the receiver." self flag: #instSizeChange. "Smalltalk browseAllCallsOn: #instSizeChange" " NOTE: This code supports the backward-compatible extension to 8 bits of instSize. When we revise the image format, it should become... ^ ((format bitShift: -1) bitAnd: 16rFF) - 1 Note also that every other method in this category will require 2 bits more of right shift after the change. " ^ ((self format bitShift: -10) bitAnd: 16rC0) + ((self format bitShift: -1) bitAnd: 16r3F) - 1! ! !Behavior methodsFor: 'accessing' stamp: 'SebastianTleye 7/16/2013 17:04'! subclassDefinerClass "Answer an evaluator class appropriate for evaluating definitions of new subclasses of this class." ^self compilerClass! ! Behavior removeSelector: #fuelIgnoredInstanceVariableNames! !TBehavior methodsFor: '*Compiler-Kernel' stamp: 'SebastianTleye 7/16/2013 17:05'! recompile: selector from: oldClass ^self explicitRequirement.! ! !TBehavior methodsFor: 'testing' stamp: 'SebastianTleye 7/16/2013 17:04'! instSize ^self explicitRequirement.! ! !TBehavior methodsFor: 'accessing' stamp: 'SebastianTleye 7/16/2013 17:04'! subclassDefinerClass ^self explicitRequirement.! ! !TraitBehavior reorganize! (#'*ast-core' parseTreeFor:) (#printing printHierarchy literalScannedAs:notifying: storeLiteral:on: printOn: longPrintOn:) (#'accessing class hierarchy' allSuperclasses superclass: withAllSubclasses withAllSuperclasses superclass allSuperclassesIncluding: withAllSubclassesDo: allSubclassesWithLevelDo:startingLevel: allSubclasses) (#'accessing method dictionary' allSelectors allMethods compiledMethodAt:ifAbsent: deregisterLocalSelector: selectors methodDict: allSelectorsAboveUntil: allSelectorsBelow: methodDictionary compress sourceCodeAt: basicLocalSelectors removeSelector: registerLocalSelector: lookupSelector: methodDict nextQuotePosIn:startingFrom: allSelectorsAbove methodDictionary: selectorsWithArgs: basicLocalSelectors: supermostPrecodeCommentFor: changeRecordsAt: >> zapAllMethods allSelectorsWithout: methods firstCommentAt: selectorsAndMethodsDo: sourceCodeAt:ifAbsent: compiledMethodAt: classAndMethodFor:do:ifAbsent: firstPrecodeCommentFor: commentsAt: precodeCommentOrInheritedCommentFor: commentsIn: methodsDo: selectorsDo: ultimateSourceCodeAt:ifAbsent: addSelectorSilently:withMethod:) (#'accessing instances and variables' allInstVarNames includesSharedPoolNamed: allClassVarNames classVarNames instVarNames instanceCount allSharedPools allowsSubInstVars allSubInstances allInstances sharedPools subclassInstVarNames someInstance) (#testing isObsolete instSize isBytes isTrait isAnonymous isBits hasAbstractMethods isWeak isCompact canZapMethodDictionary isPointers shouldNotBeRedefined isMeta isWords isVariable sourceMatchesBytecodeAt: isFixed instSpec) (#'user interface' withAllSubAndSuperclassesDo: unreferencedInstanceVariables) (#'class compatibility' subclassDefinerClass) (#'obsolete subclasses' basicObsoleteSubclasses allLocalCallsOn: addObsoleteSubclass: removeAllObsoleteSubclasses removeObsoleteSubclass: obsoleteSubclasses) (#'*NativeBoost-Core' nbBindingOf: externalTypeAlias: nbFnArgument:generator:) (#'instance creation' new: basicNew: basicNew new) (#compiling instVarNamesAndOffsetsDo: variablesAndOffsetsDo:) (#'initialize-release' initialize nonObsoleteClass superclass:methodDictionary:format:) (#'*Nautilus' realClass) (#enumerating allSuperclassesDo: subclassesDo: selectSubclasses: withAllSuperclassesDo: allSubclassesDo: withAllSuperAndSubclassesDo: allSubInstancesDo: allInstancesDo: selectSuperclasses: allUnreferencedInstanceVariables) (#'memory usage' instancesSizeInMemory) (#queries whichClassDefinesClassVar: copiesMethodsFromSuperclass whichClassDefinesInstVar: whichSuperclassSatisfies: copiesFromSuperclass: whichSelectorsRead: copiedFromSuperclass: whichSelectorsAssign: copiedMethodsFromSuperclass) (#cleanup cleanUp cleanUp:) (#'*Ring-Core-Kernel' protocols methodNamed: methodsInProtocol:) (#'system startup' shutDown: shutDown startUp startUp:) (#'*Tools-Browser' browse) (#private spaceUsed becomeCompactSimplyAt: checkCanBeUncompact becomeCompact flushCache becomeUncompact indexIfCompact setFormat:) (#'adding/removing methods' pureAddSelectorSilently:withMethod: basicRemoveSelector: addSelector:withMethod:notifying: methodDictAddSelectorSilently:withMethod: basicAddSelector:withMethod: addSelector:withMethod: pureRemoveSelector: removeSelectorSilently: adoptInstance:) (#traits addTraitSelector:withMethod: traitComposition: flattenDownAllTraits traits users flattenDown: classesComposedWithMe traitsProvidingSelector: users: traitOrClassOfSelector: removeUser: notifyUsersOfChangedSelector: traitCompositionIncludes: updateMethodDictionarySelector: purgeLocalSelectors traitComposition noteChangedSelectors: hasTraitComposition removeFromComposition: traitTransformations setTraitCompositionFrom: traitCompositionString setTraitComposition: notifyUsersOfChangedSelectors: removeTraitSelector: applyChangesOfNewTraitCompositionReplacing: ensureLocalSelectors addUser: addToComposition: addExclusionOf:to: removeAlias:of:) (#'*Fuel' fuelIgnoredInstanceVariableNames) (#'*System-Support' referencedClasses allUnsentMessages allCallsOn allCallsOnIn: allCallsOn:) (#naming environment name) (#'*Compiler-Kernel' decompilerClass recompile: parserClass compile: bindingOf: compile:classified:notifying:trailer:ifFail: compiler defaultMethodTrailer evaluatorClass compile:notifying: compileAll evaluate: compileAllFrom: compilerClass recompile:from: sourceCodeTemplate recompileChanges binding) (#'*Manifest-Core' isManifest) (#copying deepCopy copyOfMethodDictionary postCopy) (#'testing class hierarchy' kindOfSubclass inheritsFrom: includesBehavior:) (#initialization emptyMethodDictionary obsolete) (#'*Tools-Inspector' inspectAllInstances inspectSubInstances) (#accessing isComposedBy: localSelectors poolDictionaryNames classDepth typeOfClass numberOfInstanceVariables classPool localSelectors:) (#'*Rpackage-Core' originalName) (#'testing method dictionary' thoroughHasSelectorReferringTo:special:byte: isLocalAliasSelector: classBindingOf: whichClassIncludesSelector: whichSelectorsStoreInto: whichSelectorsReferTo:special:byte: isDisabledSelector: hasMethods canUnderstand: thoroughWhichSelectorsReferTo:special:byte: canPerform: whichSelectorsAccess: includesLocalSelector: whichSelectorsReferTo: isAliasSelector: includesSelector:) ! !TBehavior reorganize! (#'instance creation' new: basicNew: basicNew new) (#compiling instVarNamesAndOffsetsDo: variablesAndOffsetsDo:) (#'*NativeBoost-Core' nbBindingOf: externalTypeAlias: nbFnArgument:generator:) (#'*Manifest-Core' isManifest) (#'*Compiler-Kernel' decompilerClass recompile: parserClass compile: bindingOf: compile:classified:notifying:trailer:ifFail: compiler defaultMethodTrailer evaluatorClass compile:notifying: compileAll evaluate: compileAllFrom: compilerClass recompileChanges sourceCodeTemplate recompile:from: binding) (#naming environment) (#'obsolete subclasses' basicObsoleteSubclasses allLocalCallsOn: addObsoleteSubclass: removeAllObsoleteSubclasses removeObsoleteSubclass: obsoleteSubclasses) (#'*Fuel' fuelIgnoredInstanceVariableNames) (#testing isWeak isAnonymous isCompact isBytes instSpec sourceMatchesBytecodeAt: isObsolete shouldNotBeRedefined canZapMethodDictionary instSize isWords isMeta hasAbstractMethods isFixed isBits isVariable isPointers) (#'testing class hierarchy' kindOfSubclass inheritsFrom: includesBehavior:) (#queries copiesMethodsFromSuperclass copiedMethodsFromSuperclass whichClassDefinesInstVar: whichSuperclassSatisfies: copiesFromSuperclass: whichSelectorsRead: whichClassDefinesClassVar: whichSelectorsAssign: copiedFromSuperclass:) (#enumerating allSuperclassesDo: subclassesDo: selectSubclasses: withAllSuperAndSubclassesDo: allSubclassesDo: withAllSuperclassesDo: allInstancesDo: allUnreferencedInstanceVariables allSubInstancesDo: selectSuperclasses:) (#'accessing method dictionary' allMethods compiledMethodAt:ifAbsent: deregisterLocalSelector: selectors methodDict: allSelectorsAboveUntil: allSelectorsBelow: methodDictionary compress sourceCodeAt: registerLocalSelector: >> lookupSelector: nextQuotePosIn:startingFrom: methodDict allSelectorsAbove methodDictionary: selectorsWithArgs: supermostPrecodeCommentFor: changeRecordsAt: zapAllMethods allSelectorsWithout: methods firstCommentAt: selectorsAndMethodsDo: sourceCodeAt:ifAbsent: compiledMethodAt: classAndMethodFor:do:ifAbsent: firstPrecodeCommentFor: precodeCommentOrInheritedCommentFor: commentsAt: commentsIn: methodsDo: selectorsDo: ultimateSourceCodeAt:ifAbsent: allSelectors) (#'initialize-release' initialize nonObsoleteClass superclass:methodDictionary:format:) (#'memory usage' instancesSizeInMemory) (#'system startup' shutDown: shutDown startUp startUp:) (#'*System-Support' allCallsOn: allUnsentMessages allCallsOnIn: referencedClasses allCallsOn) (#'accessing class hierarchy' allSuperclasses superclass: withAllSubclasses withAllSuperclasses superclass allSuperclassesIncluding: withAllSubclassesDo: allSubclassesWithLevelDo:startingLevel: allSubclasses) (#initialization emptyMethodDictionary obsolete) (#'*Ring-Core-Kernel' protocols methodNamed: methodsInProtocol:) (#private spaceUsed becomeUncompact checkCanBeUncompact becomeCompactSimplyAt: becomeCompact flushCache indexIfCompact setFormat:) (#'*Tools-Inspector' inspectAllInstances inspectSubInstances) (#accessing isComposedBy: subclassDefinerClass name classDepth typeOfClass poolDictionaryNames numberOfInstanceVariables classPool) (#'*Nautilus' realClass) (#'adding/removing methods' addSelectorSilently:withMethod: basicRemoveSelector: addSelector:withMethod:notifying: methodDictAddSelectorSilently:withMethod: basicAddSelector:withMethod: removeSelector: addSelector:withMethod: removeSelectorSilently: adoptInstance:) (#'accessing instances and variables' subclassInstVarNames includesSharedPoolNamed: allClassVarNames classVarNames instVarNames instanceCount allSharedPools allowsSubInstVars allSubInstances allInstances sharedPools someInstance allInstVarNames) (#printing printHierarchy literalScannedAs:notifying: storeLiteral:on: printOn: longPrintOn:) (#'*Rpackage-Core' originalName) (#copying deepCopy copyOfMethodDictionary postCopy) (#'*ast-core' parseTreeFor:) (#traits addTraitSelector:withMethod: traitComposition: flattenDownAllTraits traits users flattenDown: classesComposedWithMe traitsProvidingSelector: users: traitOrClassOfSelector: removeUser: notifyUsersOfChangedSelector: traitCompositionIncludes: updateMethodDictionarySelector: purgeLocalSelectors traitComposition noteChangedSelectors: hasTraitComposition removeFromComposition: traitTransformations setTraitCompositionFrom: traitCompositionString setTraitComposition: notifyUsersOfChangedSelectors: removeTraitSelector: applyChangesOfNewTraitCompositionReplacing: ensureLocalSelectors addUser: addToComposition: addExclusionOf:to: removeAlias:of:) (#'testing method dictionary' thoroughHasSelectorReferringTo:special:byte: isLocalAliasSelector: classBindingOf: whichSelectorsStoreInto: whichClassIncludesSelector: whichSelectorsReferTo:special:byte: isDisabledSelector: hasMethods canUnderstand: thoroughWhichSelectorsReferTo:special:byte: canPerform: whichSelectorsAccess: includesLocalSelector: whichSelectorsReferTo: isAliasSelector: includesSelector:) (#cleanup cleanUp cleanUp:) (#'user interface' withAllSubAndSuperclassesDo: unreferencedInstanceVariables) !