[Pkg] Squeak3.10bc: 39Deprecated-kph.12.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sat Dec 13 04:48:53 UTC 2008


A new version of 39Deprecated was added to project Squeak3.10bc:
http://www.squeaksource.com/310bc/39Deprecated-kph.12.mcz

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

Name: 39Deprecated-kph.12
Author: kph
Time: 13 December 2008, 4:48:52 am
UUID: 835ceed6-92b0-4cc3-b795-67a436212222
Ancestors: 39Deprecated-md.11

Saved from SystemVersion

==================== Snapshot ====================

SystemOrganization addCategory: #'39Deprecated'!

----- Method: Behavior>>scopeHas:ifTrue: (in category '*39Deprecated') -----
scopeHas: varName ifTrue: aBlock
	"Obsolete. Kept around for possible spurios senders which we don't know about"
	self deprecated: 'Obsolete'.
	(self bindingOf: varName) ifNotNilDo:[:binding|
		aBlock value: binding.
		^true].
	^false!

----- Method: Behavior>>selectorAtMethod:setClass: (in category '*39Deprecated') -----
selectorAtMethod: method setClass: classResultBlock 
	"Answer both the message selector associated with the compiled method 
	and the class in which that selector is defined."

	| sel |

	self deprecated: 'please call #methodClass and #selector on the method'.

	sel _ self methodDict keyAtIdentityValue: method
				ifAbsent: 
					[superclass == nil
						ifTrue: 
							[classResultBlock value: self.
							^method defaultSelector].
					sel _ superclass selectorAtMethod: method setClass: classResultBlock.
					"Set class to be self, rather than that returned from 
					superclass. "
					sel == method defaultSelector ifTrue: [classResultBlock value: self].
					^sel].
	classResultBlock value: self.
	^sel!

----- Method: SharedQueue2>>flush (in category '*39Deprecated') -----
flush
	self deprecated: 'use removeAll'.
	^self removeAll!

----- Method: SharedQueue2>>flushAllSuchThat: (in category '*39Deprecated') -----
flushAllSuchThat: aBlock
	self deprecated: 'use removeAllSuchThat:'.

	^self removeAllSuchThat: aBlock!

----- Method: SharedQueue2>>removeAll (in category '*39Deprecated') -----
removeAll
	monitor critical: [
		items next: (items size) ].!

----- Method: SharedQueue2>>removeAllSuchThat: (in category '*39Deprecated') -----
removeAllSuchThat: aBlock
	"Remove from the queue all objects that satisfy aBlock."
	monitor critical: [
		items removeAllSuchThat: aBlock ]!

Object subclass: #CurrentProjectRefactoring
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: '39Deprecated'!

----- Method: CurrentProjectRefactoring class>>currentAddGuard: (in category 'revectoring to current') -----
currentAddGuard: anObject
"
CurrentProjectRefactoring currentAddGuard:
"	
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent addGuard: anObject!

----- Method: CurrentProjectRefactoring class>>currentBeIsolated (in category 'revectoring to current') -----
currentBeIsolated
"
CurrentProjectRefactoring currentBeIsolated
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent beIsolated!

----- Method: CurrentProjectRefactoring class>>currentBeParentTo: (in category 'revectoring to current') -----
currentBeParentTo: anotherProject
"
CurrentProjectRefactoring currentBeParentTo:
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^anotherProject setParent: self xxxCurrent!

----- Method: CurrentProjectRefactoring class>>currentBeParentToCurrent (in category 'revectoring to current') -----
currentBeParentToCurrent
"
CurrentProjectRefactoring currentBeParentToCurrent
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent setParent: self xxxCurrent!

----- Method: CurrentProjectRefactoring class>>currentFlapsSuppressed (in category 'revectoring to current') -----
currentFlapsSuppressed
"
CurrentProjectRefactoring currentFlapsSuppressed
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent flapsSuppressed!

----- Method: CurrentProjectRefactoring class>>currentFromMyServerLoad: (in category 'revectoring to current') -----
currentFromMyServerLoad: aProjectName
"
CurrentProjectRefactoring currentFromMyServerLoad:
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent fromMyServerLoad: aProjectName!

----- Method: CurrentProjectRefactoring class>>currentInterruptName: (in category 'revectoring to current') -----
currentInterruptName: aString
"
CurrentProjectRefactoring currentInterruptName:
"

	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^Project interruptName: aString!

----- Method: CurrentProjectRefactoring class>>currentInterruptName:preemptedProcess: (in category 'revectoring to current') -----
currentInterruptName: aString preemptedProcess: theInterruptedProcess

	^ Project interruptName: aString preemptedProcess: theInterruptedProcess!

