Marcel Taeumel uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-mt.1001.mcz ==================== Summary ==================== Name: Tools-mt.1001 Author: mt Time: 14 October 2020, 2:10:41.330569 pm UUID: e912063d-b963-cf40-b8aa-66e99da3cd31 Ancestors: Tools-mt.1000 Rename #doWithIndex: to #withIndexDo:. See http://forum.world.st/The-Inbox-60Deprecated-ct-80-mcz-td5120706.html =============== Diff against Tools-mt.1000 =============== Item was changed: ----- Method: BasicInspector>>streamInstanceVariablesOn: (in category 'fields - streaming') ----- streamInstanceVariablesOn: aStream + (thisContext objectClass: self object) allInstVarNames withIndexDo: [:name :index | - (thisContext objectClass: self object) allInstVarNames doWithIndex: [:name :index | aStream nextPut: ((self newFieldForType: #instVar key: name) name: name asString; shouldStyleName: true; valueGetter: [:object | thisContext object: object instVarAt: index]; valueGetterExpression: ('thisContext object: {1} instVarAt: {2}' format: { 'self'. index }); valueSetter: [:object :value | thisContext object: object instVarAt: index put: value]; yourself)].! Item was changed: ----- Method: ChangedMessageSet>>contents:notifying: (in category 'acceptance') ----- contents: aString notifying: aController "Accept the string as new source for the current method, and make certain the annotation pane gets invalidated" | existingSelector existingClass superResult newSelector | existingSelector := self selectedMessageName. existingClass := self selectedClassOrMetaClass. superResult := super contents: aString notifying: aController. superResult ifTrue: "succeeded" [newSelector := existingClass newParser parseSelector: aString. newSelector ~= existingSelector ifTrue: "Selector changed -- maybe an addition" [self reformulateList. self changed: #messageList. + self messageList withIndexDo: - self messageList doWithIndex: [:aMethodReference :anIndex | (aMethodReference actualClass == existingClass and: [aMethodReference methodSymbol == newSelector]) ifTrue: [self messageListIndex: anIndex]]]]. ^ superResult! Item was changed: ----- Method: ClassInspector>>streamSharedPoolsOn: (in category 'fields - streaming') ----- streamSharedPoolsOn: aStream + self object sharedPools withIndexDo: [:pool :index | - self object sharedPools doWithIndex: [:pool :index | aStream nextPut: ((self newFieldForType: #poolDictionary key: (self environment keyAtIdentityValue: pool)) shouldStyleName: true; valueGetter: [:object | object sharedPools at: index]; valueSetter: [:object :value | object sharedPools at: index put: value]; yourself)].! Item was changed: ----- Method: CodeHolder>>messageHelpTruncated: (in category 'message list') ----- messageHelpTruncated: aText "Show only the first n lines of the text." | formatted lineCount | formatted := aText. lineCount := 0. + aText withIndexDo: [:char :index | - aText doWithIndex: [:char :index | char = Character cr ifTrue: [lineCount := lineCount + 1]. lineCount > 10 ifTrue: [ formatted := formatted copyFrom: 1 to: index-1. formatted append: ' [...]'. ^ formatted]]. ^ formatted! Item was changed: ----- Method: Context>>tempsAndValuesLimitedTo:indent: (in category '*Tools-debugger access') ----- tempsAndValuesLimitedTo: sizeLimit indent: indent "Return a string of the temporary variabls and their current values" | aStream | aStream := WriteStream on: (String new: 100). self tempNames + withIndexDo: [:title :index | - doWithIndex: [:title :index | indent timesRepeat: [aStream tab]. aStream nextPutAll: title; nextPut: $:; space; tab. aStream nextPutAll: ((self tempAt: index) printStringLimitedTo: (sizeLimit -3 -title size max: 1)). aStream cr]. ^aStream contents! Item was changed: ----- Method: ContextInspector>>streamTemporaryVariablesOn: (in category 'fields - streaming') ----- streamTemporaryVariablesOn: aStream | tempNames | tempNames := [self object tempNames] ifError: [ ^ self streamError: 'Invalid temporaries' translated on: aStream]. + tempNames withIndexDo: [:name :index | - tempNames doWithIndex: [:name :index | aStream nextPut: ((self newFieldForType: #tempVar key: name) name: ('[{1}]' format: {name}); valueGetter: [:context | context namedTempAt: index]; valueSetter: [:context :value | context namedTempAt: index put: value]; yourself)]! Item was changed: ----- Method: ContextVariablesInspector>>streamTemporaryVariablesOn: (in category 'fields - streaming') ----- streamTemporaryVariablesOn: aStream "Overwritten to change the visuals of temps in debuggers." | tempNames | tempNames := [self object tempNames] ifError: [ ^ self streamError: 'Invalid temporaries' translated on: aStream]. + tempNames withIndexDo: [:name :index | - tempNames doWithIndex: [:name :index | aStream nextPut: ((self newFieldForType: #tempVar key: name) shouldStyleName: true; valueGetter: [:context | context namedTempAt: index]; valueSetter: [:context :value | context namedTempAt: index put: value]; yourself)].! Item was changed: ----- Method: DebuggerMethodMap>>tempsAndValuesForContext: (in category 'accessing') ----- tempsAndValuesForContext: aContext "Return a string of the temporary variables and their current values" | aStream | aStream := WriteStream on: (String new: 100). + (self tempNamesForContext: aContext) withIndexDo: - (self tempNamesForContext: aContext) doWithIndex: [:title :index | aStream nextPutAll: title; nextPut: $:; space; tab. aContext print: (self namedTempAt: index in: aContext) on: aStream. aStream cr]. ^aStream contents! Item was changed: ----- Method: Inspector>>streamInstanceVariablesOn: (in category 'fields - streaming') ----- streamInstanceVariablesOn: aStream + (self object perform: #class "do not inline send of #class, receiver could be a proxy") allInstVarNames withIndexDo: [:name :index | - (self object perform: #class "do not inline send of #class, receiver could be a proxy") allInstVarNames doWithIndex: [:name :index | aStream nextPut: ((self newFieldForType: #instVar key: name) shouldStyleName: true; valueGetter: [:object | object instVarNamed: name]; valueSetter: [:object :value | object instVarNamed: name put: value]; yourself)].! Item was changed: ----- Method: Message>>createStubMethod (in category '*Tools-Debugger') ----- createStubMethod | argNames | argNames := Set new. ^ String streamContents: [ :s | + self selector keywords withIndexDo: [ :key :i | - self selector keywords doWithIndex: [ :key :i | | aOrAn argName arg argClassName | s nextPutAll: key. ((key last = $:) or: [self selector isInfix]) ifTrue: [ arg := self arguments at: i. argClassName := arg canonicalArgumentName. aOrAn := argClassName first isVowel ifTrue: ['an'] ifFalse: ['a']. argName := aOrAn, argClassName. [argNames includes: argName] whileTrue: [argName := argName, i asString]. argNames add: argName. s nextPutAll: ' '; nextPutAll: argName; space ]. ]. s cr; tab. s nextPutAll: 'self shouldBeImplemented' ].! Item was changed: ----- Method: MethodFinder>>exceptions (in category 'search') ----- exceptions "Handle some very slippery selectors. asSymbol -- want to be able to produce it, but do not want to make every string submitted into a Symbol!!" | aSel | answers first isSymbol ifFalse: [^ self]. thisData first first isString ifFalse: [^ self]. aSel := #asSymbol. (self testPerfect: aSel) ifTrue: [ selector add: aSel. expressions add: (String streamContents: [:strm | strm nextPutAll: 'data', argMap first printString. + aSel keywords withIndexDo: [:key :ind | - aSel keywords doWithIndex: [:key :ind | strm nextPutAll: ' ',key. (key last == $:) | (key first isLetter not) ifTrue: [strm nextPutAll: ' data', (argMap at: ind+1) printString]]])]. ! Item was changed: ----- Method: MethodFinder>>noteDangerous (in category 'initialize') ----- noteDangerous "Remember the methods with really bad side effects." Dangerous := Set new. "Object accessing, testing, copying, dependent access, macpal, flagging" #(addInstanceVarNamed:withValue: haltIfNil copyAddedStateFrom: veryDeepCopy veryDeepCopyWith: veryDeepFixupWith: veryDeepInner: addDependent: evaluate:wheneverChangeIn: codeStrippedOut: playSoundNamed: isThisEverCalled isThisEverCalled: logEntry logExecution logExit) do: [:sel | Dangerous add: sel]. "Object error handling" #(cannotInterpret: caseError confirm: confirm:orCancel: doesNotUnderstand: error: halt halt: notify: notify:at: primitiveFailed shouldNotImplement subclassResponsibility) do: [:sel | Dangerous add: sel]. "Object user interface" #(basicInspect beep inform: inspect inspectWithLabel: notYetImplemented inspectElement ) do: [:sel | Dangerous add: sel]. "Object system primitives" #(become: becomeForward: instVarAt:put: instVarNamed:put: nextInstance nextObject rootStubInImageSegment: someObject tryPrimitive:withArgs:) do: [:sel | Dangerous add: sel]. "Object private" #(errorImproperStore errorNonIntegerIndex errorNotIndexable errorSubscriptBounds: mustBeBoolean primitiveError: species storeAt:inTempFrame:) do: [:sel | Dangerous add: sel]. "Object, translation support" #(cCode: cCode:inSmalltalk: cCoerce:to: export: inline: returnTypeC: sharedCodeNamed:inCase: var:declareC:) do: [:sel | Dangerous add: sel]. "Object, objects from disk, finalization. And UndefinedObject" #(comeFullyUpOnReload: objectForDataStream: readDataFrom:size: rehash saveOnFile storeDataOn: actAsExecutor executor finalize retryWithGC:until: suspend) do: [:sel | Dangerous add: sel]. "No Restrictions: Boolean, False, True, " "Morph" #() do: [:sel | Dangerous add: sel]. "Behavior" #(obsolete confirmRemovalOf: copyOfMethodDictionary storeLiteral:on: addSubclass: removeSubclass: superclass: "creating method dictionary" addSelector:withMethod: compile: compile:notifying: compileAll compileAllFrom: compress decompile: defaultSelectorForMethod: methodDictionary: recompile:from: recompileChanges removeSelector: compressedSourceCodeAt: selectorAtMethod:setClass: allInstances allSubInstances inspectAllInstances inspectSubInstances thoroughWhichSelectorsReferTo:special:byte: "enumerating" allInstancesDo: allSubInstancesDo: allSubclassesDo: allSuperclassesDo: selectSubclasses: selectSuperclasses: subclassesDo: withAllSubclassesDo: "too slow->" crossReference removeUninstantiatedSubclassesSilently "too slow->" unreferencedInstanceVariables "private" flushCache format:variable:words:pointers: format:variable:words:pointers:weak: format:variable:bitsUnitSize:pointers:weak: printSubclassesOn:level: basicRemoveSelector: addSelector:withMethod:notifying: addSelectorSilently:withMethod:) do: [:sel | Dangerous add: sel]. "CompiledMethod" #(defaultSelector) do: [:sel | Dangerous add: sel]. "Others " #("no tangible result" do: associationsDo: + "private" adaptToCollection:andSend: adaptToNumber:andSend: adaptToPoint:andSend: adaptToString:andSend: instVarAt:put: asDigitsToPower:do: combinations:atATimeDo: pairsDo: permutationsDo: reverseDo: reverseWith:do: with:do: withIndexDo: asDigitsAt:in:do: combinationsAt:in:after:do: errorOutOfBounds permutationsStartingAt:do: fromUser) - "private" adaptToCollection:andSend: adaptToNumber:andSend: adaptToPoint:andSend: adaptToString:andSend: instVarAt:put: asDigitsToPower:do: combinations:atATimeDo: doWithIndex: pairsDo: permutationsDo: reverseDo: reverseWith:do: with:do: withIndexDo: asDigitsAt:in:do: combinationsAt:in:after:do: errorOutOfBounds permutationsStartingAt:do: fromUser) do: [:sel | Dangerous add: sel]. #( fileOutPrototype addSpareFields makeFileOutFile ) do: [:sel | Dangerous add: sel]. #(recompile:from: recompileAllFrom: recompileChanges asPrototypeWithFields: asPrototype addInstanceVarNamed:withValue: addInstanceVariable addClassVarName: removeClassVarName: findOrAddClassVarName: instanceVariableNames: ) do: [:sel | Dangerous add: sel]. ! Item was changed: ----- Method: MethodFinder>>simpleSearch (in category 'search') ----- simpleSearch "Run through first arg's class' selectors, looking for one that works." | class supers listOfLists | self exceptions. class := thisData first first class. "Cache the selectors for the receiver class" (class == cachedClass and: [cachedArgNum = ((argMap size) - 1)]) ifTrue: [listOfLists := cachedSelectorLists] ifFalse: [supers := class withAllSuperclasses. listOfLists := OrderedCollection new. supers do: [:cls | listOfLists add: (cls selectorsWithArgs: (argMap size) - 1)]. cachedClass := class. cachedArgNum := (argMap size) - 1. cachedSelectorLists := listOfLists]. listOfLists do: [:selectorList | selectorList do: [:aSel | (selector includes: aSel) ifFalse: [ ((Approved includes: aSel) or: [AddAndRemove includes: aSel]) ifTrue: [ (self testPerfect: aSel) ifTrue: [ selector add: aSel. expressions add: (String streamContents: [:strm | strm nextPutAll: 'data', argMap first printString. + aSel keywords withIndexDo: [:key :ind | - aSel keywords doWithIndex: [:key :ind | strm nextPutAll: ' ',key. (key last == $:) | (key first isLetter not) ifTrue: [strm nextPutAll: ' data', (argMap at: ind+1) printString]]]) ]]]]]. ! Item was changed: ----- Method: SetInspector>>elementIndices (in category 'private') ----- elementIndices "In the set's internal array, extract the indices that point to actual elements." | numIndices | (numIndices := self objectSize) = 0 ifTrue: [^#()]. ^ Array new: numIndices streamContents: [:stream | + self object array withIndexDo: [:element :index | - self object array doWithIndex: [:element :index | (self isElementValid: element) ifTrue: [stream nextPut: index]]]! |
Free forum by Nabble | Edit this page |