'From Squeak3.7beta of ''1 April 2004'' [latest update: #5878] on 9 April 2004 at 6:11:35 pm'! "Change Set: ScamperTranslation-dgd Date: 9 April 2004 Author: Diego Gomez Deck Making Scamper translatable "! !Scamper methodsFor: 'access' stamp: 'dgd 10/28/2003 13:27'! labelString "return the title of the current page, or nil if there is none" document == nil ifTrue: [ ^'Scamper' ] ifFalse: [ ^'Scamper: ' , (self document head title ifNil: ['(untitled)' translated]) ]! ! !Scamper methodsFor: 'browser urls' stamp: 'dgd 10/28/2003 13:30'! aboutScamperHTML "return a string of HTML which introduces Scamper" ^' {1}

{2}

{3} ' format:{ 'About Scamper' translated. 'Scamper' translated. 'This is Scamper, a WWW browser for Squeak. Here are some URL''s to start at:' translated. 'The Squeak Swiki' translated. 'Scamper''s Home Page' translated. 'Squeak''s Home Page' translated. 'The SqueakLand Home Page' translated }! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! backButtonText ^ 'Go back to previous URL in history' translated! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! forwardButtonText ^ 'Go forward to next URL in history' translated! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! historyButtonText ^ 'Return to a recent URL in history' translated! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! homeButtonText ^ 'Go to start page' translated! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! reloadButtonText ^ 'Reload page' translated! ! !Scamper methodsFor: 'button text' stamp: 'dgd 10/28/2003 13:20'! stopButtonText ^ 'Stop loading page' translated! ! !Scamper methodsFor: 'changing page' stamp: 'dgd 10/28/2003 13:33'! 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 {1}...' translated format:{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' translated]. newSource url ifNil: [ newSource _ MIMEDocument contentType: newSource contentType content: newSource content url: newUrl ]. documentQueue nextPut: newSource. downloadingProcess _ nil. ] newProcess. downloadingProcess resume. [recentDocuments size > currentUrlIndex] whileTrue: [ "delete all elements in recentDocuments after currentUrlIndex" recentDocuments removeLast. ]. currentUrlIndex _ currentUrlIndex + 1. ^true! ! !Scamper methodsFor: 'changing page' stamp: 'dgd 10/28/2003 13:33'! jumpToNewUrl "change to a new, user-specified page" | newUrl | newUrl _ FillInTheBlank request: 'url to visit' translated initialAnswer: currentUrl toText. (newUrl isNil or: [ newUrl isEmpty ]) ifTrue: [ ^self ]. self jumpToAbsoluteUrl: newUrl! ! !Scamper methodsFor: 'changing page' stamp: 'dgd 10/28/2003 13:25'! stopEverything "stop all background threads and empty queues for communicating with them; bring this Scamper to a sane state before embarking on something new" downloadingProcess ifNotNil: [ downloadingProcess terminate. downloadingProcess _ nil. ]. [ documentQueue isEmpty ] whileFalse: [ documentQueue next ]. self status: 'sittin' translated.! ! !Scamper methodsFor: 'changing page' stamp: 'dgd 10/28/2003 13:35'! submitFormWithInputs: inputs url: url method: method "Submit the current form with the given arguments" | newUrl newSource | self stopEverything. (method asLowercase ~= 'get' and: [ method asLowercase ~= 'post' ]) ifTrue: [self inform: ('unknown FORM method: {1}' translated format:{method}). ^ false ]. newUrl _ url asUrlRelativeTo: currentUrl. newUrl schemeName ~= 'http' ifTrue: [self inform: 'I can only submit forms via HTTP' translated. ^ false]. self status: 'submitting form...' translated. downloadingProcess _ [method asLowercase = 'get' ifTrue: [newSource _ newUrl retrieveContentsArgs: inputs] ifFalse: [newSource _ newUrl postFormArgs: inputs]. documentQueue nextPut: newSource. downloadingProcess _ nil] newProcess. downloadingProcess resume. ^ true ! ! !Scamper methodsFor: 'changing page' stamp: 'dgd 10/28/2003 13:35'! submitFormWithInputs: inputs url: url method: method encoding: encoding "Submit the given form with the provided inputs, url, method, and encoding" | newUrl newSource | self stopEverything. (method asLowercase ~= 'get' and: [ method asLowercase ~= 'post' ]) ifTrue: [self inform: ('unknown FORM method: {1}' translated format:{method}). ^false ]. newUrl _ url asUrlRelativeTo: currentUrl. newUrl schemeName ~= 'http' ifTrue: [self inform: 'I can only submit forms via HTTP' translated. ^ false]. self status: 'submitting form...' translated. downloadingProcess _ [method asLowercase = 'get' ifTrue: [newSource _ newUrl retrieveContentsArgs: inputs] ifFalse: [encoding = MIMEDocument contentTypeMultipart ifTrue: [newSource _ newUrl postMultipartFormArgs: inputs] ifFalse: [newSource _ newUrl postFormArgs: inputs]]. documentQueue nextPut: newSource. downloadingProcess _ nil] newProcess. downloadingProcess resume. ^ true ! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:22'! 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 _ (Character value: 1) asText. backgroundColor _ self defaultBackgroundColor. 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...." " recentDocuments removeLast." self changeAll: #(currentUrl relabel hasLint lint backgroundColor formattedPage formattedPageSelection). self status: 'sittin' translated. ^true! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:22'! displayImagePage: newSource "an image--embed it in a text" | image imageMorph attrib text handled | handled _ true. backgroundColor _ self defaultBackgroundColor. formattedPage _ [ image _ ImageReadWriter formFromStream: (RWBinaryOrTextStream with: newSource content) binary reset. imageMorph _ ImageMorph new image: image. attrib _ TextAnchor new anchoredMorph: imageMorph. text _ (Character value: 1) 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...." " recentDocuments removeLast." self changeAll: #(currentUrl relabel hasLint lint backgroundColor formattedPage formattedPageSelection). self status: 'sittin' translated. ^handled! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:22'! displayPlainTextPage: newSource "treat as plain text" pageSource _ newSource content. document _ nil. formattedPage _ pageSource withSqueakLineEndings. backgroundColor _ self defaultBackgroundColor. currentUrl _ newSource url. self status: 'sittin' translated. self changeAll: #(currentUrl relabel hasLint lint formattedPage formattedPage formattedPageSelection). ^true! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:23'! displayTextHtmlPage: newSource "HTML page--format it" | formatter bgimageUrl bgimageDoc bgimage | currentUrl _ newSource url. pageSource _ newSource content isoToSqueak. self status: 'parsing...' translated. document _ (HtmlParser parse: (ReadStream on: pageSource)). self status: 'laying out...' translated. formatter _ HtmlFormatter preferredFormatterClass new. formatter browser: self. formatter baseUrl: currentUrl. document addToFormatter: formatter. formattedPage _ formatter text. (bgimageUrl _ document body background) ifNotNil: [bgimageDoc _ (bgimageUrl asUrlRelativeTo: currentUrl) retrieveContents. [bgimage _ ImageReadWriter formFromStream: bgimageDoc contentStream binary] ifError: [:err :rcvr | "ignore" bgimage _ nil]]. bgimage ifNotNil: [backgroundColor _ bgimage] ifNil: [backgroundColor _ Color fromString: document body bgcolor]. currentUrl fragment ifNil: [ currentAnchorLocation _ nil ] ifNotNil: [ currentAnchorLocation _ formatter anchorLocations at: currentUrl fragment asLowercase ifAbsent: [ nil ] ]. self startDownloadingMorphState: (formatter incompleteMorphs). self changeAll: #(currentUrl relabel hasLint lint backgroundColor formattedPage formattedPageSelection). self status: 'done.' translated. "pardon this horrible hack...(tk)" (currentUrl authority beginsWith: 'ets.freetranslation.com') ifTrue: [ self status: 'done. **** Please Scroll Down To See Your Results ****' translated]. ^true! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:24'! processMidiPage: newSource Smalltalk at: #MIDIFileReader ifPresent: [:reader | reader playStream: (RWBinaryOrTextStream with: newSource content) reset binary. self status: 'sittin' translated. ^true]. ^false! ! !Scamper methodsFor: 'document handling' stamp: 'dgd 10/28/2003 13:38'! processUnhandledPage: newSource "offer to save it to a file" | fileName file | self status: 'sittin' translated. (newSource url toText endsWith: '.pr') ifTrue: [ (self confirm: 'Looks like a Squeak project - do you want to load it as such?' translated) ifTrue: [ ^ProjectLoading thumbnailFromUrl: newSource url toText ]. ]. (self confirm: ('unkown content-type {1}-- Would you like to save to a file?' translated format:{newSource contentType})) ifFalse: [ ^false ]. fileName _ ''. [ fileName _ FillInTheBlank request: 'file to save in' translated initialAnswer: fileName. fileName isEmpty ifTrue: [ ^self ]. file _ FileStream fileNamed: fileName. file == nil ] whileTrue. file reset. file binary. file nextPutAll: newSource content. file close. ^true! ! !Scamper methodsFor: 'initialization' stamp: 'dgd 10/28/2003 13:23'! initialize documentQueue _ SharedQueue new. recentDocuments _ OrderedCollection new. bookmark := Dictionary new. currentUrlIndex _ 0. currentUrl _ ''. pageSource _ ''. document _ HtmlParser parse: (ReadStream on: ''). self status: 'sittin' translated! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:38'! addToBookmark | key value file filename | key _ self document head title ifNil: ['Untitled' translated]. value _ self currentUrl. filename _ key,'.lin'. bookDir deleteFileNamed: filename. file _ StandardFileStream fileNamed: (bookDir fullNameFor: filename). file ifNil:[self error: 'could not save file' translated]. file nextPutAll: value asString. file close. bookmark add: (Association key: key value: value). ! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:39'! bookmark | menu sub url | menu _ (MenuMorph entitled: ' Bookmark ' translated) defaultTarget: self. menu addStayUpItem. menu addLine. menu add: 'add to bookmark' translated target: self selector: #addToBookmark. menu add: 'Import...' translated target: self selector: #importBookmark. menu addLine. bookmark keysAndValuesDo: [:name :value | url _ value. (url isKindOf: Dictionary) ifTrue: [sub _ self addNewSubMenu: url. menu add: name subMenu: sub] ifFalse: [menu add: name selector: #jumpToUrl: argument: url]]. menu popUpInWorld: self currentWorld! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:39'! createBookmarkFiles: aDirectory dict: aDictionary dirname: aName | dir file filename | (aDirectory directoryExists: aName) ifFalse:[aDirectory createDirectory: aName]. dir _ aDirectory directoryNamed: aName. aDictionary keysAndValuesDo:[:k :v | (v isKindOf: Dictionary) ifTrue:[self createBookmarkFiles: dir dict: v dirname: k] ifFalse:[filename _ k, '.lin'. dir deleteFileNamed: filename. file _ StandardFileStream fileNamed: (dir fullNameFor: filename). file ifNil:[self error: 'could not save file' translated]. file nextPutAll: v asString. file close] ].! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:40'! displayHistory "Let the user selecet a previous page to view." | menu | menu _ MenuMorph entitled: 'Recent URLs' translated. menu defaultTarget: self. menu addStayUpItem. menu addLine. recentDocuments reverseDo: [:doc | menu add: doc url toText selector: #displayDocument: argument: doc]. menu popUpInWorld: self currentWorld! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:40'! editStartPage | win textMorph | Smalltalk isMorphic ifFalse: [^ self inform: 'only works for morphic currently' translated]. win _ SystemWindow labelled: 'edit Bookmark page' translated. win model: self. textMorph _ PluggableTextMorph on: self text: #startPage accept: #startPage:. win addMorph: textMorph frame: (0@0 extent: 1@1). win openInWorld. ^ true! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:41'! importBookmark | newDirectory importLinks filename file | newDirectory _ FillInTheBlank request: 'Directory to import' translated initialAnswer: bookDir pathName. (newDirectory isNil or: [ newDirectory isEmpty ]) ifTrue: [ ^self ]. (FileDirectory new directoryExists: newDirectory) ifTrue:[importLinks _ self makeBookmark: (FileDirectory on: newDirectory). importLinks isEmpty ifFalse:[importLinks associationsDo:[:ass | bookmark add: ass. (ass value isKindOf: Dictionary) ifTrue:[self createBookmarkFiles: bookDir dict: ass value dirname: ass key] ifFalse:[filename _ ass key,'.lin'. bookDir deleteFileNamed: filename. file _ StandardFileStream fileNamed: (bookDir fullNameFor: filename). file ifNil:[self error: 'could not save file' translated]. file nextPutAll: ass value asString. file close] ] ]. ] ifFalse:[self importBookmark].! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:41'! importUrl: aFile | oldFile url strings position | oldFile _ FileStream oldFileOrNoneNamed: aFile. oldFile isBinary ifTrue:[ self error: 'not url file' translated] ifFalse:[ strings _ (oldFile contentsOfEntireFile) substrings. strings do:[:sub | ( sub includesSubString: 'URL=') ifTrue:[ position := sub findString: 'http://'. position > 0 ifTrue:[url := sub copyFrom: position to: sub size] ifFalse:[ position := sub findString: 'ftp://'. position > 0 ifTrue:[url := sub copyFrom: position to: sub size]. ] ] ]. ]. url =='' ifTrue:[ self error: 'blank file: url not exist' translated]. ^url asUrl.! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:45'! menu: menu shifted: shifted "added 'back' and 'forward' menu options: Aibek 4/18/99" | lines selections linePositions | lines _ 'back forward new URL history view source inspect parse tree go to start page edit start page bookmark' translated. linePositions _ #(2 4 6 ). selections _ #(#back #forward #jumpToNewUrl #displayHistory #viewSource #inspectParseTree #visitStartPage #editStartPage #bookmark ). downloadingProcess ifNotNil: [lines _ lines , String cr , 'stop downloading' translated. linePositions _ linePositions , selections size asOrderedCollection. selections _ selections , #(#stopEverything )]. menu labels: lines lines: linePositions selections: selections. ^ menu! ! !Scamper methodsFor: 'menus' stamp: 'dgd 10/28/2003 13:46'! viewSource "view the source HTML of this page" (StringHolder new contents: (pageSource withSqueakLineEndings)) openLabel: ('source for {1}' translated format: {currentUrl printString}).! ! !Scamper methodsFor: 'start page' stamp: 'dgd 10/28/2003 13:32'! startPage "return the contents of the user's personal start page" | file | file _ FileStream oldFileOrNoneNamed: 'StartPage.html'. file ifNil: [ ^'{1}

{1}

{2}' format:{'Personal Start Page' translated. 'This space is empty' translated} ] ifNotNil: [ ^file contentsOfEntireFile ]! ! !Scamper methodsFor: 'start page' stamp: 'dgd 10/28/2003 13:47'! startPage: newPage "fill in the contents of the user's personal start page" | file | FileDirectory default deleteFileNamed: 'StartPage.html'. [file _ FileStream fileNamed: 'StartPage.html'. file ifNil: [self error: 'could not save file' translated]. file nextPutAll: newPage asString. ] ensure: [file close]. self changed: #startPage. ^true! ! !Scamper methodsFor: 'stepping' stamp: 'dgd 10/28/2003 13:25'! step "check if a new document has arrived" | results | [documentQueue isEmpty] whileFalse: [ results _ documentQueue next. results == #stateDownloaded ifTrue: [ "images and such have been downloaded; update the page" self status: 'reformatting page...' translated. formattedPage _ document formattedTextForBrowser: self defaultBaseUrl: currentUrl. backgroundColor _ Color fromString: document body bgcolor. self changeAll: #(backgroundColor formattedPage). self status: 'sittin' translated. ] ifFalse: [ self displayDocument: results ] ]! ! !Scamper methodsFor: 'window definition' stamp: 'dgd 10/28/2003 13:47'! buttonRowPane "Create and return a pane of navigation buttons." | buttonRow | buttonRow _ AlignmentMorph new borderWidth: 0; layoutInset: 0; hResizing: #spaceFill; wrapCentering: #center; cellPositioning: #leftCenter; clipSubmorphs: true; addTransparentSpacerOfSize: (5@0). buttonRow addMorphBack: (self simpleButtonNamed: 'Back' translated action: #back text: self backButtonText); addTransparentSpacerOfSize: (5@0); addMorphBack: (self simpleButtonNamed: 'Forward' translated action: #forward text: self forwardButtonText); addTransparentSpacerOfSize: (5@0); addMorphBack: (self simpleButtonNamed: 'History' translated action: #displayHistory text: self historyButtonText); addTransparentSpacerOfSize: (5@0); addMorphBack: (self simpleButtonNamed: 'Reload' translated action: #reload text: self reloadButtonText); addTransparentSpacerOfSize: (5@0); addMorphBack: (self simpleButtonNamed: 'Home' translated action: #visitStartPage text: self homeButtonText); addTransparentSpacerOfSize: (5@0); addMorphBack: (self simpleButtonNamed: 'Stop!!' translated action: #stopEverything text: self stopButtonText); addTransparentSpacerOfSize: (5@0). ^buttonRow! ! !Scamper methodsFor: 'user interface' stamp: 'dgd 10/28/2003 13:48'! readUrlFromFile: aFile | oldFile url | oldFile _ FileStream oldFileOrNoneNamed: aFile. oldFile isBinary ifTrue:[ self error: 'not url file' translated] ifFalse:[url _ (oldFile contentsOfEntireFile) withBlanksTrimmed. url =='' ifTrue:[ self error: 'blank file: url not exist' translated]. ^url asUrl]. ! !