Scamper broken?

Aibek Musaev abbey at cc.gatech.edu
Mon Apr 19 18:14:53 UTC 1999


Kevin,

I have a quick hack for this bug. Also, some patch for Back/Forward in
Scamper. Here's the preamble from the attached ChangeSet:

"Change Set:		ScamperHistory
Date:			18 April 1999
Author:			Aibek Musaev

This Change Set:
	-- adds Back/Forward capabilities to Scamper. Right-click in the
text area in Scamper.
	-- makes Scamper consistent with the new policy introduced by Dan,
namely numbers no longer respond with size 0. So, right-click in the text
area should work.

Note:
	-- introduced changes are surrounded by 'CHANGES!!!' and 'end of
CHANGES!!!' sequences
	-- there are other problems with Scamper that still exist. Feel
free to contribute with fixes, bug reports, etc.

Things to explore:
	-- Once a page is processed, there is no need to format it again.
Hence, it might be a good (cool!) idea to store formatted pages and
display them immediately upon request. One issue that may come up is
memory consumption. Easy solution - store only the last, say, 20 pages."

Enjoy,
Aibek.

On Mon, 19 Apr 1999, Kevin Fisher wrote:

> Hi all:
> 
> I've been a bit 'out of' the squeak scene for a bit...last night I picked
> up the latest Linux VM and applied all the updates.
> 
> When I call up Scamper, I can enter URL's just fine in the middle field
> of the window.  However, when I try and call up the menu associated with
> the browser display, I get a debug dialog popping up complaining about an
> error in Array>> ... 
> 
> Is this a known bug with Scamper?
> 
> (sorry if my details are a bit vague...I'm typing all this in from
> memory).
> 
> 

Content-Type: TEXT/PLAIN; charset=US-ASCII; name="ScamperHistory.18Apr254pm.cs"
Content-ID: <Pine.SUN.3.96.990419141453.6276C at felix.cc.gatech.edu>
Content-Description: 

'From Squeak 2.3 of January 14, 1999 on 18 April 1999 at 2:54:41 pm'!
"Change Set:		ScamperHistory
Date:			18 April 1999
Author:			Aibek Musaev

This Change Set:
	-- adds Back/Forward capabilities to Scamper. Right-click in the text area in Scamper.
	-- makes Scamper consistent with the new policy introduced by Dan, namely numbers no longer respond with size 0. So, right-click in the text area should work.

Note:
	-- introduced changes are surrounded by 'CHANGES!!!!!!' and 'end of CHANGES!!!!!!' sequences
	-- there are other problems with Scamper that still exist. Feel free to contribute with fixes, bug reports, etc.

Things to explore:
	-- Once a page is processed, there is no need to format it again. Hence, it might be a good (cool!!) idea to store formatted pages and display them immediately upon request. One issue that may come up is memory consumption. Easy solution - store only the last, say, 20 pages."!

Model subclass: #Scamper
	instanceVariableNames: 'status currentUrl pageSource document formattedPage downloadingProcess documentQueue recentDocuments currentAnchorLocation currentUrlIndex '
	classVariableNames: 'StartUrl '
	poolDictionaries: ''
	category: 'Interface-Web Browser'!

!Scamper methodsFor: 'menus' stamp: 'AM 4/18/1999 14:27'!
back
	"this method is added to Scamper: Aibek 4/18/99"
	currentUrlIndex > 1
		ifTrue: [
			currentUrlIndex _ currentUrlIndex - 1.
			self displayDocument: (recentDocuments at: currentUrlIndex).
		]
		ifFalse: [^ self].
! !

!Scamper methodsFor: 'menus' stamp: 'AM 4/18/1999 14:28'!
forward
	"this method is added to Scamper: Aibek 4/18/99"
	currentUrlIndex >= recentDocuments size
		ifTrue: [^self]
		ifFalse: [
			currentUrlIndex _ currentUrlIndex + 1.
			self displayDocument: (recentDocuments at: currentUrlIndex).
		]
! !

!Scamper methodsFor: 'menus' stamp: 'AM 4/18/1999 14:30'!
menu: menu  shifted: shifted
	| lines selections linePositions |
	"added 'back' and 'forward' menu options: Aibek 4/18/99"
	lines _ 'back