----- Method: CurrentProjectRefactoring class>>currentIsolationHead (in category 'revectoring to current') -----
currentIsolationHead
"
CurrentProjectRefactoring currentIsolationHead
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent isolationHead!

----- Method: CurrentProjectRefactoring class>>currentProjectName (in category 'revectoring to current') -----
currentProjectName
"
CurrentProjectRefactoring currentProjectName
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
		
	^self xxxCurrent name!

----- Method: CurrentProjectRefactoring class>>currentPropagateChanges (in category 'revectoring to current') -----
currentPropagateChanges
"
CurrentProjectRefactoring currentPropagateChanges
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent propagateChanges!

----- Method: CurrentProjectRefactoring class>>currentSpawnNewProcessAndTerminateOld: (in category 'revectoring to current') -----
currentSpawnNewProcessAndTerminateOld: aBoolean
"
CurrentProjectRefactoring currentSpawnNewProcessAndTerminateOld:
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^Project spawnNewProcessAndTerminateOld: aBoolean

!

----- Method: CurrentProjectRefactoring class>>currentToggleFlapsSuppressed (in category 'revectoring to current') -----
currentToggleFlapsSuppressed
"
CurrentProjectRefactoring currentToggleFlapsSuppressed
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent flapsSuppressed: self xxxCurrent flapsSuppressed not.


!

----- Method: CurrentProjectRefactoring class>>exitCurrentProject (in category 'miscellaneous') -----
exitCurrentProject
"
CurrentProjectRefactoring exitCurrentProject
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^self xxxCurrent exit
!

----- Method: CurrentProjectRefactoring class>>isFlapEnabled: (in category 'flaps') -----
isFlapEnabled: aFlapTab
	"Answer whether the given flap tab is enabled in the current project"
	
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^ self xxxCurrent isFlapEnabled: aFlapTab!

----- Method: CurrentProjectRefactoring class>>newProcessIfUI: (in category 'miscellaneous') -----
newProcessIfUI: aDeadOrDyingProcess
"
CurrentProjectRefactoring newProcessIfUI:
used ONLY for Morphic
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^Project spawnNewProcessIfThisIsUI: aDeadOrDyingProcess!

----- Method: CurrentProjectRefactoring class>>projectWithNameOrCurrent: (in category 'miscellaneous') -----
projectWithNameOrCurrent: aString
"
CurrentProjectRefactoring projectWithNameOrCurrent:
"
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^(Project named: aString) ifNil: [self xxxCurrent]!

----- Method: CurrentProjectRefactoring class>>showSharedFlaps (in category 'flaps') -----
showSharedFlaps
	"Answer whether shared flaps are currently showing (true) or suppressed (false).  The CurrentProjectRefactoring circumlocution is in service of making it possible for shared flaps to appear on the edges of an interior subworld, I believe."
	
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^ self xxxCurrent showSharedFlaps!

----- Method: CurrentProjectRefactoring class>>suppressFlapsString (in category 'flaps') -----
suppressFlapsString
	"Answer a string characterizing whether flaps are suppressed 
	at the moment or not"
	
	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^ (self currentFlapsSuppressed
		ifTrue: ['<no>']
		ifFalse: ['<yes>']), 'show shared tabs (F)' translated!

----- Method: CurrentProjectRefactoring class>>xxxCurrent (in category 'revectoring to current') -----
xxxCurrent

	self deprecated: 'CurrentProjectRefactoring is deprecated'.
	
	^Project current!

----- Method: Object>>beep (in category '*39Deprecated') -----
beep
	"Deprecated."
	
	self deprecated: 'Use Beeper class>>beep instead.'.
	Beeper beep!

----- Method: Object>>beep: (in category '*39Deprecated') -----
beep: soundName
	"Make the given sound, unless the making of sound is disabled in Preferences."

	self deprecated: 'Use SampledSound>>playSoundNamed: instead.'.
	Preferences soundsEnabled
		ifTrue: [self playSoundNamed: soundName]
!

----- Method: Object>>beepPrimitive (in category '*39Deprecated') -----
beepPrimitive
	"Deprecated. Beep in the absence of sound support."
	
	self deprecated: 'Use Beeper class>>beep or Beeper class>>beepPrimitive instead.'.
	Beeper beepPrimitive!

----- Method: Object>>contentsGetz: (in category '*39Deprecated') -----
contentsGetz: x
	self deprecated: 'there is no method named contents in object and in addition only one sender in a method not called'. 
	self contents: x!

