[squeak-dev] The Inbox: 60Deprecated-ct.43.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 15 15:40:56 UTC 2019


A new version of 60Deprecated was added to project The Inbox:
http://source.squeak.org/inbox/60Deprecated-ct.43.mcz

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

Name: 60Deprecated-ct.43
Author: ct
Time: 15 August 2019, 5:40:55.376735 pm
UUID: decdf9b2-4ca2-fe4f-9d26-09a2712766b7
Ancestors: 60Deprecated-ct.42

Mark further methods as deprecated (and check their senders)

=============== Diff against 60Deprecated-ct.42 ===============

Item was changed:
  ----- Method: AbstractEvent class>>comment1 (in category '*60Deprecated-temporary') -----
  comment1
  
+ self deprecated.
  "Smalltalk organization removeElement: #ClassForTestingSystemChanges3
  Smalltalk garbageCollect 
  Smalltalk organizati
  
  classify:under:
  
  
  SystemChangeNotifier uniqueInstance releaseAll
  SystemChangeNotifier uniqueInstance noMoreNotificationsFor: aDependent.
  
  
  aDependent := SystemChangeNotifierTest new.
  SystemChangeNotifier uniqueInstance
  	notifyOfAllSystemChanges: aDependent
  	using: #event:
  
  SystemChangeNotifier uniqueInstance classAdded: #Foo inCategory: #FooCat
  
  
  
  | eventSource dependentObject |
  eventSource := EventManager new.
  dependentObject := Object new.
  
  register - dependentObject becomes dependent:
  eventSource
  	when: #anEvent send: #error to: dependentObject.
  
  unregister dependentObject:
  eventSource removeDependent: dependentObject.
  
  [eventSource triggerEvent: #anEvent]
  	on: Error
  	do: [:exc | self halt: 'Should not be!!']."!

Item was changed:
  ----- Method: AbstractEvent class>>comment2 (in category '*60Deprecated-temporary') -----
  comment2
  
+ self deprecated.
  "HTTPSocket useProxyServerNamed: 'proxy.telenet.be' port: 8080
  TestRunner open
  
  --------------------
  We propose two orthogonal groups to categorize each event:
  (1) the 'change type':
  	added, removed, modified, renamed
  	+ the composite 'changed' (see below for an explanation)
  (2) the 'item type':
  	class, method, instance variable, pool variable, protocol, category
  	+ the composite 'any' (see below for an explanation).
  The list of supported events is the cross product of these two lists (see below for an explicit enumeration of the events).
  
  Depending on the change type, certain information related to the change is always present (for adding, the new things that was added, for removals, what was removed, for renaming, the old and the new name, etc.).
  
  Depending on the item type, information regarding the item is present (for a method, which class it belongs to). 
  
  Certain events 'overlap', for example, a method rename triggers a class change. To capture this I impose a hierarchy on the 'item types' (just put some numbers to clearly show the idea. They don't need numbers, really. Items at a certain categories are included by items one category number higher):
  level 1 category
  level 2 class
  level 3 instance variable, pool variable, protocol, method.
  
  Changes propagate according to this tree: any 'added', 'removed' or 'renamed' change type in level X triggers a 'changed' change type in level X - 1. A 'modified' change type does not trigger anything special.
  For example, a method additions triggers a class modification. This does not trigger a category modification.
  
  Note that we added 'composite events': wildcards for the 'change type' ('any' - any system additions) and for the 'item type' ('Changed' - all changes related to classes), and one for 'any change systemwide' (systemChanged).
  
  This result is this list of Events:
  
  classAdded
  classRemoved
  classModified
  classRenamed (?)
  classChanged (composite)
  
  methodAdded
  methodRemoved
  methodModified
  methodRenamed (?)
  methodChanged (composite)
  
  instanceVariableAdded
  instanceVariableRemoved
  instanceVariableModified 
  instanceVariableRenamed (?)
  instanceVariableChanged (composite)
  
  protocolAdded
  protocolRemoved
  protocolModified
  protocolRenamed (?)
  protocolChanged (composite)
  
  poolVariableAdded
  poolVariableRemoved
  poolVariableModified
  poolVariableRenamed (?)
  poolChanged (composite)
  
  categoryAdded
  categoryRemoved
  categoryModified
  categeryRenamed (?)
  categoryChanged (composite)
  
  anyAdded (composite)
  anyRemoved (composite)
  anyModified (composite)
  anyRenamed (composite)
  
  anyChanged (composite)
  
  
  
  To check: can we pass somehow the 'source' of the change (a browser, a file-in, something else) ? Maybe by checking the context, but should not be too expensive either... I found this useful in some of my tools, but it might be too advanced to have in general. Tools that need this can always write code to check it for them.  But is not always simple...
  
  
  Utilities (for the recent methods) and ChangeSet are the two main clients at this moment.
  
  Important: make it very explicit that the event is send synchronously (or asynchronously, would we take that route).
  
  
  					category
  						class
  							comment
  							protocol
  								method
  OR
  				category
  				Smalltalk
  					class
  						comment
  						protocol
  						method
  ??
  
  
  
  						Smalltalk	category
  								\	/
  								class
  							/	  |	\
  						comment  |	protocol
  								  |	/
  								method
  
  "!

Item was changed:
  ----- Method: AbstractEvent class>>comment3 (in category '*60Deprecated-temporary') -----
  comment3
  
+ self deprecated.
  "Things to consider for trapping:
  ClassOrganizer>>#changeFromCategorySpecs:
  	Problem: I want to trap this to send the appropriate bunch of ReCategorization events, but ClassOrganizer instances do not know where they belong to (what class, or what system); it just uses symbols. So I cannot trigger the change, because not enough information is available. This is a conceptual problem: the organization is stand-alone implementation-wise, while conceptually it belongs to a class. The clean solution could be to reroute this message to a class, but this does not work for all of the senders (that would work from the browserm but not for the file-in).
  
  Browser>>#categorizeAllUncategorizedMethods
  	Problem: should be trapped to send a ReCategorization event. However, this is model code that should not be in the Browser. Clean solution is to move it out of there to the model, and then trap it there (or reroute it to one of the trapped places).
  
  Note: Debugger>>#contents:notifying: recompiles methods when needed, so I trapped it to get updates. However, I need to find a way to write a unit test for this. Haven't gotten around yet for doing this though...
  "!

Item was changed:
  ----- Method: AbstractEvent class>>saveChangeNotificationAsSARFileWithNumber: (in category '*60Deprecated-temporary') -----
  saveChangeNotificationAsSARFileWithNumber: aNumber 
  	"Use the SARBuilder package to output the SystemChangeNotification 
  	stuff as a SAR file. Put this statement here so that I don't forget it 
  	when moving between images :-)"
  	"self saveChangeNotificationAsSARFileWithNumber: 6"
  
  	| filename changesText readmeText dumper |
+ 	self deprecated.
  	filename := 'SystemchangeNotification'.
  	dumper := self class environment at: #SARChangeSetDumper ifAbsent: [ ^self ].
  	changesText := 
  '
  0.6 Version for Squeak 3.7 (no longer for 3.6!!!!) Changed one hook method to make this version work in Squeak3.7. Download version 5 from http://www.iam.unibe.ch/~wuyts/SystemchangeNotification5.sar if you are working with Squeak 3.6.
  
  0.5 Updated the safeguard mechanism so that clients with halts and errors do not stop all notifications. Added and updated new tests for this. If this interests you have a look at the class WeakActionSequenceTrappingErrors.
  
  0.4 Ported to Squeak 3.6.
  
  0.3 Added the hooks for instance variables (addition, removal and renaming). Refactored the tests.
  
  0.2 Added hooks and tests for method removal and method recategorization.
  
  0.1 First release'.
  	readmeText :=
  'Implements (part of) the system change notification mechanism. Clients that want to receive notifications about system changes should look at the category #public of the class SystemChangeNotifier, and the unit tests.
  
  VERY IMPORTANT: This version is for Squeak 3.7 only. It will not work in Squeak version 3.6. Download and install the last version that worked in Squeak 3.6 (version 5) from the following URL: http://www.iam.unibe.ch/~wuyts/SystemchangeNotification5.sar'.
  
  	(dumper
  		on: Project current changeSet
  		including: (ChangeSet allChangeSetNames
  				select: [:ea | 'SystemChangeHooks' match: ea])) changesText: changesText;
  		 readmeText: readmeText;
  		 fileOutAsZipNamed: filename , aNumber printString , '.sar'!

Item was changed:
  ----- Method: AutoStart class>>checkForPluginUpdate (in category '*60Deprecated') -----
  checkForPluginUpdate
  	| pluginVersion updateURL |
+ 	self deprecated.
  	HTTPClient isRunningInBrowser
  		ifFalse: [^false].
  	pluginVersion := Smalltalk namedArguments
  		at: (Smalltalk platformName copyWithout: Character space) asUppercase
  		ifAbsent: [^false].
  	updateURL := Smalltalk namedArguments
  		at: 'UPDATE_URL'
  		ifAbsent: [^false].
  	^SystemVersion check: pluginVersion andRequestPluginUpdate: updateURL!

Item was changed:
  ----- Method: AutoStart class>>checkForUpdates (in category '*60Deprecated') -----
  checkForUpdates
  	| availableUpdate updateServer |
+ 	self deprecated: 'Running in Browser no longer supported'.
  	HTTPClient isRunningInBrowser ifFalse: [ ^ self processUpdates ].
  	availableUpdate := (Smalltalk namedArguments
  		at: 'UPDATE'
  		ifAbsent: [ '' ]) asInteger.
  	availableUpdate ifNil: [ ^ false ].
  	updateServer := Smalltalk namedArguments
  		at: 'UPDATESERVER'
  		ifAbsent:
  			[ Smalltalk namedArguments
  				at: 'UPDATE_SERVER'
  				ifAbsent: [ 'Squeakland' ] ].
  	UpdateStreamDownloader default setUpdateServer: updateServer.
  	^ SystemVersion checkAndApplyUpdates: availableUpdate!

Item was removed:
- ----- Method: Context>>blockCopy: (in category '*60Deprecated-controlling') -----
- blockCopy: numArgs 
- 	"Primitive. Distinguish a block of code from its enclosing method by 
- 	creating a new BlockContext for that block. The compiler inserts into all 
- 	methods that contain blocks the bytecodes to send the message 
- 	blockCopy:. Do not use blockCopy: in code that you write!! Only the 
- 	compiler can decide to send the message blockCopy:. Fail if numArgs is 
- 	not a SmallInteger. Optional. No Lookup. See Object documentation 
- 	whatIsAPrimitive."
- 
- 	<primitive: 80>
- 	^ (BlockContext newForMethod: self method)
- 		home: self home
- 		startpc: pc + 2
- 		nargs: numArgs!

Item was changed:
  ----- Method: DirectoryEntry class>>name:creationTime:modificationTime:isDirectory:fileSize: (in category '*60Deprecated-Files-Directories') -----
  name: name0  creationTime: creationTime  modificationTime: modificationTime   isDirectory: isDirectory  fileSize: fileSize
- 	"This is the legacy creation method we are trying to phase out.  Please use #directory:  name:  creationTime:  modificationTime:  fileSize:." 
  	| type |
+ 	self deprecated: 'Please use ', #directory:name:creationTime:modificationTime:fileSize:.
  	type := isDirectory 
  		ifTrue: [ DirectoryEntryDirectory ]
  		ifFalse: [ DirectoryEntryFile ].
  	^ type
  		directory: nil
  		name: name0  
  		creationTime: creationTime  
  		modificationTime: modificationTime   
  		fileSize: fileSize!

Item was changed:
  ----- Method: DummyUIManager>>fontFromUser: (in category '*60Deprecated') -----
  fontFromUser: priorFont
+ 	self deprecated: 'Use ', [StrikeFont fromUser] sourceString.
  	self error: 'No user response possible'!

Item was changed:
  ----- Method: DummyUIManager>>openPluggableFileList:label:in: (in category '*60Deprecated') -----
  openPluggableFileList: aPluggableFileList label: aString in: aWorld
+ 	self deprecated: 'PluggableFileList must die'.
- 	"PluggableFileList is being deprecated and this can go away soon"
  	^nil!

Item was changed:
  ----- Method: DummyUIManager>>openPluggableFileListLabel:in: (in category '*60Deprecated') -----
  openPluggableFileListLabel: aString in: aWorld
+ 	self deprecated: 'PluggableFileList must die'.
- 	"PluggableFileList is being deprecated and this can go away soon"
  	^nil!

Item was changed:
  ----- Method: FileStream class>>httpPostMultipart:args: (in category '*60Deprecated-NSPlugin-System-Support') -----
  httpPostMultipart: url args: argsDict 
  	| mimeBorder argsStream crLf resultStream result |
  	" do multipart/form-data encoding rather than x-www-urlencoded "
  
+ 	self deprecated: 'NSPlugin no longer supported'.
  	crLf := String crlf.
  	mimeBorder := '----squeak-', Time millisecondClockValue printString, '-stuff-----'.
  	"encode the arguments dictionary"
  	argsStream := WriteStream on: String new.
  	argsDict associationsDo: [:assoc |
  		assoc value do: [ :value | | fieldValue |
  		"print the boundary"
  		argsStream nextPutAll: '--', mimeBorder, crLf.
  		" check if it's a non-text field "
  		argsStream nextPutAll: 'Content-disposition: form-data; name="', assoc key, '"'.
  		(value isKindOf: MIMEDocument)
  			ifFalse: [fieldValue := value]
  			ifTrue: [argsStream nextPutAll: ' filename="', value url pathForFile, '"', crLf, 'Content-Type: ', value contentType.
  				fieldValue := (value content
  					ifNil: [(FileStream fileNamed: value url pathForFile) contentsOfEntireFile]
  					ifNotNil: [value content]) asString].
  " Transcript show: 'field=', key, '; value=', fieldValue; cr. "
  		argsStream nextPutAll: crLf, crLf, fieldValue, crLf.
  	]].
  	argsStream nextPutAll: '--', mimeBorder, '--'.
  
  	resultStream := self
  		post: 
  			('Content-type: multipart/form-data; boundary=', mimeBorder, crLf,
  			'Content-length: ', argsStream contents size printString, crLf, crLf, 
  			argsStream contents)
  		url: url ifError: [^'Error in post ' url asString].
  	"get the header of the reply"
  	result := resultStream upToEnd.
  	^MIMEDocument content: result!

Item was changed:
  ----- Method: FileStream class>>post:target:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  post: data target: target url: url ifError: errorBlock 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self concreteStream new post: data target: target url: url ifError: errorBlock!

Item was changed:
  ----- Method: FileStream class>>post:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  post: data url: url ifError: errorBlock 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self post: data target: nil url: url ifError: errorBlock!

Item was changed:
  ----- Method: FileStream class>>requestURL:target: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURL: url target: target 
  	"FileStream requestURL:'http://isgwww.cs.uni-magdeburg.de/~raab' target: ':=blank' "
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self concreteStream new requestURL: url target: target!

Item was changed:
  ----- Method: FileStream class>>requestURLStream: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURLStream: url 
  	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self concreteStream new requestURLStream: url!

Item was changed:
  ----- Method: FileStream class>>requestURLStream:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURLStream: url ifError: errorBlock 
  	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self concreteStream new requestURLStream: url ifError: errorBlock!

Item was changed:
  ----- Method: HashedCollection>>findElementOrNil: (in category '*60Deprecated-compatibility') -----
  findElementOrNil: anObject
+ 	self deprecated: 'Use ', #scanFor:.
- 	"This method has been superseeded by #scanFor:
- 	It is here for compatibility with external packages only."
  	^self scanFor: anObject!

Item was changed:
  ----- Method: HashedCollection>>fullCheck (in category '*60Deprecated-compatibility') -----
  fullCheck
  	"This is a private method, formerly implemented in Set, that is no longer required.
  	It is here for compatibility with external packages only."
  	"Keep array at least 1/4 free for decent hash behavior"
  	
+ 	self deprecated.
  	array size * 3 < (tally * 4) ifTrue: [ self grow ]!

Item was changed:
  ----- Method: Morph>>toggleDragNDrop (in category '*60Deprecated-dropping/grabbing') -----
  toggleDragNDrop
  	"Toggle this morph's ability to add and remove morphs via drag-n-drop."
  
+ 	self deprecated.
  	self enableDragNDrop: self dragNDropEnabled not.
  !

Item was changed:
  ----- Method: PasteUpMorph>>isOpenForDragNDropString (in category '*60Deprecated-menu & halo') -----
  isOpenForDragNDropString
  	"Answer the string to be shown in a menu to represent the  
  	open-to-drag-n-drop status"
+ 	self deprecated.
  	^ (self dragNDropEnabled
  		ifTrue: ['<on>']
  		ifFalse: ['<off>'])
  		, 'open to drag & drop' translated!

Item was changed:
  ----- Method: StandardFileStream class>>isRunningAsBrowserPlugin (in category '*60Deprecated-NSPlugin-System-Support') -----
  isRunningAsBrowserPlugin 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	self new waitBrowserReadyFor: 1000 ifFail: [^false].
  	^true!

Item was changed:
  ----- Method: StandardFileStream class>>privateCheckForBrowserPrimitives (in category '*60Deprecated-NSPlugin-System-Support') -----
  privateCheckForBrowserPrimitives 
  	<primitive:'primitivePluginBrowserReady'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^false!

Item was changed:
  ----- Method: StandardFileStream>>defaultBrowserReadyWait (in category '*60Deprecated-NSPlugin-System-Support') -----
  defaultBrowserReadyWait 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^5000!

Item was changed:
  ----- Method: StandardFileStream>>post:target:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  post: data target: target url: url ifError: errorBlock 
  	"Post data to the given URL. The returned file stream contains the reply of the server.
  	If Squeak is not running in a browser evaluate errorBlock"
  
+ 	self deprecated: 'NSPlugin no longer supported'.
  	self waitBrowserReadyFor: self defaultBrowserReadyWait ifFail: [^errorBlock value].
  	Smalltalk newExternalSemaphoreDo: [ :semaphore :index |
  		| request result |
  		request := self primURLPost: url target: target data: data semaIndex: index.
  		request ifNil: [
  			Smalltalk unregisterExternalObject: semaphore.
  			^errorBlock value ].
  		[ semaphore wait. "until something happens"
  			result := self primURLRequestState: request.
  			result == nil ] whileTrue.
  		result ifTrue: [ fileID := self primURLRequestFileHandle: request ].
  		self primURLRequestDestroy: request.
  		Smalltalk unregisterExternalObject: semaphore ].
  	fileID ifNil: [ ^nil ].
  	self register.
  	name := url.
  	rwmode := false.
  	buffer1 := String new: 1.
  	self enableReadBuffering!

Item was changed:
  ----- Method: StandardFileStream>>post:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  post: data url: url ifError: errorBlock 
  
+ 	self deprecated: 'NSPlugin no longer supported'.
  	self post: data target: nil url: url ifError: errorBlock!

Item was changed:
  ----- Method: StandardFileStream>>primBrowserReady (in category '*60Deprecated-NSPlugin-System-Support') -----
  primBrowserReady 
  	<primitive:'primitivePluginBrowserReady'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil!

Item was changed:
  ----- Method: StandardFileStream>>primURLPost:data:semaIndex: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLPost: url data: contents semaIndex: index 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self primURLPost: url target: nil data: contents semaIndex: index!

Item was changed:
  ----- Method: StandardFileStream>>primURLPost:target:data:semaIndex: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLPost: url target: target data: contents semaIndex: index 
  	"Post the data (url might be 'mailto:' etc)"
  	<primitive:'primitivePluginPostURL'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil
   !

Item was changed:
  ----- Method: StandardFileStream>>primURLRequest:semaIndex: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLRequest: url semaIndex: index 
  	<primitive:'primitivePluginRequestURLStream'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil!

Item was changed:
  ----- Method: StandardFileStream>>primURLRequest:target:semaIndex: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLRequest: url target: target semaIndex: index 
  	"target - String (frame, also ':=top', ':=parent' etc)"
  	<primitive:'primitivePluginRequestURL'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil
   !

Item was changed:
  ----- Method: StandardFileStream>>primURLRequestDestroy: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLRequestDestroy: request 
  	<primitive:'primitivePluginDestroyRequest'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil!

Item was changed:
  ----- Method: StandardFileStream>>primURLRequestFileHandle: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLRequestFileHandle: request 
  	<primitive: 'primitivePluginRequestFileHandle'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^nil!

Item was changed:
  ----- Method: StandardFileStream>>primURLRequestState: (in category '*60Deprecated-NSPlugin-System-Support') -----
  primURLRequestState: request 
  	<primitive:'primitivePluginRequestState'>
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^false!

Item was changed:
  ----- Method: StandardFileStream>>requestURL:target: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURL: url target: target 
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self requestURL: url target: target ifError: [nil]!

Item was changed:
  ----- Method: StandardFileStream>>requestURL:target:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURL: url target: target ifError: errorBlock 
  	"Request to go to the target for the given URL.
  	If Squeak is not running in a browser evaluate errorBlock"
  
+ 	self deprecated: 'NSPlugin no longer supported'.
  	self waitBrowserReadyFor: self defaultBrowserReadyWait ifFail: [^errorBlock value].
  	Smalltalk newExternalSemaphoreDo: [ :semaphore :index |
  		| request result |
  		request := self primURLRequest: url target: target semaIndex: index.
  		request ifNil: [
  			Smalltalk unregisterExternalObject: semaphore.
  			^errorBlock value ].
  		[ semaphore wait. "until something happens"
  			result := self primURLRequestState: request.
  			result == nil ] whileTrue.
  		self primURLRequestDestroy: request.
  		Smalltalk unregisterExternalObject: semaphore ].
  	fileID ifNil: [ ^nil ].
  	self register.
  	name := url.
  	rwmode := false.
  	buffer1 := String new: 1.
  	self enableReadBuffering!

Item was changed:
  ----- Method: StandardFileStream>>requestURLStream: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURLStream: url 
  	"FileStream requestURLStream:'http://www.squeak.org'"
+ 	self deprecated: 'NSPlugin no longer supported'.
  	^self requestURLStream: url ifError:[nil]!

Item was changed:
  ----- Method: StandardFileStream>>requestURLStream:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
  requestURLStream: url ifError: errorBlock 
  	"Request a FileStream for the given URL.
  	If Squeak is not running in a browser evaluate errorBlock"
  	"FileStream requestURLStream:'http://www.squeak.org'"
  
+ 	self deprecated: 'NSPlugin no longer supported'.
  	self waitBrowserReadyFor: self defaultBrowserReadyWait ifFail: [^errorBlock value].
  	Smalltalk newExternalSemaphoreDo: [ :semaphore :index |
  		| request result |
  		request := self primURLRequest: url semaIndex: index.
  		request ifNil: [
  			Smalltalk unregisterExternalObject: semaphore.
  			^errorBlock value ].
  		[ semaphore wait. "until something happens"
  			result := self primURLRequestState: request.
  			result == nil ] whileTrue.
  		result ifTrue: [ fileID := self primURLRequestFileHandle: request ].
  		self primURLRequestDestroy: request.
  		Smalltalk unregisterExternalObject: semaphore ].
  	fileID ifNil: [ ^nil ].
  	self register.
  	name := url.
  	rwmode := false.
  	buffer1 := String new: 1.
  	self enableReadBuffering!

Item was changed:
  ----- Method: StandardFileStream>>waitBrowserReadyFor:ifFail: (in category '*60Deprecated-NSPlugin-System-Support') -----
  waitBrowserReadyFor: timeout ifFail: errorBlock 
  	| startTime delay okay |
+ 	self deprecated: 'NSPlugin no longer supported'.
  	okay := self primBrowserReady.
  	okay ifNil:[^errorBlock value].
  	okay ifTrue: [^true].
  	startTime := Time millisecondClockValue.
  	delay := Delay forMilliseconds: 100.
  	[(Time millisecondsSince: startTime) < timeout]
  		whileTrue: [
  			delay wait.
  			okay := self primBrowserReady.
  			okay ifNil:[^errorBlock value].
  			okay ifTrue: [^true]].
  	^errorBlock value!

Item was changed:
  ----- Method: SystemVersion class>>check:andRequestPluginUpdate: (in category '*60Deprecated-testing method dictionary') -----
  check: pluginVersion andRequestPluginUpdate: updateURL
  	"SystemVersion check: 'zzz' andRequestPluginUpdate: 'http://www.squeakland.org/installers/update.html' "
  
+ 	self deprecated.
  	"We don't have a decent versioning scheme yet, so we are basically checking for a nil VM version on the mac."
  	(self pluginVersion: pluginVersion newerThan: self currentPluginVersion)
  		ifFalse: [^true].
  	(self confirm: 'There is a newer plugin version available. Do you want to install it now?')
  		ifFalse: [^false].
  	HTTPClient
  		requestURL: updateURL , (Smalltalk platformName copyWithout: Character space) asLowercase , '.html'
  		target: '_top'.
  	^false!

Item was changed:
  ----- Method: UndefinedObject>>suspend (in category '*60Deprecated') -----
  suspend
  	"Kills off processes that didn't terminate properly"
  	"Display reverse; reverse."  "<-- So we can catch the suspend bug"
+ 	self deprecated: 'Use ', [Processor terminateActive] sourceString.
  	Processor terminateActive!



More information about the Squeak-dev mailing list