[ENH] WebBrowser Plugin API

Michael Rueger Michael.Rueger.-ND at disney.com
Wed Mar 1 23:00:33 UTC 2000


Change Set:		Plugin-requests
Date:			1 March 2000
Author:			Michael Rueger, Andreas Raab

Provides access to a set of primitives to download data through the borwser
plugin api.
This only work when Squeak is run as a plugin in a web browser.
The primitive make use of the plugin api, thus going through the browser's
cache and proxy mechanism. You should also be able to go through safe
connections (https), but that's not tested.
The public protocol:

-requestURLStream: url
-requestURLStream: url ifError: errorBlock
These calls return a stream which contains the contents of the url.
The stream should be a StandardFileStream pointing to a file in the browser's
cache.
Example:
FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'
FileStream requestURLStream:'http://www.disney.com'

-requestURL: url target: target
-requestURL: url target: target ifError: errorBlock
These calls request the browser to go to the specified url and the target
within the url's content.
This can be used to jump to a different web page from within squeak. This may
terminate the plugin in case you are actually leaving the page with the
embedded plugin.


-- 

 "To improve is to change, to be perfect is to change often." 
                                            Winston Churchill
+------------------------------------------------------------+
| Michael Rueger                                             |
| Phone: ++1 (818) 623 3283        Fax:   ++1 (818) 623 3559 |
+---------- Michael.Rueger.-ND at corp.go.com ------------------+
-------------- next part --------------
"Change Set:		Plugin-requests
Date:			1 March 2000
Author:			Michael Rueger, Andreas Raab

Provides access to a set of primitives to download data through the borwser plugin api.
This only work when Squeak is run as a plugin in a web browser.
The primitive make use of the plugin api, thus going through the browser's cache and proxy mechanism. You should also be able to go through safe connections (https), but that's not tested.
The public protocol:

-requestURLStream: url
-requestURLStream: url ifError: errorBlock
These calls return a stream which contains the contents of the url.
The stream should be a StandardFileStream pointing to a file in the browser's cache.
Example:
FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'
FileStream requestURLStream:'http://www.disney.com'

-requestURL: url target: target
-requestURL: url target: target ifError: errorBlock
These calls request the browser to go to the specified url and the target within the url's content.
This can be used to jump to a different web page from within squeak. This may terminate the plugin in case you are actually leaving the page with the embedded plugin.

"!
!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 1/11/2000 10:44'!
defaultBrowserReadyWait
	^5000! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 1/11/2000 10:38'!
primBrowserReady
	<primitive:'primitivePluginBrowserReady'>
	self primitiveFailed! !

!StandardFileStream methodsFor: 'browser requests'!
primURLRequest: url semaIndex: index
	<primitive:'primitivePluginRequestURLStream'>
	^nil! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 2/29/2000 11:22'!
primURLRequest: url target: target semaIndex: index
	"target - String (frame, also '_top', '_parent' etc)"
	<primitive:'primitivePluginRequestURL'>
	^nil
 ! !

!StandardFileStream methodsFor: 'browser requests'!
primURLRequestDestroy: request
	<primitive:'primitivePluginDestroyRequest'>
	^nil! !

!StandardFileStream methodsFor: 'browser requests'!
primURLRequestFileHandle: request
	<primitive: 'primitivePluginRequestFileHandle'>
	^nil! !

!StandardFileStream methodsFor: 'browser requests'!
primURLRequestState: request
	<primitive:'primitivePluginRequestState'>
	^false! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 2/29/2000 11:22'!
requestURL: url target: target
	^self requestURL: url target: target ifError: [nil]! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 2/29/2000 11:24'!
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"

	| sema index request result |
	self waitBrowserReadyFor: self defaultBrowserReadyWait ifFail: [^errorBlock value].
	sema _ Semaphore new.
	index _ Smalltalk registerExternalObject: sema.
	request _ self primURLRequest: url target: target semaIndex: index.
	request == nil ifTrue:[
	
	Smalltalk unregisterExternalObject: sema.
		^errorBlock value.
	] ifFalse:[
		[sema wait. "until something happens"
		result _ self primURLRequestState: request.
		result == nil] whileTrue.
		self primURLRequestDestroy: request.
	].
	Smalltalk unregisterExternalObject: sema.
	fileID == nil ifTrue:[^nil].
	self register.
	name _ url.
	rwmode _ false.
	buffer1 _ String new: 1.! !

!StandardFileStream methodsFor: 'browser requests'!
requestURLStream: url
	"FileStream requestURLStream:'http://www.squeak.org'"
	^self requestURLStream: url ifError:[nil]! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 1/11/2000 10:43'!
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'"
	| sema index request result |
	self waitBrowserReadyFor: self defaultBrowserReadyWait ifFail: [^errorBlock value].
	sema _ Semaphore new.
	index _ Smalltalk registerExternalObject: sema.
	request _ self primURLRequest: url semaIndex: index.
	request == nil ifTrue:[
	
	Smalltalk unregisterExternalObject: sema.
		^errorBlock value.
	] ifFalse:[
		[sema wait. "until something happens"
		result _ self primURLRequestState: request.
		result == nil] whileTrue.
		result ifTrue:[fileID _ self primURLRequestFileHandle: request].
		self primURLRequestDestroy: request.
	].
	Smalltalk unregisterExternalObject: sema.
	fileID == nil ifTrue:[^nil].
	self register.
	name _ url.
	rwmode _ false.
	buffer1 _ String new: 1.! !

!StandardFileStream methodsFor: 'browser requests' stamp: 'mir 1/11/2000 10:55'!
waitBrowserReadyFor: timeout ifFail: errorBlock
	| startTime delay |
	self primBrowserReady
		ifTrue: [^true].
	startTime _ Time millisecondClockValue.
	delay _ Delay forMilliseconds: 100.
	[(Time millisecondsSince: startTime) < timeout]
		whileTrue: [
			delay wait.
			self primBrowserReady
				ifTrue: [^true]].
	^errorBlock value! !


!FileStream class methodsFor: 'browser requests'!
requestURLStream: url
	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
	^self concreteStream new requestURLStream: url! !

!FileStream class methodsFor: 'browser requests'!
requestURLStream: url ifError: errorBlock
	"FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'"
	^self concreteStream new requestURLStream: url ifError: errorBlock! !


More information about the Squeak-dev mailing list