Squeak
  QotD    "To be or not to be" – Shakespeare
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Displaying HTML in Squeak - Notes
Last updated at 5:39 am UTC on 1 July 2018

How does the display of HTML in the Squeak Help browser work?


 AbstractHelpTopic subclass: #HtmlHelpTopic
	instanceVariableNames: 'url document selectBlock convertBlock subtopicUrls subtopics level'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Model'

contents

	| start end |
	start := (self document findString: '<body').
	start := (self document findString: '>' startingAt: start) + 1.
	end := self document findString: '</body>' startingAt: start.
	
	start > end ifTrue: [^ self document].
	
	^ ((self document copyFrom: start to: end - 1)
		copyReplaceAll: String cr with: '<br>') 
		asTextFromHtml


The Squeak wiki serves HTML pages - how are they used within Squeak?



 CustomHelp subclass: #SWikiHelp
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Help-Squeak-SWiki'

asHelpTopic

	^ HtmlHelpTopic new
		url: 'http://wiki.squeak.org/squeak';
		selectBlock: [:url | ((url beginsWith: '/squeak/') and: [(url includes: $.) not ".edit, .history, ..."]) and: [url last isDigit]];
		convertBlock: [:url | 'http://wiki.squeak.org', url];
		yourself


Comment