[Vm-dev] [commit][3421] Add Squeak V5 sources

commits at squeakvm.org commits at squeakvm.org
Wed Aug 12 00:09:25 UTC 2015


Revision: 3421
Author:   eliot
Date:     2015-08-11 17:09:24 -0700 (Tue, 11 Aug 2015)
Log Message:
-----------
Add Squeak V5 sources

Added Paths:
-----------
    branches/Cog/sources/SqueakV50.sources

Added: branches/Cog/sources/SqueakV50.sources
===================================================================
--- branches/Cog/sources/SqueakV50.sources	                        (rev 0)
+++ branches/Cog/sources/SqueakV50.sources	2015-08-12 00:09:24 UTC (rev 3421)
@@ -0,0 +1,941973 @@
+'From Squeak5.0 of 20 July 2015 [latest update: #15110] on 20 July 2015 at 4:13:52 pm'!
+Error subclass: #CRCError
+	instanceVariableNames: ''
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'Compression-Streams'!
+
+!CRCError methodsFor: 'as yet unclassified' stamp: 'nk 3/7/2004 15:56'!
+isResumable
+	^true! !
+BorderedMorph subclass: #BorderedSubpaneDividerMorph
+	instanceVariableNames: 'resizingEdge'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'Morphic-Windows'!
+
+!BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+firstEnter: evt
+	"The first time this divider is activated, find its window and redirect further interaction there."
+	| window |
+
+	window := self firstOwnerSuchThat: [:m | m respondsTo: #secondaryPaneTransition:divider:].
+	window ifNil: [ self suspendEventHandler. ^ self ]. "not working out"
+	window secondaryPaneTransition: evt divider: self.
+	self on: #mouseEnter send: #secondaryPaneTransition:divider: to: window.
+! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+horizontal
+
+	self hResizing: #spaceFill.! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+resizingEdge
+
+	^resizingEdge
+! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+resizingEdge: edgeSymbol
+
+	(#(top bottom) includes: edgeSymbol) ifFalse:
+		[ self error: 'resizingEdge must be #top or #bottom' ].
+	resizingEdge := edgeSymbol.
+	self on: #mouseEnter send: #firstEnter: to: self.
+! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+vertical
+
+	self vResizing: #spaceFill.! !
+
+
+!BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'!
+defaultBorderWidth
+"answer the default border width for the receiver"
+	^ 0! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'!
+defaultColor
+"answer the default color/fill style for the receiver"
+	^ Color black! !
+
+!BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'!
+initialize
+	"initialize the state of the receiver"
+	super initialize.
+""
+	self extent: 1 @ 1! !
+
+"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
+
+BorderedSubpaneDividerMorph class
+	instanceVariableNames: ''!
+
+!BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'!
+forBottomEdge
+	^self new horizontal resizingEdge: #bottom! !
+
+!BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'!
+forTopEdge
+	^self new horizontal resizingEdge: #top! !
+
+!BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'!
+horizontal
+	^self new horizontal! !
+
+!BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'!
+vertical
+	^self new vertical! !
+Object subclass: #PostscriptDummyWarp
+	instanceVariableNames: 'canvas subCanvas transform'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'MorphicExtras-Postscript Canvases'!
+!PostscriptDummyWarp commentStamp: '<historical>' prior: 0!
+I simulate the effects of having a WarpBlit done in Postscript, by simply adjusting the coordinate system.
+!
+
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+canvas
+	^canvas
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:19'!
+canvas:newCanvas
+	canvas _ newCanvas.
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:19' prior: 16780638!
+canvas:newCanvas
+	canvas := newCanvas.
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+cellSize:newCellSize
+	^self.! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:09'!
+colorMap:aMap
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+combinationRule:newRule
+	^self.! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:12'!
+drawPostscriptContext:aCanvas
+	canvas drawPostscriptContext:aCanvas.
+
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'di 8/12/2000 10:01'!
+preserveStateDuring: aBlock
+
+	^ canvas preserveStateDuring:
+		"Note block arg must be self so various things get overridden properly"
+		[:inner | aBlock value: self]
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+sourceForm:newForm
+	^self.! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:10'!
+sourceQuad:aQuad destRect:aRect
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/10/1930 21:02'!
+subCanvas:patchRect
+	subCanvas ifNil:
+		[ subCanvas _ PostscriptCanvas new reset setOrigin:patchRect topLeft clipRect:(-10000 at -10000 extent:20000 at 20000)].
+	^subCanvas.
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/10/1930 21:02' prior: 16781692!
+subCanvas:patchRect
+	subCanvas ifNil:
+		[ subCanvas := PostscriptCanvas new reset setOrigin:patchRect topLeft clipRect:(-10000 at -10000 extent:20000 at 20000)].
+	^subCanvas.
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'nice 12/29/2010 14:58' prior: 16781953!
+subCanvas:patchRect
+	subCanvas ifNil:
+		[ subCanvas := PostscriptCanvas new reset setOrigin:patchRect topLeft clipRect: (-10000 @ -10000 extent: 20000 @ 20000)].
+	^subCanvas.
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+transform
+	^transform.
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy'!
+transform:newTransform
+	transform _ newTransform.
+	^self.
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' prior: 16782510!
+transform:newTransform
+	transform := newTransform.
+	^self.
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'mpw 8/4/1930 09:11'!
+transformBy:aTransform
+	canvas transformBy:aTransform.
+
+
+! !
+
+!PostscriptDummyWarp methodsFor: 'dummy' stamp: 'di 8/12/2000 10:13'!
+warpBits
+	canvas preserveStateDuring:
+		[:inner | 
+		transform ifNotNil: [inner transformBy: transform].
+		inner drawPostscriptContext:subCanvas].
+! !
+
+"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
+
+PostscriptDummyWarp class
+	instanceVariableNames: ''!
+
+!PostscriptDummyWarp class methodsFor: 'as yet unclassified' stamp: 'mpw 8/4/1930 09:18'!
+canvas:aCanvas
+	^self new canvas:aCanvas.! !
+SimpleButtonMorph subclass: #SimpleSwitchMorph
+	instanceVariableNames: 'onColor offColor'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'MorphicExtras-Widgets'!
+!SimpleSwitchMorph commentStamp: 'apb 5/3/2006 16:04' prior: 0!
+I represent a switch that can be either on or off.  I chnage my state in response to a mouse click.  When clicked, I also send my actionSelector to my target, just like a SimpleButtonMorph.!
+
+
+!SimpleSwitchMorph methodsFor: 'button' stamp: 'dgd 2/22/2003 18:40'!
+doButtonAction
+	"Perform the action of this button. The last argument of the message sent to the target is the new state of this switch."
+
+	| newState |
+	(target notNil and: [actionSelector notNil]) 
+		ifTrue: 
+			[newState := color = onColor.
+			target perform: actionSelector
+				withArguments: (arguments copyWith: newState)]! !
+
+
+!SimpleSwitchMorph methodsFor: 'copying' stamp: 'jm 1/29/98 16:15'!
+updateReferencesUsing: aDictionary
+	"Copy and update references in the arguments array during copying."
+
+	super updateReferencesUsing: aDictionary.
+	arguments _ arguments collect:
+		[:old | aDictionary at: old ifAbsent: [old]].
+! !
+
+!SimpleSwitchMorph methodsFor: 'copying' stamp: 'jm 1/29/98 16:15' prior: 16784199!
+updateReferencesUsing: aDictionary
+	"Copy and update references in the arguments array during copying."
+
+	super updateReferencesUsing: aDictionary.
+	arguments := arguments collect:
+		[:old | aDictionary at: old ifAbsent: [old]].
+! !
+
+
+!SimpleSwitchMorph methodsFor: 'event handling' stamp: 'ar 6/4/2001 00:39'!
+mouseDown: evt
+
+	oldColor _ self fillStyle.! !
+
+!SimpleSwitchMorph methodsFor: 'event handling' stamp: 'ar 6/4/2001 00:39' prior: 16784827!
+mouseDown: evt
+
+	oldColor := self fillStyle.! !
+
+!SimpleSwitchMorph methodsFor: 'event handling' stamp: 'jm 1/30/98 13:55'!
+mouseMove: evt
+
+	(self containsPoint: evt cursorPoint)
+		ifTrue: [self setSwitchState: (oldColor = offColor)]
+		ifFalse: [self setSwitchState: (oldColor = onColor)].
+! !
+
+!SimpleSwitchMorph methodsFor: 'event handling' stamp: 'jm 1/30/98 13:58'!
+mouseUp: evt
+
+	(self containsPoint: evt cursorPoint)
+		ifTrue: [  "toggle and do action"
+			self setSwitchState: (oldColor = offColor).
+			self doButtonAction]
+		ifFalse: [  "restore old appearance"
+			self setSwitchState: (oldColor = onColor)].
+! !
+
+
+!SimpleSwitchMorph methodsFor: 'initialization' stamp: 'di 6/5/2000 08:44'!
+initialize
+
+	^ self initializeWithLabel: 'Toggle'
+! !
+
+!SimpleSwitchMorph methodsFor: 'initialization' stamp: 'apb 5/3/2006 15:51'!
+initializeWithLabel: labelString
+
+	super initializeWithLabel: labelString.
+	self borderWidth: 3.
+	self extent: self extent + 2.
+	onColor := Color r: 1.0 g: 0.6 b: 0.6.
+	offColor := Color lightGray.
+	color := offColor
+! !
+
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 15:45'!
+isOff
+	^ color ~= onColor! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 15:45'!
+isOn
+	^ color = onColor! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18'!
+offColor
+
+	^ offColor
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18'!
+offColor: aColor
+
+	offColor _ aColor.
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18' prior: 16786389!
+offColor: aColor
+
+	offColor := aColor.
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18'!
+onColor
+
+	^ onColor
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18'!
+onColor: aColor
+
+	onColor _ aColor.
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'jm 1/29/98 20:18' prior: 16786727!
+onColor: aColor
+
+	onColor := aColor.
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 15:46'!
+setSwitchState: aBoolean
+
+	aBoolean
+		ifTrue: [self turnOn]
+		ifFalse: [self turnOff].
+! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 16:11'!
+toggleState
+	self isOn
+		ifTrue: [self turnOff]
+		ifFalse: [self turnOn]! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 15:44'!
+turnOff
+	self borderColor: #raised.
+	self color: offColor! !
+
+!SimpleSwitchMorph methodsFor: 'switching' stamp: 'apb 5/3/2006 15:44'!
+turnOn
+	self borderColor: #inset.
+	self color: onColor! !
+Object subclass: #UPolicyResponse
+	instanceVariableNames: 'allowed reason'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'Universes-Policy'!
+!UPolicyResponse commentStamp: '<historical>' prior: 0!
+A response to a policy query.!
+
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:56'!
+allowed
+	^allowed! !
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:56'!
+allowed: anObject
+	allowed _ anObject! !
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:56' prior: 16787876!
+allowed: anObject
+	allowed := anObject! !
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:58'!
+reason
+	^reason! !
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:56'!
+reason: anObject
+	reason _ anObject! !
+
+!UPolicyResponse methodsFor: 'accessing' stamp: 'ls 7/29/2004 17:56' prior: 16788207!
+reason: anObject
+	reason := anObject! !
+
+"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
+
+UPolicyResponse class
+	instanceVariableNames: ''!
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/29/2004 16:47'!
+allowed
+	^self allowed: nil! !
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/30/2004 10:34'!
+allowed: reason
+	^self allowed: true  reason: reason! !
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/29/2004 16:46'!
+allowed: aBoolean  reason: aReason
+	^self basicNew
+		allowed: aBoolean;
+		reason: (aReason ifNil: ['no reason given']);
+		yourself! !
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/29/2004 16:46'!
+denied
+	^self denied: nil! !
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/29/2004 17:58'!
+denied: reason
+	^self allowed: false  reason: reason! !
+
+!UPolicyResponse class methodsFor: 'instance creation' stamp: 'ls 7/29/2004 16:47'!
+new
+	self shouldNotImplement ! !
+Object subclass: #HTTPClient
+	instanceVariableNames: ''
+	classVariableNames: 'BrowserSupportsAPI RunningInBrowser'
+	poolDictionaries: ''
+	category: 'System-Support'!
+
+"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
+
+HTTPClient class
+	instanceVariableNames: ''!
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 4/2/2002 15:37'!
+browserSupportsAPI
+	^BrowserSupportsAPI == true! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 4/2/2002 15:37' prior: 16789686!
+browserSupportsAPI
+	^BrowserSupportsAPI == true! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 4/2/2002 15:36'!
+browserSupportsAPI: aBoolean
+	BrowserSupportsAPI _ aBoolean! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 4/2/2002 15:36' prior: 16789970!
+browserSupportsAPI: aBoolean
+	BrowserSupportsAPI := aBoolean! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 4/2/2002 15:36' prior: 16790132!
+browserSupportsAPI: aBoolean
+	BrowserSupportsAPI := aBoolean! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 2/2/2001 17:27'!
+determineIfRunningInBrowser
+	"HTTPClient determineIfRunningInBrowser"
+
+	RunningInBrowser _ StandardFileStream isRunningAsBrowserPlugin
+! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 2/2/2001 17:27' prior: 16790442!
+determineIfRunningInBrowser
+	"HTTPClient determineIfRunningInBrowser"
+
+	RunningInBrowser := StandardFileStream isRunningAsBrowserPlugin
+! !
+
+!HTTPClient class methodsFor: 'class initialization' stamp: 'mir 2/2/2001 17:27' prior: 16790680!
+determineIfRunningInBrowser
+	"HTTPClient determineIfRunningInBrowser"
+
+	RunningInBrowser := StandardFileStream isRunningAsBrowserPlugin
+! !
+
+
+!HTTPClient class methodsFor: 'examples' stamp: 'mir 2/2/2001 17:43'!
+exampleMailTo
+	"HTTPClient exampleMailTo"
+
+	HTTPClient mailTo: 'm.rueger at acm.org' message: 'A test message from within Squeak'
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'mir 2/2/2001 17:43' prior: 16791131!
+exampleMailTo
+	"HTTPClient exampleMailTo"
+
+	HTTPClient mailTo: 'm.rueger at acm.org' message: 'A test message from within Squeak'
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'md 7/28/2005 10:33'!
+examplePostArgs
+	"HTTPClient examplePostArgs"
+
+	| args result |
+	args := Dictionary new.
+	args
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result := HTTPClient httpPostDocument: 'http://www.squeaklet.com/cgi-bin/thrd.pl [^]' args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'ul 1/11/2010 07:17' prior: 16791551!
+examplePostArgs
+	"HTTPClient examplePostArgs"
+
+	| args result |
+	args := Dictionary new
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result := HTTPClient httpPostDocument: 'http://www.squeaklet.com/cgi-bin/thrd.pl [^]' args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'ul 1/11/2010 07:17' prior: 16791949!
+examplePostArgs
+	"HTTPClient examplePostArgs"
+
+	| args result |
+	args := Dictionary new
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result := HTTPClient httpPostDocument: 'http://www.squeaklet.com/cgi-bin/thrd.pl [^]' args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'mir 2/2/2001 17:44'!
+examplePostMultipart
+	"HTTPClient examplePostMultipart"
+
+	| args result |
+	args _ Dictionary new.
+	args
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result _ HTTPClient httpPostMultipart: 'http://www.squeaklet.com/cgi-bin/thrd.pl'  args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'ul 1/11/2010 07:17' prior: 16792715!
+examplePostMultipart
+	"HTTPClient examplePostMultipart"
+
+	| args result |
+	args := Dictionary new
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result := HTTPClient httpPostMultipart: 'http://www.squeaklet.com/cgi-bin/thrd.pl'  args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+!HTTPClient class methodsFor: 'examples' stamp: 'ul 1/11/2010 07:17' prior: 16793119!
+examplePostMultipart
+	"HTTPClient examplePostMultipart"
+
+	| args result |
+	args := Dictionary new
+		at: 'arg1' put: #('val1');
+		at: 'arg2' put: #('val2');
+		yourself.
+	result := HTTPClient httpPostMultipart: 'http://www.squeaklet.com/cgi-bin/thrd.pl'  args: args.
+	Transcript show: result content; cr; cr.
+
+! !
+
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'nk 8/30/2004 07:50'!
+httpGet: url
+	| document |
+	document _ self httpGetDocument: url.
+	^(document isString)
+		ifTrue: [
+			"strings indicate errors"
+			document]
+		ifFalse: [(RWBinaryOrTextStream with: document content) reset]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'nk 8/30/2004 07:50' prior: 16793902!
+httpGet: url
+	| document |
+	document := self httpGetDocument: url.
+	^(document isString)
+		ifTrue: [
+			"strings indicate errors"
+			document]
+		ifFalse: [(RWBinaryOrTextStream with: document content) reset]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'nk 8/30/2004 07:50' prior: 16794199!
+httpGet: url
+	| document |
+	document := self httpGetDocument: url.
+	^(document isString)
+		ifTrue: [
+			"strings indicate errors"
+			document]
+		ifFalse: [(RWBinaryOrTextStream with: document content) reset]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/11/2001 12:55'!
+httpGetDocument: url
+	| stream content | 
+	^self shouldUsePluginAPI
+		ifTrue: [
+			stream _ FileStream requestURLStream: url ifError: [self error: 'Error in get from ' , url printString].
+			stream ifNil: [^''].
+			stream position: 0.
+			content _ stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpGetDocument: url]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/11/2001 12:55' prior: 16794780!
+httpGetDocument: url
+	| stream content | 
+	^self shouldUsePluginAPI
+		ifTrue: [
+			stream := FileStream requestURLStream: url ifError: [self error: 'Error in get from ' , url printString].
+			stream ifNil: [^''].
+			stream position: 0.
+			content := stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpGetDocument: url]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/11/2001 12:55' prior: 16795231!
+httpGetDocument: url
+	| stream content | 
+	^self shouldUsePluginAPI
+		ifTrue: [
+			stream := FileStream requestURLStream: url ifError: [self error: 'Error in get from ' , url printString].
+			stream ifNil: [^''].
+			stream position: 0.
+			content := stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpGetDocument: url]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 15:04'!
+httpPostDocument: url args: argsDict
+	^self httpPostDocument: url target: nil args: argsDict! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 15:04' prior: 16796120!
+httpPostDocument: url args: argsDict
+	^self httpPostDocument: url target: nil args: argsDict! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 15:06'!
+httpPostDocument: url target: target args: argsDict
+	| argString stream content |
+	^self shouldUsePluginAPI
+		ifTrue: [
+			argString _ argsDict
+				ifNotNil: [argString _ HTTPSocket argString: argsDict]
+				ifNil: [''].
+			stream _ FileStream post: argString , ' ' target: target url: url , argString ifError: [self error: 'Error in post to ' , url printString].
+			stream position: 0.
+			content _ stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpPostDocument: url  args: argsDict]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 15:06' prior: 16796470!
+httpPostDocument: url target: target args: argsDict
+	| argString stream content |
+	^self shouldUsePluginAPI
+		ifTrue: [
+			argString := argsDict
+				ifNotNil: [argString := HTTPSocket argString: argsDict]
+				ifNil: [''].
+			stream := FileStream post: argString , ' ' target: target url: url , argString ifError: [self error: 'Error in post to ' , url printString].
+			stream position: 0.
+			content := stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpPostDocument: url  args: argsDict]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 15:06' prior: 16797088!
+httpPostDocument: url target: target args: argsDict
+	| argString stream content |
+	^self shouldUsePluginAPI
+		ifTrue: [
+			argString := argsDict
+				ifNotNil: [argString := HTTPSocket argString: argsDict]
+				ifNil: [''].
+			stream := FileStream post: argString , ' ' target: target url: url , argString ifError: [self error: 'Error in post to ' , url printString].
+			stream position: 0.
+			content := stream upToEnd.
+			stream close.
+			MIMEDocument content: content]
+		ifFalse: [HTTPSocket httpPostDocument: url  args: argsDict]! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 12:51'!
+httpPostMultipart: url args: argsDict
+	" do multipart/form-data encoding rather than x-www-urlencoded "
+
+	^self shouldUsePluginAPI
+		ifTrue: [self pluginHttpPostMultipart: url args: argsDict]
+		ifFalse: [HTTPSocket httpPostMultipart: url args: argsDict accept: nil request: '']! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 5/1/2001 12:51' prior: 16798316!
+httpPostMultipart: url args: argsDict
+	" do multipart/form-data encoding rather than x-www-urlencoded "
+
+	^self shouldUsePluginAPI
+		ifTrue: [self pluginHttpPostMultipart: url args: argsDict]
+		ifFalse: [HTTPSocket httpPostMultipart: url args: argsDict accept: nil request: '']! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 4/2/2002 15:52'!
+requestURL: url target: target
+	^self shouldUsePluginAPI
+		ifTrue: [FileStream requestURL: url target: target]
+		ifFalse: [self error: 'Requesting a new URL target is not supported.']! !
+
+!HTTPClient class methodsFor: 'post/get' stamp: 'mir 4/2/2002 15:52' prior: 16799036!
+requestURL: url target: target
+	^self shouldUsePluginAPI
+		ifTrue: [FileStream requestURL: url target: target]
+		ifFalse: [self error: 'Requesting a new URL target is not supported.']! !
+
+
+!HTTPClient class methodsFor: 'testing' stamp: 'ccn 3/14/2001 19:56'!
+isRunningInBrowser
+
+	RunningInBrowser isNil
+		ifTrue: [self determineIfRunningInBrowser].
+	^RunningInBrowser! !
+
+!HTTPClient class methodsFor: 'testing' stamp: 'ccn 3/14/2001 19:56' prior: 16799569!
+isRunningInBrowser
+
+	RunningInBrowser isNil
+		ifTrue: [self determineIfRunningInBrowser].
+	^RunningInBrowser! !
+
+!HTTPClient class methodsFor: 'testing' stamp: 'mir 8/4/2003 13:44'!
+isRunningInBrowser: aBoolean
+	"Override the automatic process.
+	This should be used with caution.
+	One way to determine it without using the primitive is to check for parameters typically only encountered when running as a plugin."
+

@@ Diff output truncated at 50000 characters. @@


More information about the Vm-dev mailing list