----- Method: Object>>deprecated:explanation: (in category '*39Deprecated') -----
deprecated: aBlock explanation: aString 
	 "This method is OBSOLETE.  Use #deprecated:block: instead."
	self deprecated: 'Use Object>>deprecated:block: instead of deprecated:explanation:.'.

	Preferences showDeprecationWarnings ifTrue:
		[Deprecation
			signal: ('{1} has been deprecated. {2}' translated format: {thisContext sender printString. aString})].
	^ aBlock value.
!

----- Method: Object>>deprecatedExplanation: (in category '*39Deprecated') -----
deprecatedExplanation: aString
     "This method is OBSOLETE.  Use #deprecated: instead."
	self deprecated: 'Use Object>>deprecated: instead of deprecatedExplanation:.'.

	Preferences showDeprecationWarnings ifTrue:
		[Deprecation signal: ('{1} has been deprecated. {2}' translated format: {thisContext sender printString. aString})]!

----- Method: Object>>doIfNotNil: (in category '*39Deprecated') -----
doIfNotNil: aBlock
	self deprecated: 'use ifNotNilDo:'.
	^ self ifNotNilDo: aBlock
!

----- Method: Object>>ifKindOf:thenDo: (in category '*39Deprecated') -----
ifKindOf: aClass thenDo: aBlock
	self deprecated: 'Deprecated. Just use #isKindOf:'.
	^ (self isKindOf: aClass) ifTrue: [aBlock value: self]!

----- Method: Object>>playSoundNamed: (in category '*39Deprecated') -----
playSoundNamed: soundName
	"Deprecated.
	Play the sound with the given name."

	self deprecated: 'Use "SoundService default playSoundNamed: aName" instead.'.
	SoundService default playSoundNamed: soundName!

----- Method: ClassDescription>>categoryFromUserWithPrompt: (in category '*39Deprecated') -----
categoryFromUserWithPrompt: aPrompt
	"SystemDictionary categoryFromUserWithPrompt: 'testing'"

	self deprecated: 'Use CodeHolder>>categoryFromUserWithPrompt: aPrompt for: aClass instead'.
	"this deprecation helps to remove UI dependency from the core of Squeak.
	Normally only CodeHolder was calling this method"
	CodeHolder new categoryFromUserWithPrompt: aPrompt for: self!

----- Method: ClassDescription>>letUserReclassify: (in category '*39Deprecated') -----
letUserReclassify: anElement
	"Put up a list of categories and solicit one from the user.  
	Answer true if user indeed made a change, else false"
	
	self deprecated: 'Use CodeHolder>>letUserReclassify: anElement in: aClass'.
	CodeHolder new letUserReclassify: anElement in: self.!

----- Method: ClassDescription>>methods (in category '*39Deprecated') -----
methods
	"Answer a ClassCategoryReader for compiling messages that are not classified, as in fileouts made with Smalltalk/V"
	self deprecated: 'Is this used?'.
	^ ClassCategoryReader new setClass: self category: ClassOrganizer default!

----- Method: CompiledMethod>>decompileClass:selector: (in category '*39Deprecated') -----
decompileClass: aClass selector: selector
	"Return the decompiled parse tree that represents self"

	self deprecated: 'just call #decompile on the CompiledMethod'.
	^ self decompilerClass new decompile: selector in: aClass method: self!

----- Method: CompiledMethod>>decompileTree (in category '*39Deprecated') -----
decompileTree
	self deprecated: 'just use #decompile'.
	^self decompile.!

