The Trunk: 60Deprecated-pre.35.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: 60Deprecated-pre.35.mcz

commits-2
Patrick Rein uploaded a new version of 60Deprecated to project The Trunk:
http://source.squeak.org/trunk/60Deprecated-pre.35.mcz

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

Name: 60Deprecated-pre.35
Author: pre
Time: 9 May 2019, 4:35:21.000225 pm
UUID: 64cb9104-c19b-d546-8cf5-f41d1da8fe8c
Ancestors: 60Deprecated-nice.34

Deprecates classes and methods related to executing Squeak in a web browser through a browser plugin. They can be loaded through the 60Deprecated-NSPlugin-System-Support package.

=============== Diff against 60Deprecated-nice.34 ===============

Item was changed:
  SystemOrganization addCategory: #'60Deprecated-Collections-Streams'!
  SystemOrganization addCategory: #'60Deprecated-Kernel-Methods'!
+ SystemOrganization addCategory: #'60Deprecated-NSPlugin-System-Support'!
  SystemOrganization addCategory: #'60Deprecated-System-Support'!
  SystemOrganization addCategory: #'60Deprecated-Tools-Inspector'!
  SystemOrganization addCategory: #'60Deprecated-Tools-Menus'!

Item was added:
+ ----- Method: FileStream class>>httpPostDocument:args: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ httpPostDocument: url args: argsDict
+ | argString |
+ self deprecated: 'Browser plugin based http requests are not supported anymore.'.
+ argString := argsDict
+ ifNotNil: [argString := HTTPSocket argString: argsDict]
+ ifNil: [''].
+ ^self post: argString url: url , argString ifError: [self halt]!

Item was added:
+ ----- 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 "
+
+ 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 added:
+ ----- Method: FileStream class>>post:target:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ post: data target: target url: url ifError: errorBlock
+ ^self concreteStream new post: data target: target url: url ifError: errorBlock!

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

Item was added:
+ ----- 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 concreteStream new requestURL: url target: target!

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

Item was added:
+ ----- 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 concreteStream new requestURLStream: url ifError: errorBlock!

Item was added:
+ HTTPDownloadRequest subclass: #PluginHTTPDownloadRequest
+ instanceVariableNames: 'fileStream'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: '60Deprecated-NSPlugin-System-Support'!
+
+ !PluginHTTPDownloadRequest commentStamp: '<historical>' prior: 0!
+ HTTPBrowserRequest attempts to fetch the contents through a Webbrowser. This works transparently if Squeak is not running in the browser.!

Item was added:
+ ----- Method: PluginHTTPDownloadRequest>>contentStream (in category 'accessing') -----
+ contentStream
+ semaphore wait.
+ fileStream
+ ifNotNil: [^ fileStream].
+ ^ content
+ ifNotNil: [content isString
+ ifTrue: [self error: 'Error loading ' , self url printString]
+ ifFalse: [content contentStream]]!

Item was added:
+ ----- Method: PluginHTTPDownloadRequest>>contents (in category 'accessing') -----
+ contents
+ | |
+ semaphore wait.
+ (content isNil and:[fileStream notNil]) ifTrue:[
+ " pos := fileStream position."
+ fileStream position: 0.
+ content := MIMEDocument content: fileStream upToEnd.
+ fileStream close.
+ ].
+ ^content!

Item was added:
+ ----- Method: PluginHTTPDownloadRequest>>maxAttempts (in category 'accessing') -----
+ maxAttempts
+ "Return the number of attempts to retry before giving up"
+ ^3!

Item was added:
+ ----- Method: PluginHTTPDownloadRequest>>signalAbort (in category 'accessing') -----
+ signalAbort
+ fileStream ifNotNil: [
+ fileStream close].
+ fileStream := nil.
+ super signalAbort.!

Item was added:
+ ----- Method: PluginHTTPDownloadRequest>>startRetrieval (in category 'accessing') -----
+ startRetrieval
+ | attempts |
+ attempts := self maxAttempts.
+ "Note: Only the first request may fail due to not running in a browser"
+ url first = $/
+ ifTrue: [url := url copyFrom: 2 to: url size].
+ fileStream := FileStream requestURLStream: url ifError:[^super startRetrieval].
+ [fileStream == nil] whileTrue:[
+ attempts := attempts - 1.
+ attempts = 0 ifTrue:[^self content:'Error downloading file'].
+ fileStream := FileStream requestURLStream: url].
+ semaphore signal.!

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

Item was added:
+ ----- Method: StandardFileStream class>>privateCheckForBrowserPrimitives (in category '*60Deprecated-NSPlugin-System-Support') -----
+ privateCheckForBrowserPrimitives
+ <primitive:'primitivePluginBrowserReady'>
+ ^false!

Item was added:
+ ----- Method: StandardFileStream>>defaultBrowserReadyWait (in category '*60Deprecated-NSPlugin-System-Support') -----
+ defaultBrowserReadyWait
+ ^5000!

Item was added:
+ ----- 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 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 added:
+ ----- Method: StandardFileStream>>post:url:ifError: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ post: data url: url ifError: errorBlock
+
+ self post: data target: nil url: url ifError: errorBlock!

Item was added:
+ ----- Method: StandardFileStream>>primBrowserReady (in category '*60Deprecated-NSPlugin-System-Support') -----
+ primBrowserReady
+ <primitive:'primitivePluginBrowserReady'>
+ ^nil!

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

Item was added:
+ ----- 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'>
+ ^nil
+  !

Item was added:
+ ----- Method: StandardFileStream>>primURLRequest:semaIndex: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ primURLRequest: url semaIndex: index
+ <primitive:'primitivePluginRequestURLStream'>
+ ^nil!

Item was added:
+ ----- 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'>
+ ^nil
+  !

Item was added:
+ ----- Method: StandardFileStream>>primURLRequestDestroy: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ primURLRequestDestroy: request
+ <primitive:'primitivePluginDestroyRequest'>
+ ^nil!

Item was added:
+ ----- Method: StandardFileStream>>primURLRequestFileHandle: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ primURLRequestFileHandle: request
+ <primitive: 'primitivePluginRequestFileHandle'>
+ ^nil!

Item was added:
+ ----- Method: StandardFileStream>>primURLRequestState: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ primURLRequestState: request
+ <primitive:'primitivePluginRequestState'>
+ ^false!

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

Item was added:
+ ----- 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 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 added:
+ ----- Method: StandardFileStream>>requestURLStream: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ requestURLStream: url
+ "FileStream requestURLStream:'http://www.squeak.org'"
+ ^self requestURLStream: url ifError:[nil]!

Item was added:
+ ----- 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 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 added:
+ ----- Method: StandardFileStream>>waitBrowserReadyFor:ifFail: (in category '*60Deprecated-NSPlugin-System-Support') -----
+ waitBrowserReadyFor: timeout ifFail: errorBlock
+ | startTime delay okay |
+ 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!