forward
new URL
history
view source
inspect parse tree
go to start page
edit start page'.
	linePositions _ #(2 4 6).
	selections _ #(back forward jumpToNewUrl displayHistory viewSource inspectParseTree visitStartPage editStartPage ).

	downloadingProcess ifNotNil: [ 
		lines _ lines, String cr, 'stop downloading'.
		linePositions _ linePositions, selections size asOrderedCollection.
		selections _ selections, #(stopEverything) ].

	menu labels: lines lines: linePositions selections: selections.
	^menu.! !

!Scamper methodsFor: 'changing page' stamp: 'AM 4/18/1999 13:58'!
jumpToAbsoluteUrl: urlText
	"start downloading a new page.  The page source is downloaded in a background thread"
	|  newUrl newSource |

	self stopEverything.

	"get the new url"
	newUrl _ urlText asUrl.


	"if it fundamentally doesn't fit the pages-and-contents model used internally, spawn off an external viewer for it"
	newUrl hasContents ifFalse: [ newUrl activate.  ^true ].

	"fork a Process to do the actual downloading, parsing, and formatting.  It's results will be picked up in #step"
	self status: 'downloading ', newUrl toText, '...'.

	downloadingProcess _ [ 
	  	newSource _ [ newUrl retrieveContentsForBrowser: self ] ifError: [ :msg :ctx |
			MIMEDocument contentType: 'text/plain' content: msg ].

		newSource 
			ifNil: [ newSource _ MIMEDocument contentType: 'text/plain' content: 'Error retrieving this URL' ].

			newSource url ifNil: [
				newSource _ MIMEDocument contentType: newSource contentType  content: newSource content  url: newUrl ].

			documentQueue nextPut: newSource.
			downloadingProcess _ nil.
	] newProcess.

	downloadingProcess resume.

	"CHANGES!!!!!!"
	[recentDocuments size > currentUrlIndex] whileTrue: [
		"delete all elements in recentDocuments after currentUrlIndex"
		recentDocuments removeLast.
	].
	currentUrlIndex _ currentUrlIndex + 1.
	"end of CHANGES!!!!!!"

	^true! !

!Scamper methodsFor: 'initialization' stamp: 'AM 4/18/1999 14:25'!
initialize
	documentQueue _ SharedQueue new.
	recentDocuments _ OrderedCollection new.
	"CHANGES!!!!!!"
	currentUrlIndex _ 0.
	"end of CHANGES!!!!!!"
	currentUrl _ 'http://minnow.cc.gatech.edu/squeak.1' asUrl.
	pageSource _ ''.
	document _ HtmlParser parse: (ReadStream on: '').
	self status: 'sittin'.
	self jumpToUrl: currentUrl.
! !

!Scamper methodsFor: 'document handling' stamp: 'AM 4/18/1999 14:27'!
displayDocument: mimeDocument
	"switch to viewing the given MIMEDocument"
	|  handled  urlString |
	handled _ false.

	"add it to the history"
"CHANGES!!!!!!"
"	recentDocuments removeAllSuchThat: [ :d | d url = mimeDocument url ]."
	currentUrlIndex > recentDocuments size
		ifTrue: [recentDocuments addLast: mimeDocument].
"		ifFalse: [recentDocuments removeAt: currentUrlIndex]."
"end of CHANGES!!!!!!"
	recentDocuments size > 20 ifTrue: [ recentDocuments removeFirst ].
		
	mimeDocument mainType = 'image' 
		ifTrue: [handled _ self displayImagePage: mimeDocument].

	mimeDocument contentType = 'text/html' 
		ifTrue: [handled _ self displayTextHtmlPage: mimeDocument].

	mimeDocument contentType = 'x-application/shockwave-flash'
		ifTrue:[handled _ self displayFlashPage: mimeDocument].

	(#('audio/midi' 'audio/x-midi') includes: mimeDocument contentType) 
		ifTrue: [handled _ self processMidiPage: mimeDocument].

	"Before we display plain text files we should look at the extension of the URL"
	(handled not and:[ mimeDocument mainType = 'text']) ifTrue:[
		urlString _ mimeDocument url toText.
		(urlString endsWithAnyOf: #('.gif' '.jpg' '.pcx')) 
			ifTrue:[handled _ self displayImagePage: mimeDocument].
		(handled not and:[urlString endsWithAnyOf: #('.mid' '.midi')])
			ifTrue:[handled _ self processMidiPage: mimeDocument].
		(handled not and:[urlString endsWith: '.swf'])
			ifTrue:[handled _ self displayFlashPage: mimeDocument].
	].

	(handled not and: [ mimeDocument mainType = 'text']) ifTrue: [
		self displayPlainTextPage: mimeDocument.
		handled _ true].


	handled ifFalse: [self processUnhandledPage: mimeDocument].! !

!Scamper methodsFor: 'document handling' stamp: 'AM 4/18/1999 14:00'!
displayFlashPage: newSource
	"A shockwave flash document -- embed it in a text"
	| attrib stream player |
	stream _ (RWBinaryOrTextStream with: newSource content) binary reset.
	(FlashFileReader canRead: stream) ifFalse:[^false]. "Not a flash file"
	player _ (FlashMorphReader on: stream) processFileAsync.
	player sourceUrl: newSource url.
	player startPlaying.
	attrib _ TextAnchor new anchoredMorph: player.
	formattedPage _ ' * ' asText.
	formattedPage addAttribute: attrib from: 2 to: 2.

	currentUrl _ newSource url.
	pageSource _ newSource content.

	"remove it from the history--these thigns are too big!!"
	"ideally, there would be a smarter history mechanism that can do things like remove items when memory consumption gets too high...."
	"CHANGES!!!!!!"
"	recentDocuments removeLast."
	"end of CHANGES!!!!!!"

	self changeAll: 	#(currentUrl title hasLint lint formattedPage formattedPageSelection).
	self status: 'sittin'.
	^true! !

!Scamper methodsFor: 'document handling' stamp: 'AM 4/18/1999 14:00'!
displayImagePage: newSource
	"an image--embed it in a text"
	| image imageMorph attrib text handled |
	handled _ true.
	formattedPage _ [
		image _ ImageReadWriter formFromStream: (RWBinaryOrTextStream with: newSource content) binary reset.
		imageMorph _ ImageMorph new image: image.
		attrib _ TextAnchor new anchoredMorph: imageMorph.
		text _ ' * ' asText.
		text addAttribute: attrib from: 2 to: 2.
		text] ifError: [ :msg :ctx | handled _ false ].

	currentUrl _ newSource url.
	pageSource _ newSource content.

	"remove it from the history--these thigns are too big!!"
	"ideally, there would be a smarter history mechanism that can do things like remove items when memory consumption gets too high...."
	"CHANGES!!!!!!"
"	recentDocuments removeLast."
	"end of CHANGES!!!!!!"

	self changeAll: 	#(currentUrl title hasLint lint formattedPage formattedPageSelection).
	self status: 'sittin'.
	^handled! !





More information about the Squeak-dev mailing list