----- Method: CompiledMethod>>who (in category '*39Deprecated') -----
who
	"Answer an Array of the class in which the receiver is defined and the 
	selector to which it corresponds."
	
	self deprecated: 'use #methodClass and #selector directly'.
	self isInstalled ifFalse: [^#(unknown unknown)].
	^{self methodClass . self selector}.!

----- Method: MethodContext>>answer: (in category '*39Deprecated') -----
answer: anObject
	"ar 3/6/2001: OBSOLETE. Must not be used. Will be removed VERY SOON."
	
	self deprecated: 'ar 3/6/2001: OBSOLETE. Must not be used. Will be removed VERY SOON.'.
	
	"Modify my code, from the current program counter value, to answer anObject."
	self push: anObject.
	(method at: pc) = 124 ifFalse: [
		method _ (
			(method clone)
				at: pc + 1 put: 124;
				yourself)]!

----- Method: MethodContext>>who (in category '*39Deprecated') -----
who
	self deprecated: 'please use #methodClass and #selector'.
	
	self method ifNil: [^ #(unknown unkown)].
	^ {self methodClass . self selector}.
!

----- Method: SystemDictionary>>associationAtOrAbove:ifAbsent: (in category '*39Deprecated') -----
associationAtOrAbove: varName ifAbsent: absentBlock 
	"Compatibility with environment protocol."

	self deprecated: 'use associationAt:ifAbsent:'.
	^ self associationAt: varName ifAbsent: absentBlock!

----- Method: SystemDictionary>>atOrAbove:ifAbsent: (in category '*39Deprecated') -----
atOrAbove: key ifAbsent: absentBlock
	"Compatibility with environment protocol."

	self deprecated: 'use at:ifAbsent:'.
	^ self at: key ifAbsent: absentBlock!

----- Method: SystemDictionary>>atOrBelow:ifAbsent: (in category '*39Deprecated') -----
atOrBelow: key ifAbsent: absentBlock
	"Compatibility with environment protocol."
	
	self deprecated: 'use at:ifAbsent:'.
	^ self at: key ifAbsent: absentBlock!

----- Method: SystemDictionary>>environmentForCategory: (in category '*39Deprecated') -----
environmentForCategory: catName 
	"Default response for non-partitioned systems"
	self deprecated: 'deprecated'.
	^ self!

----- Method: SystemDictionary>>getFileNameFromUser (in category '*39Deprecated') -----
getFileNameFromUser

	| newName |
	self deprecated: 'Use SmalltalkImage current getFileNameFromUser'.
	newName := UIManager default
		request: 'New File Name?' translated
		initialAnswer: (FileDirectory localNameFor: SmalltalkImage current imageName).
	newName = '' ifTrue: [^nil].
	((FileDirectory default fileOrDirectoryExists: (SmalltalkImage current fullNameForImageNamed: newName)) or:
	 [FileDirectory default fileOrDirectoryExists: (SmalltalkImage current fullNameForChangesNamed: newName)]) ifTrue: [
		(self confirm: ('{1} already exists. Overwrite?' translated format: {newName})) ifFalse: [^nil]].
	^newName
!

----- Method: SystemDictionary>>includesKeyOrAbove: (in category '*39Deprecated') -----
includesKeyOrAbove: key
	"Compatibility with environment protocol."

	self deprecated: 'use includesKey:'.
	self at: key ifAbsent: [^ false].
	^ true!

----- Method: SystemDictionary>>scopeFor:from:envtAndPathIfFound: (in category '*39Deprecated') -----
scopeFor: varName from: lower envtAndPathIfFound: envtAndPathBlock
	"Null compatibility with partitioning into environments."
	
	self deprecated: 'deprecated'.

	(self includesKey: varName)
		ifTrue: [^ envtAndPathBlock value: self value: String new]
		ifFalse: [^ nil]!

----- Method: SystemDictionary>>vmParameterAt: (in category '*39Deprecated') -----
vmParameterAt: parameterIndex
	"See comment for SmalltalkImage>vmParameterAt:"

	^ self deprecated: 'Use SmalltalkImage current vmParameterAt:'
		block: [SmalltalkImage current vmParameterAt: parameterIndex]
	!

----- Method: ContextPart>>mclass (in category '*39Deprecated') -----
mclass 
	"Answer the class in which the receiver's method was found."
	self deprecated: 'use #methodClass'.
	^ self methodClass!

----- Method: ContextPart>>methodSelector (in category '*39Deprecated') -----
methodSelector
	"Answer the selector of the method that created the receiver."
	self deprecated: 'use #selector'.

	^self selector.!

----- Method: Utilities class>>browseVersionsForClass:selector: (in category '*39Deprecated') -----
browseVersionsForClass: aClass selector: aSelector
	self deprecated: 'Use VersionsBrowser browseVersionsForClass: aClass selector: aSelector instead'.
	VersionsBrowser browseVersionsForClass: aClass selector: aSelector!

----- Method: Utilities class>>fileOutChangeSetsNamed: (in category '*39Deprecated') -----
fileOutChangeSetsNamed: nameList
	"File out the list of change sets whose names are provided"
     self deprecated: 'Use ChangeSet fileOutChangeSetsNamed: nameList'.
	ChangeSet fileOutChangeSetsNamed: nameList!

----- Method: PasteUpMorph>>bringFlapTabsToFront (in category '*39Deprecated') -----
bringFlapTabsToFront
	self deprecated: 'Replaced by #bringTopmostsToFront'.
	(submorphs select:[:m| m wantsToBeTopmost]) do:[:m| self addMorphInLayer: m].!



More information about the Packages mailing list